adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml MOOC http://1149.fr/ocaml-mooc | OCaml 4.02.3 announced http://ocaml.org/releases/4.02.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
superboum__ has joined #ocaml
superboum_ has quit [Quit: superboum_]
Kakadu has quit [Remote host closed the connection]
Emmanuel`_ has quit [Quit: Konversation terminated!]
Emmanuel`_ has joined #ocaml
orbifx has quit [Ping timeout: 276 seconds]
<octachron> oliveira, sorry I forgot that one need also Plugins: META(0.4). With this, opam installs the libraries, however the internal modules are not specified by the _oasis file
<octachron> so utop cannot load the libraries due to undefined internal modules...
ollehar has joined #ocaml
Anarchos has joined #ocaml
<Anarchos> my first attempt to write an ocaml maths demonstration verifier : https://github.com/Sylvain78/Preuves
ollehar has quit [Client Quit]
<Algebr> its in french!
Emmanuel`_ has quit [Quit: Konversation terminated!]
Emmanuel`_ has joined #ocaml
silver has quit [Quit: rakede]
<Anarchos> Algebr and ?
<def`> Anarchos: people on this channel are not expected to speak french
<Algebr> hard to understand non english code
<Anarchos> Algebr sorry i will keep that in mind. It is the very first commit
<Algebr> thanks! the code looks awesome
<lobo> kudos to people providing good ocaml tooling. opam-publish is awesome
octachron has quit [Quit: Leaving]
Emmanuel`_ has quit [Quit: Konversation terminated!]
Emmanuel`_ has joined #ocaml
<Algebr> yes, its nice, we need to improve oasis and oasis2opam too....
Vintila has quit [Ping timeout: 250 seconds]
<lobo> Algebr: these worked well for my simple cases. current missing piece is just on how to publish mli documentation automagically to a gh-pages branch
Emmanuel`_ has quit [Client Quit]
Bobbejaantje has left #ocaml ["Men are my passion"]
<Algebr> notty is using some nice formatting, perhaps take a gander there.
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
seangrove has joined #ocaml
hydan has quit [Ping timeout: 268 seconds]
<lobo> Algebr: thx. i'll have a look
Vintila has joined #ocaml
Reshi has quit [Ping timeout: 240 seconds]
shinnya has quit [Ping timeout: 244 seconds]
yunxing has quit [Remote host closed the connection]
rpip has quit [Ping timeout: 240 seconds]
rpip has joined #ocaml
gfixler has joined #ocaml
<Druup> seangrove: I'm late, but use syndic for rss feeds
Reshi has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
Reshi has quit [Ping timeout: 244 seconds]
struk|desk|away is now known as struk|desk
<seangrove> Druup: for generating them?
wiredsis` has quit [Ping timeout: 248 seconds]
<seangrove> Druup: I'll look into it, thanks. It still has a transitive dep on Unix, but seems like it's not a ton of work to fix that
Emmanuel`_ has joined #ocaml
Vintila has quit [Ping timeout: 276 seconds]
Reshi has joined #ocaml
rwmjones has quit [Ping timeout: 276 seconds]
atsampson has quit [Ping timeout: 260 seconds]
struk|desk is now known as struk|desk|away
seangrove has quit [Ping timeout: 240 seconds]
tennix has quit [Ping timeout: 240 seconds]
Emmanuel`_ has quit [Read error: Connection reset by peer]
FreeBirdLjj has quit []
struk|desk|away is now known as struk|desk
BitPuffin|osx has quit [Ping timeout: 240 seconds]
noddy has joined #ocaml
Haudegen has quit [Ping timeout: 276 seconds]
mcc has quit [Quit: Connection closed for inactivity]
Reshi has quit [Ping timeout: 268 seconds]
tennix has joined #ocaml
Haudegen has joined #ocaml
noddy has quit [Ping timeout: 250 seconds]
ibor has joined #ocaml
ygrek has quit [Ping timeout: 244 seconds]
Reshi has joined #ocaml
rwmjones has joined #ocaml
atsampson has joined #ocaml
Reshi has quit [Quit: WeeChat 1.4]
Algebr` has joined #ocaml
atsampson has quit [Ping timeout: 240 seconds]
atsampson has joined #ocaml
ygrek has joined #ocaml
johnelse has quit [Ping timeout: 244 seconds]
johnelse has joined #ocaml
aantron has quit [Remote host closed the connection]
ggole has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
ggole_ has joined #ocaml
ggole has quit [Ping timeout: 248 seconds]
badon_ has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
yunxing has joined #ocaml
<Algebr`> What the hell is this CamlinternalLazy.Undefined. After being plagued by lwt woes for over a month I finally got some kind of revelant information.
<flux> algebr`, # let rec a = lazy (Lazy.force a);;
<Algebr`> okay, 1. didn't realize a value could be rec as well, 2. no idea why lwt non deterministically does this
<flux> well it's probably a bit more complicated case than that
<flux> involving mutable values
<flux> but the gist is that when forcing a value it somehow ends up forcing the same value :)
<flux> I suppose it'd be easy to find out how this occurs if ocaml had a decent debugger :/
<Algebr`> right, I don't even know how to go about fixing this: Just have this stacktrace https://github.com/onlinemediagroup/ocaml-usbmux/issues/3
<Algebr`> digging through relevant lwt code to see what might be happening...
<flux> where does this "this is a bug" come from?
<flux> if from lwt then perhaps you should file a bug report?-o
<Algebr`> actually looking through source of lwt and i think its my fault (Although lwt didn't say anything about it, i might be able to make small repro test case)
Algebr` has quit [Ping timeout: 248 seconds]
ggole__ has joined #ocaml
ggole_ has quit [Ping timeout: 260 seconds]
seangrove has joined #ocaml
yunxing has quit [Remote host closed the connection]
nicholasf has quit []
martintrojer has quit [Ping timeout: 276 seconds]
martintrojer has joined #ocaml
ggole_ has joined #ocaml
ggole has joined #ocaml
ggole__ has quit [Ping timeout: 276 seconds]
troydm has quit [Ping timeout: 244 seconds]
ggole_ has quit [Ping timeout: 276 seconds]
seangrove has quit [Ping timeout: 248 seconds]
ggole_ has joined #ocaml
ggole has quit [Ping timeout: 264 seconds]
ggole__ has joined #ocaml
ggole_ has quit [Ping timeout: 268 seconds]
struk|desk is now known as struk|desk|away
oliveira has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
oliveira has joined #ocaml
oliveira has quit [Client Quit]
MercurialAlchemi has joined #ocaml
larhat has quit [Quit: Leaving.]
AlexRussia has quit [Ping timeout: 246 seconds]
freehck has joined #ocaml
thomasga has joined #ocaml
seangrove has joined #ocaml
tane has joined #ocaml
seangrove has quit [Ping timeout: 264 seconds]
butts_butts has joined #ocaml
thomasga has quit [Quit: Leaving.]
toolslive has quit [Remote host closed the connection]
djellemah has quit [Ping timeout: 276 seconds]
Mercuria1Alchemi has joined #ocaml
butts_butts has quit [Ping timeout: 244 seconds]
ibor has quit [Ping timeout: 260 seconds]
MercurialAlchemi has quit [Remote host closed the connection]
Mercuria1Alchemi has quit [Ping timeout: 260 seconds]
schive has joined #ocaml
larhat has joined #ocaml
rossberg has quit [Ping timeout: 264 seconds]
ygrek has quit [Ping timeout: 276 seconds]
thomasga has joined #ocaml
rossberg has joined #ocaml
silver has joined #ocaml
Haudegen has quit [Ping timeout: 240 seconds]
thomasga has quit [Quit: Leaving.]
seangrove has joined #ocaml
darkf has quit [Quit: Leaving]
seangrove has quit [Ping timeout: 260 seconds]
pierpa` has joined #ocaml
mal`` has quit [Ping timeout: 264 seconds]
ontologiae has joined #ocaml
Simn has joined #ocaml
seirl has left #ocaml ["WeeChat 1.2"]
malc_ has joined #ocaml
Haudegen has joined #ocaml
averell has joined #ocaml
djellemah has joined #ocaml
teiresias has quit [Ping timeout: 268 seconds]
dwillems has joined #ocaml
Kakadu has joined #ocaml
seangrove has joined #ocaml
<Kakadu> .о нщсещ
<Kakadu> oops
jwatzman|work has joined #ocaml
jwatzman|work has quit [Client Quit]
dwillems has quit [Ping timeout: 244 seconds]
seangrove has quit [Ping timeout: 244 seconds]
pyon has quit [Quit: ... the fear fades away.]
mal`` has joined #ocaml
<malc_> снкшддшс АЕЦ
FredF has joined #ocaml
ibor has joined #ocaml
nicholasf has joined #ocaml
pierpa` is now known as pierpa
nichola__ has joined #ocaml
pyon has joined #ocaml
jwatzman|work has joined #ocaml
nicholasf has quit [Ping timeout: 248 seconds]
Haudegen has quit [Ping timeout: 246 seconds]
mal`` has quit [Read error: Connection reset by peer]
<Kakadu> mrvn: Did my patchhelp you to understand yesxterday issue?
mal`` has joined #ocaml
_andre has joined #ocaml
aggelos_ has joined #ocaml
FredF has quit [Remote host closed the connection]
nicholasf has joined #ocaml
seangrove has joined #ocaml
nichola__ has quit [Ping timeout: 246 seconds]
Haudegen has joined #ocaml
seangrove has quit [Ping timeout: 260 seconds]
<freehck> Wow, a few russians have occupied the channel.
<freehck> In this case I'd like to wonder one thing. Is there in Russia some senior developer vacancies for an ocaml programmer?
<freehck> Moscow city is preferrable.
ibor has quit [Ping timeout: 252 seconds]
<Kakadu> No one I heared of
<Kakadu> Actually I have seen only one vacancy about OCaml
snhmib has joined #ocaml
_andre has quit [Read error: Connection reset by peer]
orbifx has joined #ocaml
_andre has joined #ocaml
<freehck> Kakadu: is it already closed?
<freehck> Kakadu: what's the name of the company?
<Kakadu> yep, I think that they don't do XAPI-realted stuff in Selectel
<Kakadu> anymore
<Kakadu> There were a lot of haskell code base there
<Kakadu> And they needed Xen hacjer there and I failed
<Kakadu> Ah, forget about it
<Kakadu> Life is bad
<orbifx> Bold statement
<orbifx> mrvn: here?
julien_t has joined #ocaml
tane has quit [Ping timeout: 244 seconds]
copy` has joined #ocaml
julien_t is now known as picolino
tane has joined #ocaml
nicholasf has quit [Read error: Connection reset by peer]
nicholasf has joined #ocaml
seangrove has joined #ocaml
Anarchos has joined #ocaml
seangrove has quit [Ping timeout: 246 seconds]
<Anarchos> hi everybody
troydm has joined #ocaml
foocraft has joined #ocaml
<Anarchos> how to install a printer for ocamldebug to print more explicit messages than "Invalid_demonstration(_,_)" ?
<zozozo> Anarchos: Printexc.register_printer ?
<Anarchos> zozozo oh thanks i didn't know this one
djellemah has quit [Ping timeout: 268 seconds]
fraggle_ has quit [Remote host closed the connection]
foocraft_ has joined #ocaml
BitPuffin has joined #ocaml
foocraft has quit [Ping timeout: 246 seconds]
zaquest has quit [Ping timeout: 276 seconds]
<Anarchos> zozozo and how to register a printer for values (as with #install_printer inside the toplevel)
<Anarchos> but from a module ?
<zozozo> hm.. don't know
<zozozo> but you can use whatever pretty printer you want in your exception printer
<Anarchos> zozozo even printers for #install_printer ?
<zozozo> Anarchos: I don't really understand what you mean, or even what you want to do, :p
<ggole__> #install_printer is a toplevel thing. There's no analogue outside the toplevel.
rwmjones is now known as rwmjones_mtg
ggole__ is now known as ggole
<ggole> ocamldebug does have some support for printing, but it's flaky
<Anarchos> ok
<Anarchos> i have to go.
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
<companion_cube> how's the progress on using gdb/lldb?
aantron has joined #ocaml
seangrove has joined #ocaml
fraggle_ has joined #ocaml
badon has quit [Ping timeout: 264 seconds]
badon has joined #ocaml
seangrove has quit [Ping timeout: 248 seconds]
foocraft_ has quit [Ping timeout: 240 seconds]
Vintila has joined #ocaml
aantron has quit [Remote host closed the connection]
<orbifx> How can I do a functional update of a sub-record?
<ggole> Nested with, probably
<ggole> Gets a bit clumsy
<orbifx> Hmm, will do for now.
struk|desk|away is now known as struk|desk
mettekou has joined #ocaml
<orbifx> There is a proposal to allow simpler updates.
teiresias has joined #ocaml
seangrove has joined #ocaml
<picolino> Hi there ! Does someone know if it's possible to have backtrace recording activated with js-of_ocaml ?
<picolino> In order to have them printed when using Printexc.to_string
seangrove has quit [Ping timeout: 240 seconds]
aantron has joined #ocaml
foocraft has joined #ocaml
thomasga has joined #ocaml
mettekou has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
seangrove has joined #ocaml
thomasga has quit [Remote host closed the connection]
tennix has quit [Ping timeout: 248 seconds]
<zozozo> orbifx: https://github.com/ocaml/ocaml/pull/291 if you're interested
<picolino> thx flux , I went through this already but I didn't figure out how to use it
Anarchos has joined #ocaml
<picolino> I should read it more carefully perhaps... I was loooking for a fast solution for lazy guy :p
<orbifx> zozozo: thank, I noticed that when I was looking for a solution.
<picolino> like "pass this an option to the compiler" or something like that
mettekou has joined #ocaml
<picolino> I have the following exception : output_value: abstract value (number), and I can't find what causes it.
teknozulu has joined #ocaml
ibor has joined #ocaml
mettekou has quit [Read error: Connection reset by peer]
Vintila has quit [Ping timeout: 268 seconds]
<malc_> picolino: OCAMLRUNPARAM=b and code compiled with -g should help narrowing it down
<picolino> how do you pass OCAMLRUNPARAM=b to js_of_ocaml ?
<flux> picolino, btw, you can use some function to enable that, though I don't know if it works with js_of_ocaml
<flux> it might be something like Printexc.set_backtrace true, but it might've been something else
ibor has quit [Ping timeout: 244 seconds]
<picolino> ah yes I tried that I think... didn't work... will try again just in case
<malc_> oh js_of_ocaml.. no clue there
struk|desk is now known as struk|desk|away
<picolino> It's Printexc.record_backtrace but it doesn't work
<flux> well, chances are it isn't implemented then.. you're compiling with -g right?
teknozulu has quit [Ping timeout: 252 seconds]
<picolino> yes my first try I forgot this but now I have the -g flag. I was wondering if I should pass something similar to js_of_ocaml
<picolino> I use --enable debuginfo, which seems to be related
teknozulu has joined #ocaml
tennix has joined #ocaml
wagle_ has joined #ocaml
Drup has joined #ocaml
martintrojer has quit [*.net *.split]
theblatte has quit [*.net *.split]
Druup has quit [*.net *.split]
stomp has quit [*.net *.split]
Khady has quit [*.net *.split]
def` has quit [*.net *.split]
wagle has quit [*.net *.split]
tokik has quit [*.net *.split]
lokien has quit [Ping timeout: 240 seconds]
lokien has joined #ocaml
AlexRussia has joined #ocaml
<Nazral> what would be the clean way to kill a process opened with Lwt_process.pread_lines ("python2.7", [| "python2.7"; "./getdata.py" |]) (where getdata.py loops forever)
martintrojer has joined #ocaml
theblatte has joined #ocaml
stomp has joined #ocaml
Khady has joined #ocaml
def` has joined #ocaml
tokik has joined #ocaml
nicholasf has quit [Remote host closed the connection]
emmanueloga has quit [Ping timeout: 248 seconds]
sspi has quit [Ping timeout: 248 seconds]
pootler_ has quit [Ping timeout: 248 seconds]
nicholasf has joined #ocaml
emmanueloga has joined #ocaml
sspi has joined #ocaml
ibor has joined #ocaml
pootler_ has joined #ocaml
nicholasf has quit [Ping timeout: 260 seconds]
<Enjolras> Nazral: the unix way is to use stdin. Make the process terminate when stdin is closed and make the parent process wait with waitpid
<Enjolras> i suspect there is helper for that in Lwt_process but i don't remember
superboum__ has quit [Quit: superboum__]
<seangrove> hannes: Could I use https://github.com/hannesm/tlstunnel in place of e.g. `ssh -D localhost:9009 some@server.com` (which I use for SOCKS, usually)?
picolino has quit [Ping timeout: 244 seconds]
foocraft has quit [Remote host closed the connection]
Anarchos has quit [Quit: in a far far away galaxy....]
<seangrove> Drup: .... I think I misunderstood, now that I've ripped out Calendar from Syndic and got the tests passing with a facade
<seangrove> Does Syndic generate RSS feeds? That's what I wanted to add to my site.
<Drup> Atom.write ?
<seangrove> Ok, I'll explore that. I didn't see any examples of it in tests :(
<Drup> You didn't look at the API ?
<seangrove> Drup: You mean the .mli?
d0nn1e has quit [Ping timeout: 240 seconds]
<seangrove> Everything on that link mentions parsing
<Drup> That's the same information
mettekou has joined #ocaml
<Drup> doh, dinosaure !
lokien has quit [Ping timeout: 264 seconds]
<seangrove> Thanks, looking how to create a feed now
<Drup> there are various constructors there
d0nn1e has joined #ocaml
<seangrove> OCaml community doesn't seem to have agreed on make vs create, but neither show up in that page
<seangrove> But I see, they're just functions
<seangrove> That's nice!
<companion_cube> create : unit -> something
<companion_cube> make : int -> 'a -> 'a thing
<companion_cube> :D
lokien has joined #ocaml
<seangrove> companion_cube: Is that real?
<Drup> sort of ...
<ggole> No. The make/create thing is simply inconsistent.
<ggole> See Array.make/create, Hashtbl.create, etc
<Drup> Array.create is deprecated though
<companion_cube> Array.create is deprecated, I think
<Drup> there is a sort of convention
<companion_cube> seangrove: it's more or less my impression
<Drup> which is that create makes empty thing, but needs parameters
<companion_cube> but it's not as if the stdlib was really consistent
<Drup> while make create non empty things
rks` is now known as `rks
<ggole> String.create doesn't make an empty string
<Drup> Yes, I stand by my choice of verbs :D
<companion_cube> String.create doesn't exist anymore :p
<companion_cube> well, same as Array.create actually
<Drup> the convention is rather vague anyway
<tobast> Hi
<tobast> I'm trying to implement a clean interface for a module, but I can't find any information about this precise case...
<ggole> Bigarray.M.create don't create empty things either
<tobast> I have a functor which heavily relies on its module parameter subtypes, so it would be quite dirty to do it as in Map (with Map.S which is not a functor and Map.Make which does a "with type ..."), so I define the whole module as a functor
<Drup> Well, it's not initialized (in both bigarray and byte) ...
zaquest has joined #ocaml
<tobast> say, my functor is Blah(X: SomeStuff)
<tobast> then I have to write an interface line corresponding for module PredefBlah = Blah(SomePredefinedModule)
<tobast> and that's where I can't find any clean syntax.
<companion_cube> what's Bigarray.M? oO
yunxing has joined #ocaml
<Drup> companion_cube: Bigarray.ArrayX
<companion_cube> oh -_-
<tobast> It will be easier to understand with the real code: https://github.com/tobast/ORandForest/blob/master/src/ORandForest.mli
mettekou has quit [Read error: Connection reset by peer]
M-Illandan has joined #ocaml
mettekou has joined #ocaml
orbifx2 has joined #ocaml
orbifx has quit [Ping timeout: 268 seconds]
<seangrove> Drup: Ah, it wasn't obvious to me that you can have a type and a constructur with the same name, and the docs would refelct that with e.g. `type feed = ...` and `val feed = ...`
pyon has quit [Quit: reboot]
ontologiae has quit [Ping timeout: 264 seconds]
pyon has joined #ocaml
<seangrove> dinosaure: Do I have to add the ~ns_prefix here? https://www.dropbox.com/s/p5l9amof5aovlia/Screenshot%202016-03-24%2009.55.13.png?dl=0
slash^ has joined #ocaml
wiredsister has joined #ocaml
jwatzman|work has quit [Read error: Connection reset by peer]
jwatzman|work has joined #ocaml
<flux> we should ride the wave and provide left pad in ocaml standard library. now, with batteries included!
<companion_cube> so we should have left_pad in Batteries included?
<flux> no, I said batteries, not Batteries
<ggole> What does it actually do?
<Drup> clearly no
<flux> who knows
<Drup> we need an independent package in opam
<flux> I guess some kind of padding is involved
<flux> also the left side is important
<Drup> With proper _oasis file and html documentation
<ggole> I got a vague impression of something like fun str n char -> String.make n char ^ str
<ggole> Which is a pretty hilarious thing to need a library for
<companion_cube> it's slightly more complicated
tane has quit [Ping timeout: 268 seconds]
<flux> that's not even O(n^2), are you even trying?
<companion_cube> fun str n char -> String.make (n-String.length str) char ^ str
<companion_cube> :D
<ggole> Ah, pad to length. Right.
<companion_cube> there should be a `max 0` somewhere
<companion_cube> but well, let's not bother about correctness
mettekou has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Drup> Actually, iirc, the argument "char" is optional.
<companion_cube> ok, who creates the repo?
<companion_cube> maybe we should ask Bünzli
<companion_cube> he would make a perfect API to solve this hard problem
<Drup> companion_cube: You are the Inventor Of Wheels
<Drup> you should do it
<companion_cube> nah, I would just put this in containers :/
<companion_cube> I think it would be funnier if someone wrote a "left-pad as a service" in mirage
<Drup> someone already did left-pad as a service
<Drup> too late :/
<companion_cube> but is it a unikernel? I don't think so
shinnya has joined #ocaml
orbifx2 has quit [Ping timeout: 240 seconds]
Anarchos has joined #ocaml
<flux> while fun, I might think defaulting to `Right would be more sensible ;)
<companion_cube> hmm, really?
<companion_cube> I mean, usually this is for aligning strings, right ?
tane has joined #ocaml
<flux> hmm, maybe not then. Printf.printf "%10s" pads left as well.
<companion_cube> you can "%-10s"
<companion_cube> and I realized that this was a bit more flexible than sprintf anyway
<companion_cube> because you can easily choose the padding length at runtime
larhat has quit [Quit: Leaving.]
<ggole> Can't you do that with *
<companion_cube> how do you mean?
djellemah has joined #ocaml
<flux> printf "%*%s" 10 "helo"
<flux> oops, one % extra
<companion_cube> oh
<companion_cube> amazing!!!
<companion_cube> TIL
<flux> :)
<ggole> printf is pretty nice
<companion_cube> this is very nice, indeed
<companion_cube> still, I think it's a bit hard to know
<companion_cube> (since I didn't find out about it earlier)
<ggole> You should have a handy link to the printf manual page
<companion_cube> and anyway a language can't be taken seriously without a `pad` function :p
<ggole> Because the hell with remembering all that stuff when you need it
<companion_cube> yeah, `man Printf`
<companion_cube> but still
<dinosaure> seangrove: euh, i will see this night but if you write a issue, it will be cool :)
<ggole> (I find the html a lot easier to read, but whatevs.)
<companion_cube> oh also, I think I can pad with any char, unlike sprintf
<Algebr> What is the difference between using a Lazy value and simple wrapping something in a lambda that takes unit, seems like the same thing
<companion_cube> yeah but man is faster
<ggole> True
<companion_cube> Algebr: Lazy is evaluated only once
<Algebr> Where is that state maintained, in the Lazy.t?
<companion_cube> let x = lazy (big computation; print_endline "yolo") in Lazy.force x; Lazy.force x; ()
<companion_cube> yeah, it's magic
<companion_cube> ^ the code above only {take time and print} only once
<flux> pretty easy to implement it, but I understand the ocaml implementation is fast than doing it yourself
<flux> also I wonder how well it works with ocaml-multicore..
rwmjones_mtg is now known as rwmjones
<companion_cube> probably bad
<companion_cube> badly*
<ggole> Lazy can have a bunch of tricky representations iirc
<Algebr> flux: what is the correction invocation of the printf padding trick?
<ggole> It can be a tagged int directly, a block directly, a block with a lazy tag, or a block with a forward tag
<Algebr> companion_cube: oh nice
<ggole> With a bunch of compiler tricks to use the best choice where it's obvious which that is
<Drup> ggole: and with the GC transforming them when it pleases him
<ggole> Yeah, making the forwarding work that way is very neat
<seangrove> I'm constantly running into problems like this with opam https://gist.github.com/sgrove/2aeae61647489068334b
<Algebr> ocamlfind remove syndic
<seangrove> Looks like ocamlfind thinks syndic is already installed?
<Algebr> perhaps needed to have done an opam unpin as well
<flux> algebr, Printf.printf "%*s" 42 "hello"
<Algebr> since it was already pinned someone where. flux ah, thanks I figured it out from manual as well, printf is magic, i want to know how it does this all, need to look at src.
<flux> functional unparsing is a nice whitepaper to read
<Algebr> ah, from 1998, nice
<Drup> functional unparsing is basically "printf without the types" :p
<companion_cube> flux: what's it about?
<companion_cube> m'ok
<Algebr> very short paper
<seangrove> Algebr: Are pins global across switches?
<Algebr> i think so, i wish pins were per switch
<Drup> (I don't remember if it already has the equivalent of %a)
<Algebr> or not? don't remember
<Drup> pins are per switch
<companion_cube> I was vaguely wondering whether it would be possible to use Format and output Pprint.t with it :]
<Drup> Pprint.t ?
lokien has quit [Ping timeout: 260 seconds]
<companion_cube> I mean formatting boxes
<companion_cube> as a tree
<Drup> ?
<Algebr> oh right, its the repositorys that are global
<seangrove> And what about https://gist.github.com/sgrove/40521ba64a6c56e811cc - syndic clearly shows up a bunch of times. Should it show up on the ocamlbuild invocation?
lokien has joined #ocaml
<seangrove> ocamlfind says that there isn't a package 'syndic'
<seangrove> Bah
<seangrove> Maybe `opam pin add .` isn't meant to add something to ocamlfind?
<wiredsister> seangrove: opam info syndic
<wiredsister> what does that say?
<wiredsister> specifically under "installed"
<seangrove> Says nice things!
<seangrove> (updated with ocamlfind list output)
<seangrove> Is this normal?
<wiredsister> well, looks like it's installed for you on syndic and riseos switches
<wiredsister> so nothing helpful there.
<Algebr> camlinternallazy.ml is scary
<wiredsister> Algebr: why?
<flux> Obj Obj Obj ;)
<wiredsister> seangrove: as per https://opam.ocaml.org/doc/FAQ.html, try `opam remove --force syndic` then `opam install syndic`
hydan has joined #ocaml
<seangrove> wiredsister: should I `opam pin add syndic <path>` instead of, or before `opam install syndic`, or not at all?
<wiredsister> just to sync with ocamlfind
<wiredsister> apparently you can also, get OPAM to register an install without performing the install as well with --fake
dwillems has joined #ocaml
<wiredsister> well, the pin will try to install after you add, which won't help you since we want to force the install. I don't think it matters. Just try the removal with --force and see what that gets you.
<wiredsister> I'm an OPAM noob. Just been doing a lot of mucking about in OPAM recently with getting mirage things to play nicely.
<seangrove> wiredsister: Yeah, I've hit a lot of frustrating edges between the two of them
<Algebr> there's a lot of mirage packages, i was bit by opam and find lib being out of sync, even on opam itself. small bugs.
Kakadu has quit [Quit: Page closed]
yunxing has quit [Remote host closed the connection]
<wiredsister> We'll build a wall around OPAM. Make OPAM great again.
<seangrove> I feel like the switches aren't working properly
<wiredsister> seangrove: you can always see what reality is by viewing in ~/.opam/SWITCH/
yunxing has joined #ocaml
<seangrove> We have `/Users/s/.opam/riseos/build/syndic.1.4`, but then `ocamlfind: Package syndic is already installed (file /Users/s/.opam/syndic/lib/syndic/META already exists)` when invoking `"Command ''/Users/s/.opam/syndic/bin/ocamlfind' install syndic...`
<Algebr> ocamlfind remove syndic
<Algebr> then try installing?
<seangrove> Will there are two switches there - one is riseos, the other is syndic
<seangrove> `$ which ocamlfind` -> /Users/s/.opam/riseos/bin/ocamlfind` `$ ocamlfind remove syndic` -> ocamlfind: [WARNING] No such directory: /Users/s/.opam/riseos/lib/syndic
<seangrove> Which makes sense
<seangrove> But them when trying to build, it's not looking at /Users/s/.opam/riseos, it's looking at /Users/s/.opam/syndic (another switch) for some reason
<yunxing> I would like to try out 4.03 (or whatever on ocaml/trunk), do I have to uninstall 4.02 in order to try it? is there any sandboxed environment for me to compile the code and try it?
<malc_> seangrove: please never use which, it's an abomination (bashism if you will) that should die.. `command -v' if you need to (actually portable way to do this)
<wiredsister> yunxing: no you don't need to uninstall to add a new switch. OPAM makes it very easy.
<seangrove> malc_: ? why should it die? It has the same output as command -v
<yunxing> wiredsister: thanks. Is it possible for me to tell opam to "add a switch from a given compiler source code?"
<wiredsister> yunxing: Do, `opam switch list --all` and find the experimental one you want. In your case, I think 4.03.0+trunk.
<yunxing> wiredsister: Can I modify the source code and recompile it?
<wiredsister> yunxing: yes.
<yunxing> wiredsister: thanks! I can look up for the instructions of how to do that
<wiredsister> yunxing: Yes. Switches all the way down. Although, I've never done this. I usually use switches just to have separate installs for Mirage or a switch for core.
<wiredsister> Yes, do `opam switch --help`
<wiredsister> you'll see the install and set commands
<malc_> seangrove: because it's non standard with no documentation nor promise to emit any particular output (i.e. no documentation)
<malc_> it's a bultin in bash
<malc_> an external program
<malc_> or what?
<malc_> i.e. use command -v and make the world a better place
<seangrove> What if I told you I aliased which to `command -v` in the above snippet, would that work?
<malc_> seangrove: aliased no, functioned it to do a command -v - sure
<malc_> i fail to see why you'd want to though... to save on typing? uhm..
<malc_> bottom line one is POSIX and the other is some folk wisdom
<Drup> companion_cube: https://crates.io/crates/left-pad
<companion_cube> oh dear.
<yunxing> wiredsister: hmm.. I don't see an option to install a switch from a local compiler codebase
<wiredsister> hm, does import and export not do that for you?
<yunxing> I think it somehow serializes the switch state to a single file
<Drup> seangrove: you forgot to "make distclean" twice again ?
jwatzman|work has quit [Quit: jwatzman|work]
<wiredsister> Yeah, could be. Seems to read that way from the man page.
<Algebr> Drup: ha, purple
noddy has joined #ocaml
shinnya has quit [Ping timeout: 240 seconds]
shinnya has joined #ocaml
pyon is now known as c-pyon-s
<seangrove> Drup: I assume that's a joke...?
<Drup> aren't you the one that got this issue ?
<Drup> (I just glanced at the whole discussion, sorry)
<seangrove> The ocamlfind/syndic/opam fiasco?
<seangrove> That's me, but I have to step away from it for today
quicquid has joined #ocaml
quicquid has left #ocaml [#ocaml]
noddy has quit [Ping timeout: 240 seconds]
seangrove has quit [Ping timeout: 240 seconds]
ggole has quit []
wagle_ is now known as wagle
yunxing has quit [Remote host closed the connection]
yunxing has joined #ocaml
lokien has quit [Ping timeout: 268 seconds]
octachron has joined #ocaml
Kakadu has joined #ocaml
mettekou has joined #ocaml
hxegon has joined #ocaml
julien_t has joined #ocaml
hxegon has quit [Quit: PEACE OUT]
hxegon has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
octachron has quit [Ping timeout: 252 seconds]
octachron has joined #ocaml
leyyin has joined #ocaml
yunxing has left #ocaml ["Leaving..."]
cgc_ has joined #ocaml
rwmjones is now known as rwmjones_hols
octachron has quit [Ping timeout: 276 seconds]
<cgc_> hi, why do i have to surround a constructor with brackets when i give it to a function?
Haudegen has quit [Ping timeout: 246 seconds]
<cgc_> for example: address Add
<Algebr> cgc_: for that example you don't but if the constructor took arguments then you would need to
<cgc_> for example: address Address(1,"string)*
larhat has joined #ocaml
<cgc_> why the interpreter thinks i'm giving too many arguments?
<Algebr> then need to do address (Address (10128, "Foo bar"))
<cgc_> yea, i know that, my question is why :)
<Algebr> because function application binds tightly
<wiredsister> If that starts to look cramped, @@ is your friend.
<lyxia> it would parse as (address Address) (10128, "Foo bar")
<cgc_> so the interpreter thinks Address is an argument and (10128, "Foo bar") is another?
<lyxia> yes
<Drup> the parser, not the interpreter
octachron has joined #ocaml
<leyyin> wiredsister, what is @@? I know that @ is list concatenation
<wiredsister> [g @@ f @@ x] is the same thing as [g (f (x))]
<wiredsister> it's in Pervasives
BitPuffin has quit [Ping timeout: 240 seconds]
<leyyin> nice
<wiredsister> in other words, it's a function that is the application operator
<wiredsister> yeah, I don't use it enough.
_andre has quit [Quit: leaving]
darkf has joined #ocaml
Haudegen has joined #ocaml
malc_ has left #ocaml ["ERC (IRC client for Emacs 25.0.50.2)"]
butts_butts has joined #ocaml
hxegon is now known as hxegon_AFK
hxegon_AFK is now known as hxegon
dwillems has quit [Ping timeout: 240 seconds]
acieroid`` has quit [Ping timeout: 240 seconds]
vpm has quit [Ping timeout: 240 seconds]
vpm has joined #ocaml
acieroid`` has joined #ocaml
phrst has quit [Ping timeout: 240 seconds]
schive has quit [Quit: Leaving]
phrst has joined #ocaml
mettekou has quit [Read error: Connection reset by peer]
hxegon is now known as hxegon_AFK
hxegon_AFK has quit [Quit: BRB]
hxegon has joined #ocaml
dwillems has joined #ocaml
wiredsister has quit [Read error: Network is unreachable]
wiredsister has joined #ocaml
strmpnk has quit [Ping timeout: 240 seconds]
iorivur has quit [Quit: No Ping reply in 180 seconds.]
iorivur has joined #ocaml
myst|fon has quit [Ping timeout: 240 seconds]
sz0 has quit [Ping timeout: 240 seconds]
jeroud has quit [Ping timeout: 240 seconds]
myst|fon has joined #ocaml
rom1504 has quit [Ping timeout: 240 seconds]
jeroud has joined #ocaml
cdidd has quit [Remote host closed the connection]
sz0 has joined #ocaml
strmpnk has joined #ocaml
rom1504 has joined #ocaml
Rome has joined #ocaml
julien_t has quit [Ping timeout: 244 seconds]
RomanZ5 has quit [Read error: Connection reset by peer]
julien_t has joined #ocaml
phrst has quit [Ping timeout: 246 seconds]
phrst has joined #ocaml
cgc_ has quit [*.net *.split]
hydan has quit [*.net *.split]
martintrojer has quit [*.net *.split]
theblatte has quit [*.net *.split]
stomp has quit [*.net *.split]
Khady has quit [*.net *.split]
def` has quit [*.net *.split]
tokik has quit [*.net *.split]
phrst has quit [Ping timeout: 276 seconds]
octachron has quit [Quit: Leaving]
leyyin has quit [Quit: So Long, and Thanks for All the Fish]
phrst has joined #ocaml
def` has joined #ocaml
martintrojer has joined #ocaml
stomp has joined #ocaml
theblatte has joined #ocaml
Khady has joined #ocaml
tokik has joined #ocaml
strmpnk has quit [Ping timeout: 248 seconds]
strmpnk has joined #ocaml
Haudegen has quit [Ping timeout: 244 seconds]
butts_butts has quit [Ping timeout: 268 seconds]
cdidd has joined #ocaml
hxegon is now known as hxegon_AFK
cdidd has quit [Ping timeout: 276 seconds]
hxegon_AFK has quit [Quit: BRB]
noddy has joined #ocaml
ollehar has joined #ocaml
orbifx has joined #ocaml
Haudegen has joined #ocaml
cdidd has joined #ocaml
Haudegen has quit [Ping timeout: 276 seconds]
hxegon has joined #ocaml
hxegon is now known as hxegon_AFK
hxegon_AFK is now known as hxegon
dwillems has quit [Quit: Leaving]
nicholasf has joined #ocaml
boegel has quit [Ping timeout: 268 seconds]
Kakadu has quit [Remote host closed the connection]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
boegel has joined #ocaml
chindy has joined #ocaml
tane has quit [Quit: Verlassend]
pierpa has quit [Read error: Connection reset by peer]
pierpa has joined #ocaml
chindy has quit [Remote host closed the connection]
Vintila has joined #ocaml
Haudegen has joined #ocaml