lapinou changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | http://www.ocaml.org | OCaml 4.01.0 announce at http://bit.ly/1851A3R | Public logs at http://tunes.org/~nef/logs/ocaml/
<philtor> So I want to be able to translate tree-like structures to graphviz dot format.
clan has quit [Quit: clan]
<philtor> I'm looking at Deriving where you can do things like:
Eyyub has quit [Ping timeout: 240 seconds]
<philtor> type fruit = Apple | Orange | Banana | Kiwi deriving (Enum)
<philtor> or for a tree type:
<philtor> type 'a tree = Leaf of 'a | Branch of 'a tree * 'a * 'a tree deriving (Functor)
<philtor> Thoughts on using deriving for this kind of thing? What about type_conv?
<philtor> I guess I'd like something like:
<philtor> type 'a tree = Leaf of 'a | Branch of 'a tree * 'a * 'a tree deriving (Dot)
darkf has joined #ocaml
<philtor> where Dot would be a pretty printer that would output the dot format.
<Drup> It seems quite doable to me. type_conv or deriving doesn't matter, it's going to be pretty much the same
finnrobi has quit [Ping timeout: 264 seconds]
<Drup> deriving may be a bit more friendly to work with
jwatzman|work has quit [Quit: jwatzman|work]
<philtor> Is it possible to write new plugin classes for deriving?
<Drup> absolutly
<Drup> there is two part in a plugin, a "runtime" part which is for base type and a "syntax extension" part to derive the code from the ADT.
clan has joined #ocaml
<philtor> Would this sort of thing be doable with a -ppx extension?
<Drup> I think deriving is going to be translated to ppx anyway.
<philtor> Yes, that's what I hear.
<philtor> I wanted to play with ppx extensions and was looking for a motivating example.
<Drup> deriving as some mecanism that are going to help you when writing this, so I think it would be easier to use it
<philtor> Is this the location of the "canonical" latest deriving: https://github.com/jaked/deriving (I ask because there's also a google code site which actually seems to have more documentation)
<philtor> ah, ok, I'll check that.
<philtor> thanks.
marr has quit [Read error: Connection reset by peer]
clan has quit [Quit: clan]
clan has joined #ocaml
freling has quit [Ping timeout: 246 seconds]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
jao has quit [Ping timeout: 276 seconds]
freling has joined #ocaml
oriba has quit [Quit: Verlassend]
racycle__ has quit [Quit: ZZZzzz…]
thomasga has quit [Quit: Leaving.]
tab1293 has joined #ocaml
tlockney is now known as tlockney_away
igitoor has quit [Ping timeout: 240 seconds]
clan has quit [Quit: clan]
finnrobi has joined #ocaml
Nuki has quit [Ping timeout: 252 seconds]
igitoor has joined #ocaml
<tautologico> llvm package seems to be up-to-date
<tautologico> ThatTreeOverTher: are you using OS X?
clan has joined #ocaml
clan has quit [Client Quit]
<Drup> tautologico: it's the example that is not up to date :)
<tautologico> oh
<tautologico> the kaleidoscope tutorial? this is old
<tautologico> I think my MiniC compiler is outdated as well
igitoor has quit [Changing host]
igitoor has joined #ocaml
q66 has quit [Quit: Leaving]
divyanshu has joined #ocaml
<Drup> yes, I tried
<Drup> (I had to fix the build script before, because it's broken)
studybot has quit [Read error: Connection reset by peer]
rgrinberg has quit [Quit: Leaving.]
<ThatTreeOverTher> tautologico, I'm using Arch Linux :P yeah Kaleidoscope is old
berke_durak has quit [Quit: Leaving.]
_obad_ has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 264 seconds]
NoNNaN has quit [Ping timeout: 272 seconds]
kig has joined #ocaml
Rota has joined #ocaml
boogie has quit [Remote host closed the connection]
boogie has joined #ocaml
tab1293 has quit [Ping timeout: 276 seconds]
ThatTreeOverTher has quit [Remote host closed the connection]
boogie has quit [Ping timeout: 255 seconds]
tlockney_away is now known as tlockney
xenocons has joined #ocaml
<xenocons> has anyone build oasis on 4.0?
<tautologico> 4.01 here
<xenocons> hmmm
malo has quit [Quit: Leaving]
<xenocons> ocamlfind whinging about not finding odn
<xenocons> i dont want to start down the garden path (dependencies etc)
<tautologico> I has some trouble when trying to install packages on a machine with OS X Mavericks
<xenocons> ah actually, i think findlib might be broken on my box
<tautologico> apparently there's a XCode bug causing problems
<xenocons> nothing is resolving
<xenocons> im on nix
<xenocons> probably butchered it with opam
kig has quit [Quit: kig]
studybot has joined #ocaml
<tautologico> the zmq update changed the API, so now IOCaml does not compile with newer zmq
<xenocons> ah
f[x] has joined #ocaml
thomasga has joined #ocaml
cesar_ has joined #ocaml
cesar_ is now known as Guest39654
boogie has joined #ocaml
thomasga has quit [Ping timeout: 252 seconds]
racycle__ has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
racycle__ has quit [Ping timeout: 240 seconds]
mcclurmc_ has joined #ocaml
Eyyub has joined #ocaml
robink has quit [Quit: No Ping reply in 180 seconds.]
clan has joined #ocaml
robink has joined #ocaml
racycle__ has joined #ocaml
Eyyub has quit [Ping timeout: 264 seconds]
alinab has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
rgrinberg has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 265 seconds]
steshaw has joined #ocaml
studybot has quit [Remote host closed the connection]
studybot has joined #ocaml
tab1293 has joined #ocaml
divyanshu has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
mcclurmc_ has quit [Remote host closed the connection]
tlockney is now known as tlockney_away
studybot has quit [Read error: Connection reset by peer]
racycle__ has quit [Quit: ZZZzzz…]
SrPx has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 252 seconds]
philtor has quit [Ping timeout: 240 seconds]
axiles has joined #ocaml
tab1293 has quit [Ping timeout: 240 seconds]
boogie has quit [Remote host closed the connection]
Guest39654 has quit [Remote host closed the connection]
studybot has joined #ocaml
f[x] has quit [Ping timeout: 255 seconds]
studybot_ has joined #ocaml
steshaw has quit [Quit: Leaving.]
tab1293 has joined #ocaml
thomasga has joined #ocaml
studybot has quit [Ping timeout: 276 seconds]
thomasga has quit [Ping timeout: 264 seconds]
rgrinberg has quit [Quit: Leaving.]
steshaw has joined #ocaml
claudiuc has quit [Remote host closed the connection]
ruzu has quit [Quit: No Ping reply in 180 seconds.]
ruzu has joined #ocaml
angerman has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
arthurb has quit [Ping timeout: 276 seconds]
arthurb has joined #ocaml
boogie has joined #ocaml
zpe has joined #ocaml
patojo has joined #ocaml
boogie has quit [Ping timeout: 264 seconds]
Membeer is now known as reynir
Simn has joined #ocaml
patojo has quit [Ping timeout: 240 seconds]
alinab has quit [Quit: leaving]
claudiuc has joined #ocaml
claudiuc_ has joined #ocaml
Submarine has quit [Remote host closed the connection]
claudiuc has quit [Ping timeout: 252 seconds]
jayprich has joined #ocaml
jayprich has quit [Read error: Connection reset by peer]
thomasga has joined #ocaml
Nuki has joined #ocaml
clan has quit [Quit: clan]
zpe has quit [Remote host closed the connection]
thomasga has quit [Ping timeout: 252 seconds]
jao has quit [Ping timeout: 252 seconds]
f[x] has joined #ocaml
mort___ has quit [Quit: Leaving.]
hyperboreean has quit [Ping timeout: 240 seconds]
hyperboreean has joined #ocaml
hyperboreean has quit [Changing host]
hyperboreean has joined #ocaml
claudiuc has joined #ocaml
boogie has joined #ocaml
studybot has joined #ocaml
ygrek has joined #ocaml
studybo__ has joined #ocaml
claudiuc_ has quit [Ping timeout: 252 seconds]
studybot_ has quit [Read error: Connection reset by peer]
clan has joined #ocaml
f[x] has quit [Ping timeout: 255 seconds]
boogie has quit [Ping timeout: 252 seconds]
studybot has quit [Ping timeout: 255 seconds]
rwmjones has quit [Ping timeout: 252 seconds]
AltGr has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
<xenocons> is there a way to delay the application of a constructor? type x = | A of int | B of int | Failure; let try_to_t (t : x) d = try t(int_of_string d) with _ -> Failure
<xenocons> (poor wording maybe)
<companion_cube> you mean, you want a function that builds A or B
<xenocons> yeah
<companion_cube> that's not in the language, you need a proper (int -> t) function
<companion_cube> even if it's just fun x -> A x
<xenocons> ah, fair enough, as i suspected, same as F#
<companion_cube> (yeah, it's a bit cumbersome)
<xenocons> another one, i notice there is no generic printf fmt string, like %A in F#, what do people normally do to get around that?
<companion_cube> there is %a
<companion_cube> it requires to pass both the printer and the printee as arguments
<companion_cube> then you can write printer combinators
<xenocons> ahhh
<companion_cube> :)
<xenocons> i wanted something simple for logging failed unions
<xenocons> type p = | X | Y | Z
<xenocons> > sprintf "%A" X;;
<xenocons> val it : string = "X"
<companion_cube> also I discovered recently %t, which doesn't take an argument
<xenocons> whats %t for?
<companion_cube> it takes a (out_channel -> unit) and calls it at the right "moment"
<xenocons> interesting
<xenocons> got the OUnit stuff working, seems pretty easy, although i dont like the idea of using a test frameworks stuff, work requirement
<xenocons> am digging optional params in ocaml, heh
<companion_cube> what is wrong with unit testing?
<xenocons> hmm not anything in particular, but makes me feel uneasy that its often used as a replacement of verification, people go 'oh unit test ran, code is 100%'
<companion_cube> hmm, you mean formal verification?
<xenocons> ounit is far superior to stuff ive used before, at least in terms of just hitting the ground running with it
<xenocons> yeah
<companion_cube> that's better of course, but much harder
<xenocons> yes
<companion_cube> then, you also have quickCheck and the likes
<companion_cube> not verification, but still nice
ollehar has joined #ocaml
<xenocons> yeah, i like quickcheck and gencheck etc, they seem fun
<xenocons> id like to try integrate them into a more robust 'test' approach
mort___ has joined #ocaml
steshaw has quit [Quit: Leaving.]
<xenocons> whats this .ml+mli -> coq description stuff like?
<xenocons> (im no expert in the field, but seems interesting)
<companion_cube> hmm, is there such a thing? Sounds nice
<xenocons> going off the first answer, last bullet http://stackoverflow.com/questions/12937082/ocaml-used-in-demonstrations
yacks has quit [Ping timeout: 240 seconds]
zpe has joined #ocaml
Muzer has quit [Ping timeout: 252 seconds]
zpe has quit [Ping timeout: 240 seconds]
Kakadu has joined #ocaml
ggole has joined #ocaml
NoNNaN has joined #ocaml
ikaros has joined #ocaml
dsheets has joined #ocaml
mort___ has left #ocaml []
mort___ has joined #ocaml
eizo has joined #ocaml
marr has joined #ocaml
SrPx has quit [Ping timeout: 240 seconds]
yacks has joined #ocaml
tautologico has quit [Quit: Connection closed for inactivity]
thomasga has joined #ocaml
<xenocons> 4.5s to load a file and stringify it, seems a bit slow for a mere 8mb
<companion_cube> what do you use to do this?
<xenocons> (the first one)
<NoNNaN> that's horrible slow, using a non-extractove method (mmap), you could read it at 1.5-2GB/sec rate
<companion_cube> xenocons: it seems weird that it takes so long
<xenocons> yes, i read that file in python in a few hundred miliseconds
<adrien_oww> stringify?
<xenocons> wait, i just found i was doing something wrong
<NoNNaN> what kind of syscalls it made during the 4.5sec ?
<xenocons> ... i had some parsing code wrapped around teh file read up ahead, heh
<xenocons> s/teh/the
<xenocons> so removing that takes it to 0.015s ;)
<xenocons> nice to know i have ~4.5sec parsing delay :\
<companion_cube> :)
yetanotherion has joined #ocaml
<yetanotherion> Hello to all
<companion_cube> o/
<yetanotherion> I'm posting back the question from #ocsigen
<xenocons> ok, so 977miliseconds to split each line at \r then again at , not too bad.. so 3.5ish seconds are lost on my actual parsing of the data :( sad
<yetanotherion> after reading
<yetanotherion> :)
<yetanotherion> and the work the openbsd team is doing right now in cleaning openssl
<yetanotherion> I have two questions
<yetanotherion> a) why cryptokit is not taken as an alternative, even some packages in opam use openssl bindings if I understood correctly
<yetanotherion> b) is writing a formally verified ssl library still a fairy tale with the current state of coq ?
<companion_cube> well, C people won't even think about using an Ocaml library
<xenocons> yetanotherion: not sure about coq, but mitls is a verified implementation of tls
<xenocons> from the folks @ inria
<yetanotherion> inria chooses f# over ocaml ?
<yetanotherion> due to .net libraries ?
<NoNNaN> more like Microsoft Research at Inria
<yetanotherion> ok
troydm has quit [Quit: What is hope? That all of your wishes and all of your dreams come true? (C) Rau Le Creuset]
<yetanotherion> thanks for the answers !
<xenocons> langs are pretty close to each other tho, should give an idea that its possible
troydm has joined #ocaml
freling has quit [Ping timeout: 246 seconds]
testcocoon has quit [Quit: Coyote finally caught me]
kig has joined #ocaml
tab1293 has quit [Remote host closed the connection]
testcocoon has joined #ocaml
rand000 has joined #ocaml
freling has joined #ocaml
Muzer has joined #ocaml
rand000 has quit [Ping timeout: 255 seconds]
boogie has joined #ocaml
clan has quit [Quit: clan]
boogie has quit [Ping timeout: 265 seconds]
maattdd has joined #ocaml
<xenocons> whats the best option to profile source lines (instead of gprof which seems to display lots about ocaml gc internals?)
<adrien_oww> well
<adrien_oww> if gprof shows stuff in the GC maybe that there's a reason :)
<xenocons> yeah, but i will have a better chance tracking it down if i know where abouts it is in relation to my src
<adrien_oww> if GC takes more than 20 of the CPU time, you can probably tweak i
<adrien_oww> t
<adrien_oww> often trade memory for CPU
<xenocons> (nb: i have never really used gprof before, so im probably not looking at the right things)
Muzer has quit [Ping timeout: 252 seconds]
<adrien_oww> well, pastebin the output
<xenocons> ok 1 tic
<xenocons> whats the func for freeing a string (caml internals)
<xenocons> i should probably check # allocs vs # frees, but i doubt it will be something like that
<mrvn> There isn't one.
<xenocons> it just gets swept?
<mrvn> it gets garbage collected
<xenocons> so if you alloc lots of strings, and see a lot of time used in GC, a suspicion may be that is the cause?
<adrien_oww> and it looks like you spend a lot of time in the GC
<adrien_oww> (either through allocations or deallocations)
rand000 has joined #ocaml
<xenocons> right
<mrvn> are you doing lots of ^?#
<adrien_oww> xenocons: can you showq the code?
<xenocons> im guessing thats due to using Str.regexp and stuff to split
<adrien_oww> likely part of the reason
<xenocons> adrien_oww: not without getting in trouble, but i can paste a generic example i guess
<xenocons> yeah
<adrien_oww> ok
<xenocons> mrvn: a bit of that yeh
Muzer has joined #ocaml
<adrien_oww> well, do you use (^) to concantenate strings?
<xenocons> yes
<xenocons> i do
<adrien_oww> like a ^ b ^ c ?
<xenocons> yes
<adrien_oww> try to replace that with either String.concat "" [ a; b; c ]
<mrvn> Then think about creating a string list instead and only at the end allocate a string the right size and blit them all together or something.
<adrien_oww> (check the corresponding doc to see why)
<adrien_oww> or use Buffer
<xenocons> ahhh
<xenocons> let me try
<mrvn> every ^ will allocate a string and copy the two parts. over and over.
<xenocons> heh, i see
<xenocons> i was doing it because it was something like a ^ " " ^ b ^ c, but i guess i can String.concat "" [a;" ";b;c]
<mrvn> could be 3 times faster
<xenocons> does replace_global allocate too? or mutate
divyanshu has quit [Quit: Computer has gone to sleep.]
<xenocons> ok that wasnt it, sill have 4.5s hmm
waneck has quit [Ping timeout: 252 seconds]
<mrvn> xenocons: http://xkcd.com/1205/
<xenocons> heh
<xenocons> very true
<xenocons> not going to stop me!
<adrien_oww> xenocons: the Buffer module is also worth looking at
<xenocons> ok, i will check that out
<adrien_oww> semantics are different but it can be worth it
<adrien_oww> xenocons: have the new profile?
dsheets has quit [Ping timeout: 245 seconds]
<xenocons> adrien_oww: shortly, i just realised i was using the bad regex replace somewhere else
<adrien_oww> heh :)
<xenocons> im guessing sprintf hurts too right
<adrien_oww> likely
<adrien_oww> Printf.bprintf!
<adrien_oww> prints to a Buffer :P
<xenocons> im guessing i should just use buffer before i go down the garden path
<xenocons> so in terms of how ocamls GC works and let bindings
<xenocons> if you do let x = "abc" if x = someval then ... does the 'x' get cleared after scope is lost?
<mrvn> no
<xenocons> and in terms of gc semantics is it different to just if "abc" = someval
<xenocons> ok
<mrvn> it might optimize to the same but I think not.
<ggole> Well, "abc" is never GCed as it is a statically allocated constant
<mrvn> right, that too
<companion_cube> bprintf rocks
<xenocons> i see
<ggole> In general the GC will traverse any value that is 'live' as seen in the frame tables
<ggole> This is necessarily a conservative approximation of true liveness
<xenocons> hmm
Nuki has quit [Remote host closed the connection]
<mrvn> e.g. values don't die until the function returns even if they are never used again.
<xenocons> i see
<ggole> I don't think that's accurate
<ggole> If you make a call f (); and f GCs, the only stuff that is traced is what the compiler thinks remains live.
<mrvn> ggole: let x = foo () in f (); g () Then x is in the frame table until g is called, right?
<mrvn> (g being the tail-recursive end of the function)
thomasga has quit [Quit: Leaving.]
<ggole> No, I don't think so
<ggole> There's more than one frametable for each function.
<mrvn> hmm
<ggole> AFAICT x wouldn't be live in the frametable for either the call to f or g.
<ggole> My understanding is that there is one table for each return address that might be seen during a GC.
<mrvn> hmm, could be. don't know the internals enough.
<ggole> And that those tables indicate the live set at those points.
<mrvn> then why is it only an approximation?
<ggole> Same reason as halting problem, Rice's theorem, etc
<xenocons> amusing
<mrvn> well, ok. You can't know which side of an if is going to be used and a value might only be alive in one branch.
<xenocons> im most certainly crazy, but i scraped out the string operations and replaced the entire function with just [ ], and i still get 4.5s ;p
<xenocons> is allocating an empty list really expensive or something?
<xenocons> wouldn't have tohught so
<def-lkb> it's free
<mrvn> [] isn't allocated iirc
<def-lkb> (empty lists are not allocated, it's a constant)
<xenocons> it must be something in this function then: let list_of_csv_fmt_data csv = split_char '\n' csv |> List.map (split_char ',')
<xenocons> only possibility i can think of
<ggole> Is csv a large string?
<xenocons> yes
<xenocons> well, 8mb ish
<ggole> Sounds like it
thomasga has joined #ocaml
mort___ has quit [Quit: Leaving.]
<mrvn> and that returns a string list list?
thomasga has quit [Client Quit]
<xenocons> yeh
<xenocons> implementation is taken from http://rosettacode.org/wiki/Tokenize_a_string#OCaml
<mrvn> you could try folding this together so you only parse and copy the data once.
<xenocons> it is getting the 4.5 seconds when i remove my actual post parsing processing
<mrvn> and with it?
<xenocons> 4.5 heh
<xenocons> (there is a milisecond flucation around 50ms i think)
<mrvn> so I guess you are at the end of optimizing the post processing.
<ggole> That isn't the best implementation of split_char, and you are probably calling it quite a few times
<xenocons> ggole: yeah, guessing around 82k times
<xenocons> which funnily enough corresponds to some of the gc stats i was seeing
<mrvn> split_char sep (String.sub str (i+1) (String.length str - i - 1))
<mrvn> That is horrible.
<mrvn> You find the first \n. Then you split the string into the first line and all the rest and repeat.
<def-lkb> It's quadratic :D
<xenocons> i confess, i plug and played :(
<mrvn> Rewrite that so it recurses over the index and only copies out the substrings.
divyanshu has joined #ocaml
rwmjones has joined #ocaml
<mrvn> like the third split_char on your url.
<xenocons> hmm, i wonder if it will get much faster than the regex
<mrvn> compare and contrast
<mrvn> Some (String.index_from str i sep) hurts too since it allocates every time.
AltGr has left #ocaml []
AltGr has joined #ocaml
boogie has joined #ocaml
<def-lkb> mrvn: it allocates 2 words, this is completely negligible
rwmjones has quit [Ping timeout: 240 seconds]
<xenocons> why is there no nice way to split a string reasonably, just ran some benchmarks and 82k lines are expected to split in 200msec on a slow day
<mrvn> try recursing over the index of the string keeping an accumulator for lines and terms and then match each char against ',', '\n' or _
<xenocons> yeah, ok
<ggole> OCaml's stdlib is very bare bones
<xenocons> does batteries improve on this with some fast string functions?
<mrvn> append to the lines and terms and reverse the terms when you add them to lines and lines at the end.
<xenocons> (actually, that split on rosetta performs slower than regex split)
<def-lkb> (if you're running it in the toplevel, that's to be expeced)
<def-lkb> expected*
<mrvn> are you using ocamlopt?
jonludlam has joined #ocaml
<xenocons> mrvn: yeh
<xenocons> ah...
<xenocons> wait a moment
<xenocons> :)
<xenocons> this might be number 2 for tonight
<mrvn> using unsafe function could also help a bit
boogie has quit [Ping timeout: 264 seconds]
<xenocons> i may have been running the wrong binary...
<mrvn> doh
thomasga has joined #ocaml
<xenocons> had a -o to ocamlopt, let me check
<xenocons> ok, so 800 msec now
<Drup> optimisations 101 :D
<xenocons> my bad
<xenocons> i need(want) to get it ~200
<ggole> Bit ugly :/
<xenocons> ggole: you just shaved off 100msec
thomasga has quit [Client Quit]
divyanshu has quit [Quit: Computer has gone to sleep.]
thomasga has joined #ocaml
thomasga has quit [Client Quit]
<xenocons> time to look into buffers
divyanshu has joined #ocaml
<ggole> At this point I would abandon split_char and write something that constructed the desired list directly
<ggole> Ie, instead of constructing line strings and splitting them, just construct them
<xenocons> ah
<ggole> Does this string come from a file?
<xenocons> yes
<ggole> You could consume the file directly, too
<xenocons> mmap?
<ggole> Just channels would probably do
<xenocons> ok, never done that in ocaml before
<xenocons> ruins the high level nature of such a parser though doesn't it?
<ggole> A bit
<xenocons> :(
<ggole> There's a lexer and parser generator if you want to go down that road
<ggole> All up to you.
<xenocons> hmm, its just a simple file format, so not at this stage
<mrvn> Should "1,foo\nbar,baz\n" be [["1"; "foo"]; ["bar"; "baz"]; [""]] or [["1"; "foo"]; ["bar"; "baz"]]?
<xenocons> empty lines will get discarded
<xenocons> so parsing as "" would be fine
<xenocons> maybe ill steal MS's split code and have a play for kicks
thomasga has joined #ocaml
<xenocons> (it gets ~250ms)
<ggole> You could try read_line and split_char
<ggole> That would be fairly easy to write and avoids constructing the large string
<xenocons> ggole: hmm, let me check to see, i am not sure if the initial split costs, or the map+split on the line
<xenocons> so splitting by '\n' takes 100msec
<xenocons> the ~700msec is lost in the List.map (split_char ',')
<xenocons> which kinda makes sense
<ggole> With the new version of split_char?
<xenocons> yeh
<ggole> Mmm.
<xenocons> 82k calls for '\n', 82k*11
<xenocons> meaning split_char gets called 902000 times ? i guess
<mrvn> xenocons: Try mine.
<xenocons> ok
petterw has quit [Ping timeout: 240 seconds]
<ousado> does ocaml have a memchr wrapper?
<xenocons> mrvn: 540 msec
<ggole> No, the closest thing is String.index{_from}, which is OCaml code
<ggole> There's no crazy SSE-optimized search under the hood.
<mrvn> xenocons: That's a 33% improvement. :)
skchrko has quit [Ping timeout: 264 seconds]
<mrvn> xenocons: Now tweak the GC values so it doesn't GC before the end.
<def-lkb> Mine is processing from right to left… Easy to fix if needed, but that avoid a lot of garbage.
<xenocons> hmm def-lkb yours is slightly slower (by 30msec) than mrvns
<flux> all this optimization but no-one is profiling.. ;-)
<mrvn> def-lkb: isn't that bad for the cache?
<xenocons> mrvn: its a big improvement thanks!, ill look into gc tune
<def-lkb> mrvn: yep, it can be
<arthurb> I am writing a test for a module Foo, the module has an abstract type "Foo.t" that is just "Bar.t". In my test, I want to test if "Foo.Make 10" is equal to "Bar.Make 10". Of course, the compiler refuses that because Foo.t and Bar.t are a priori different. Is there a way to explicitely tell the compiler that everything is ok and that Bar.t is really Foo.t, and if so how?
<def-lkb> for performance purpose, you should just avoid building the list
<xenocons> guessing ocamlrunparams are env settings
<mrvn> def-lkb: one could use a mutable list to append to the end instead of List.rev in my case. Or you could inline the "f" recursion.
<xenocons> mrvn: so i used some plug and play OCAMLRUNPARAM=s=4M,i=32M,o=150 , 420msec now
<mrvn> arthurb: in Foo add let eq_to_bar foo bar = foo = bar
<xenocons> might try tweaking those values
<xenocons> what worries me is that this is small data
<xenocons> going to have to really rethink this later
<mrvn> xenocons: Are you on 64bit?
<xenocons> yeh
<mrvn> 32bit ocaml limits strings to 16mb.
<xenocons> haven't finished reading article yet
<xenocons> ah
<xenocons> i compiled from source, hoping its 64bit ocaml
<mrvn> I once had code on 32bit where the input was 16MiB + 100 byte.
<mrvn> Just barely over the limit.
<xenocons> ill need to do some resource management later, i saw you can use bigarray to partition large strings, then i guess i can lazy process them in batches
<xenocons> mrvn: heh
<xenocons> so actual data once live will be 80-140mb every 10 mins
<xenocons> (initially)
<xenocons> i think i may probably run into issues with current approach
<mrvn> xenocons: Then you probably want to stream that instead of strings.
<xenocons> yeh hmm
<mrvn> With an input file you can mmap it. But with stdin or pipes that won't work.
<xenocons> its def a file
thomasga has quit [Quit: Leaving.]
<mrvn> you could write some C stub to split a bigarray into string list list
<mrvn> otherwise I would just read the whole file into a string.
<ggole> arthurb: you can leave the type non-abstract, or if it is a functor application you can use with constraints
<xenocons> mrvn: yeah thats an option
skchrko has joined #ocaml
<mrvn> xenocons: don't forget maintainability.
<mrvn> xenocons: The 5 seconds you save might mean 1h trying to understand the code again later.
<xenocons> yeh thats a big concern if i start going down the perf rabbit hole
<xenocons> yep
<xenocons> agree
<xenocons> but im pretty happy with the 4.5 to 420msec boundary now ;p
<xenocons> how long to debian paste bins stay up
<mrvn> xenocons: as long as you specified
hyperboreean has quit [Quit: leaving]
<xenocons> k, in a comment i wrote (* from @mrvn in #ocaml on freenode *) muhaha
<mrvn> I think my default is 72h.
<companion_cube> :D
<xenocons> so opam raped my system and utop has now abandoned me
<xenocons> time to rm -rf and reinstall it
<arthurb> I made the type non abstract, thanks
dsheets has joined #ocaml
kig has quit [Quit: kig]
petterw has joined #ocaml
boogie has joined #ocaml
hyperboreean has joined #ocaml
boogie has quit [Ping timeout: 252 seconds]
NoNNaN has quit [Remote host closed the connection]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
NoNNaN has joined #ocaml
AltGr has left #ocaml []
AltGr has joined #ocaml
AltGr has left #ocaml []
AltGr has joined #ocaml
rwmjones has joined #ocaml
studybo__ has quit [Ping timeout: 240 seconds]
studybot has joined #ocaml
zpe has joined #ocaml
cyborks has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 276 seconds]
connarks has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 255 seconds]
<whitequark> Drup: pong
<whitequark> Drup: TargetData doesn't exist anymore
<whitequark> but, there's DataLayout, and it performs most of the relevant tasks
jave has quit [Ping timeout: 276 seconds]
kig has joined #ocaml
<Drup> whitequark: unfortunatly, the interested user is not here anymore :)
<whitequark> oh
thomasga has joined #ocaml
jave has joined #ocaml
boogie has joined #ocaml
ygrek has joined #ocaml
boogie has quit [Ping timeout: 240 seconds]
divyanshu has quit [Quit: Computer has gone to sleep.]
ygrek has quit [Ping timeout: 264 seconds]
divyanshu has joined #ocaml
arthurb has quit [Ping timeout: 255 seconds]
kig has quit [Quit: kig]
studybot has quit [Remote host closed the connection]
Rota has quit [Ping timeout: 252 seconds]
waneck has joined #ocaml
kig has joined #ocaml
AltGr has left #ocaml []
AltGr has joined #ocaml
tane has joined #ocaml
racycle__ has joined #ocaml
ygrek has joined #ocaml
racycle__ has quit [Client Quit]
darkf has quit [Quit: Leaving]
angerman has quit [Quit: Bye]
boogie has joined #ocaml
lostcuaz has joined #ocaml
Rota has joined #ocaml
boogie has quit [Ping timeout: 240 seconds]
_obad_ has quit [Remote host closed the connection]
AltGr has left #ocaml []
AltGr has joined #ocaml
mcclurmc has joined #ocaml
mcclurmc has quit [Client Quit]
LU324 has quit [Remote host closed the connection]
mcclurmc has joined #ocaml
LU324 has joined #ocaml
rgrinberg has joined #ocaml
lostcuaz has quit [Ping timeout: 240 seconds]
Hannibal_Smith has joined #ocaml
yacks has quit [Ping timeout: 252 seconds]
tani has joined #ocaml
rand000 has quit [Quit: leaving]
Nahra has quit [Remote host closed the connection]
Nahra has joined #ocaml
Nahra has quit [Changing host]
Nahra has joined #ocaml
lostcuaz has joined #ocaml
lostcuaz has quit [Read error: Connection reset by peer]
lostcuaz has joined #ocaml
berke_durak has joined #ocaml
tane has quit [Ping timeout: 240 seconds]
Axman6 has quit [Read error: Connection reset by peer]
Axman6 has joined #ocaml
marr has quit [Ping timeout: 240 seconds]
<Drup> whitequark: the "right" way to load some bytecode is with Llvm_bytereader, right ?
<Drup> what is the difference between get_module and parse_bytecode ?
AltGr has left #ocaml []
yacks has joined #ocaml
boogie has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
boogie has quit [Ping timeout: 252 seconds]
tlockney_away is now known as tlockney
<whitequark> Drup: hang on, Llvm_bytereader?
<Drup> bitreader*
<Drup> =')
<whitequark> hm.... good question
<Drup> also, how do I generate the html documentation ?
<Drup> "make ocamldoc" just give me some .odoc, I have no idea what to do with them
<whitequark> ahh... get_module performs lazy deserialization. parse_bitcode does it eager
<whitequark> I think parse_bitcode should probably be gotten rid of
<Drup> ok
<whitequark> (html docs) honestly? no clue, I just use Sublime's GoTo function to look at .mli files :p
<whitequark> I think the docs ocamldoc (or any of its derivatives) generate are nearly unreadable
<Drup> I link the hyperlinks x)
<Drup> like*
ygrek has quit [Ping timeout: 252 seconds]
<whitequark> ocamldoc -html -d doc/ -load foo.odoc, perhaps?
lpw25 has joined #ocaml
angerman has joined #ocaml
kig has quit [Quit: kig]
S11001001 has joined #ocaml
S11001001 has quit [Changing host]
S11001001 has joined #ocaml
<Drup> whitequark: yep, done, thanks
<Drup> whitequark: by curiosity, why all the types Foo.t with only t inside Foo, instead of types foo
<Drup> ?
<whitequark> Drup: so that you would have Foo.t, Foo.of_string, Foo.to_string etc, instead of t_of_string, t_to_string, etc
<Drup> but, huh, you don't :D
<whitequark> I dunno, I didn't write these bindings
<kerneis> grrrr, why are constructor arguments not actual tuples?
<Drup> ok :p
<whitequark> although I would have done the same
<kerneis> </rant>
<whitequark> kerneis: SPEEDZ
<Drup> kerneis: add paranthesis
<whitequark> (they're unboxed)
<Drup> Foo of (int * string) instead of Foo of int * string
Submarine has quit [Remote host closed the connection]
<kerneis> I want it the otherway round
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<kerneis> the constructor is defined in an API I am using
<Drup> oh
<kerneis> and I'd like to do let x = (42, 43); Foo x
<def-lkb> In this case… Obj.magic
<kerneis> :-D
<Drup> yell at the maintaneur and send a patch ?
<def-lkb> Well, Obj.set_tag i maen
<def-lkb> I mean*
<kerneis> well, I also maintain the other project as it turns out
<def-lkb> :D
rz has quit [Quit: Ex-Chat]
berke_durak has quit [Remote host closed the connection]
<Drup> yell at the maintaner(yourself) and commit a fix ? :D
<kerneis> anyway, I just finished a cup of Oolong and started listening to Scarlatti; things cannot but improve
berke_durak has joined #ocaml
rand000 has joined #ocaml
<kerneis> and, indeed, the API is correct and I was stupid (misreading doc)
divyanshu has joined #ocaml
array has joined #ocaml
array is now known as Guest70563
lostcuaz has joined #ocaml
nlucaroni has quit [Quit: leaving]
AltGr has joined #ocaml
Rota has quit [Ping timeout: 252 seconds]
Hannibal_Smith has quit [Ping timeout: 240 seconds]
studybot has joined #ocaml
Hannibal_Smith has joined #ocaml
studybot_ has joined #ocaml
AltGr has left #ocaml []
AltGr has joined #ocaml
studybot has quit [Ping timeout: 240 seconds]
Kakadu has quit [Quit: Page closed]
kig has joined #ocaml
Rota has joined #ocaml
boogie has joined #ocaml
shinnya has joined #ocaml
boogie has quit [Ping timeout: 252 seconds]
eizo has quit [Ping timeout: 240 seconds]
ontologiae has joined #ocaml
ygrek has joined #ocaml
philtor has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
rz has joined #ocaml
racycle_ has joined #ocaml
divyanshu has quit [Ping timeout: 255 seconds]
divyanshu has joined #ocaml
boogie has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
jwatzman|work has joined #ocaml
boogie has quit [Remote host closed the connection]
pminten has joined #ocaml
Guest70563 has quit [Quit: Page closed]
Rota has quit [Ping timeout: 265 seconds]
shinnya has quit [Ping timeout: 252 seconds]
Kakadu has joined #ocaml
Rota has joined #ocaml
jonludlam has quit [Ping timeout: 240 seconds]
boogie has joined #ocaml
lunaryorn has joined #ocaml
ygrek_ has joined #ocaml
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
ygrek has quit [Ping timeout: 276 seconds]
<thorsten`> is there something like Haskell's Either in ocaml or do i have to build it myself?
<Drup> you have to build it
<pippijn> I don't like Either
<companion_cube> i sometimes use type 'a result = Ok of 'a | Error of string
<pippijn> companion_cube: exactly
<pippijn> but not left and right
<pippijn> I have Either-like types, too, but they are explicitly named, with descriptive constructors
<thorsten`> pippijn: it's not that horrible if you treat Ok as the "right answer" ;)
<pippijn> such as Ok and Error
<pippijn> thorsten`: I don't like Left/Right, it's meaningless
<pippijn> even if you say "Right is the right answer" meh
<ggole> I often find that I've defined option with more specific names
<pippijn> I have done that, but rarely
<pippijn> sometimes I have the None case inlined into the type
<ggole> Hmm, rename Either to Judgement and call the cases Good and Evil?
<pippijn> haha
<pippijn> yes, that is better
q66 has joined #ocaml
q66 has quit [Changing host]
q66 has joined #ocaml
<ggole> Yeah, I've done the inline not-here constructor thing a lot too
<ggole> Sometimes its cleaner, sometimes it turns out to be a mistake
<pippijn> yes
<pippijn> it's risky
<pippijn> because you lose the type not containing the None case
<pippijn> => your type is always nullable
<pippijn> which may be bad
<ggole> Yeah
divyanshu has quit [Quit: Computer has gone to sleep.]
<thorsten`> hm and as it turn's out I won't build my own Either plus the monad but I'll use plain ocaml and will raise exceptions ;)
<pippijn> haha
<pippijn> yes
<pippijn> going Either-monad in ocaml is a bad idea (for performance)
ontologiae has quit [Ping timeout: 264 seconds]
<companion_cube> it's not so bad if you use it just a little
<companion_cube> ie not in inner loops
<pippijn> yes
pminten has quit [Read error: Connection reset by peer]
lpw25 has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
Simn has quit [Ping timeout: 265 seconds]
kig has quit [Quit: kig]
Simn has joined #ocaml
divyanshu has joined #ocaml
dsheets has quit [Ping timeout: 255 seconds]
<berke_durak> anyone annoyed by the lack of %a composability of format strings when using Lwt?
jwatzman|work has quit [Quit: jwatzman|work]
<berke_durak> # fun oc -> Printf.fprintf oc "%a";;
<berke_durak> - : out_channel -> (out_channel -> 'a -> unit) -> 'a -> unit = <fun>
<berke_durak> # fun oc -> Lwt_io.printf "%a";;
<berke_durak> - : 'a -> (unit -> 'b -> string) -> 'b -> unit Lwt.t = <fun>
jwatzman|work has joined #ocaml
<berke_durak> Sorry that last line should have been: # fun oc -> Lwt_io.fprintf oc "%a";;
<berke_durak> - : Lwt_io.output_channel -> (unit -> 'a -> string) -> 'a -> unit Lwt.t
<berke_durak> so we cannot compose Lwt_io formatters using "%a".
<Drup> seems like a bug
<berke_durak> maybe Lwt tasks don't fit into the format type system?
maattdd has quit [Ping timeout: 252 seconds]
<Drup> my bet would be more than someone just got the type signature wrong :)
<berke_durak> I never understood those format types anyway
<adrien> heh
AltGr has left #ocaml []
rgrinberg1 has joined #ocaml
<berke_durak> oh yey lunchtime reading. thanks drup
rgrinberg has quit [Ping timeout: 276 seconds]
elfring has joined #ocaml
dsheets has joined #ocaml
<berke_durak> ok mystery solved... Lwt uses Printf.ksprintf to implement formatting. So that's why %a can't possibly work
<berke_durak> ksprintf produces a string and then Lwt uses that to call Lwt_io.write
<companion_cube> aww, why not kbprintf? :/
<berke_durak> yeah that would have been quite a bit better
rgrinberg1 has quit [Ping timeout: 265 seconds]
tautologico has joined #ocaml
maattdd has joined #ocaml
<mrvn> What does %a do?
<berke_durak> it allows you to use a custom formatter
<berke_durak> for example Printf.printf "My list is: %a\n" print_int_list x
<berke_durak> and then you define print_int_list oc l = List.iter (fun x -> Printf.fprintf oc " %d" x)
<companion_cube> printf "my list: %a" (print_list print_int) x is even better
maattdd has quit [Ping timeout: 252 seconds]
<berke_durak> sure I was trying to give a simple example
<companion_cube> no problem :)
<mrvn> companion_cube: doesn't printf "my list: %a" print_list print_int x work too?
lunaryorn has quit []
<companion_cube> it wouldn't
<companion_cube> print_list, in this case, would be a printer combinator
<companion_cube> %a always requires 2 arguments to the printf
<companion_cube> the printer, and the element to print
kig has joined #ocaml
<Drup> whitequark: I was trying to dump some bitcode from some c code to test inspecting it in ocaml, and was super confused : the bitcode was empty
<Drup> clang was optimizing everything out =__=
<mrvn> I was thinkinf (printf "my list: %a") would be something like (channel -> 'a), print_list : channel -> (int list -> unit) -> int list -> unit and so on.
<companion_cube> printf "my list: %a" is basically of type (channel -> 'a -> unit) -> 'a -> unit
<companion_cube> channel being either Buffer.t, string, or out_channel
<tautologico> Drup: this happens a lot, I was benchmarking some algorithms but not using the result so clang was eliminating the code and running my code superfast :)
maattdd has joined #ocaml
<Drup> tautologico: how do I disable that ?
<mrvn> That's why optimizing compilers are bad.
<Drup> =')
<NoNNaN> whitequark: do you know what happened with GuaranteedTailCallOpt ? it looks like moved to targetoptions, new/old features also coming http://lists.cs.uiuc.edu/pipermail/llvmdev/2014-April/071735.html
<tautologico> Drup: I don't know, but I was benchmarking a single function so I put code after calling it to use the result and then print something, this disabled the code elimination
<ggole> Compilers with strong DCE should really expose a "use" operation that pins results to being calculated
<ggole> Otherwise benchmarking can become a stupid game of hiding just enough information.
<mrvn> ggole: volatile void * p = (void*)res; while (p != p) { }
angerman has quit [Quit: Gone]
elfring has quit [Quit: Konversation terminated!]
<Drup> mrvn: "no compiler will be smart enough to optimize this"
<mrvn> Drup: how could it? p is volatile so p != p can have different values of p
dsheets has quit [Quit: Leaving]
dsheets has joined #ocaml
rgrinberg has joined #ocaml
waneck_ has joined #ocaml
skchrko has quit [Ping timeout: 252 seconds]
morolin has quit [Ping timeout: 245 seconds]
ontologiae has joined #ocaml
angerman has joined #ocaml
thomasga has quit [Ping timeout: 240 seconds]
maattdd has quit [Ping timeout: 252 seconds]
ontologiae has quit [Ping timeout: 240 seconds]
thomasga has joined #ocaml
rz has quit [Quit: Ex-Chat]
thomasga has quit [Quit: Leaving.]
divyanshu has quit [Quit: Computer has gone to sleep.]
thomasga has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
Thooms has joined #ocaml
thomasga has quit [Client Quit]
ygrek_ has quit [Ping timeout: 276 seconds]
tani has quit [Quit: Verlassend]
clan has joined #ocaml
claudiuc_ has joined #ocaml
claudiuc has quit [Ping timeout: 252 seconds]
clan has quit [Quit: clan]
maattdd has joined #ocaml
clan has joined #ocaml
maattdd has quit [Ping timeout: 252 seconds]
claudiuc_ has quit [Remote host closed the connection]
axiles has quit [Remote host closed the connection]
ollehar has quit [Ping timeout: 252 seconds]
<whitequark> NoNNaN: yep, that's not currently exposed in the bindings
ollehar has joined #ocaml
<whitequark> mrvn: Drup: ggole: for C, volatile is exactly intended for that. otherwise, Java (HotSpot, specifically) has a BlackHole...
angerman has quit [Quit: Bye]
<whitequark> you don't even need the loop, volatile itself provides the guarantee you want.
<whitequark> (it's all in the standard, read it :p)
thomasga has joined #ocaml
tnguyen has joined #ocaml
rz has joined #ocaml
ontologiae has joined #ocaml
mort___ has joined #ocaml
mort___ has quit [Client Quit]
lpw25 has joined #ocaml
oafa has joined #ocaml
<oafa> hello
<oafa> why does an ocaml int have a precision of 63 bits?
jao has quit [Ping timeout: 255 seconds]
<tautologico> because one bit is used to mark a word as being either a pointer to a heap block or an (unboxed) integer
<tautologico> i.e. it's a technicality of the GC and memory representation of objects in the runtime
<Drup> whitequark: does "dump_value" works on everything ?
<oafa> why is it necessary to distinguish between an unboxed integer and a heap block?
<companion_cube> for the GC
<companion_cube> it needs to know whether some value is an int, or a pointer to the heap
<flux> because ocaml has a mostly precise GC. GC follows the pointers, but doesn't follow integers like they were pointers.
thomasga has quit [Quit: Leaving.]
<tautologico> and this allows integers to be unboxed
<oafa> ah, okay.. if the runtime didn't distinguish between unboxed integers and heap blocks then the gc would be conservative?
<flux> yes
<oafa> what else are the tag bits of a heap block used for?
<oafa> does the ocaml runtime use "pointer tagging" like with ghc?
<flux> the ocaml manual has a chapter on how to interact with C, it touches the subject of data representation
thomasga has joined #ocaml
<flux> where was some other nice writeups on the subject as well but I don't quite recall how to find the,..
<ggole> Real world ocaml has some stuff on the runtime
<ggole> I don't think anything other than the low bit is used for tagging
<ggole> Heap blocks have a header word that has various information packed into it
<oafa> i see.. thanks
<whitequark> Drup: yep, on everything. functions as well
thomasga has quit [Quit: Leaving.]
claudiuc has joined #ocaml
<Drup> whitequark: then I have empty functions :(
<Drup> whitequark: is "clang -c -emit-llvm -o foo.bc foo.c" the good way to have some bitcode ?
<whitequark> Drup: yes, just fine
<whitequark> try clang -emit-llvm -S to look at assembly, or llvm-dis foo.bc
<Drup> yeah, those two give me lot's of thing
<Drup> but if I dump stuff, I have nothing
<whitequark> odd
<whitequark> do you use get_module or parse_bitcode?
maattdd has joined #ocaml
<whitequark> how do you get an llvalue?
<Drup> get_module
<Drup> "Llvm.iter_functions Llvm.dump_value m"
<whitequark> odd.
<whitequark> try parse_bitcode?
<Drup> and it gives me only this kind of stuff : "declare i32 @fibo(i32) #0"
<Drup> nothing was not a good term, it gives me something, but it's not very interesting
<Drup> (or do I assume wrongly that it would give me the complete function ?)
<whitequark> it should give you complete function
<Drup> oooh
<Drup> I replace "get_module" by "parse_bitcode" and I have everything
<Drup> mystery solved
maattdd has quit [Ping timeout: 264 seconds]
Hannibal_Smith has quit [Quit: Sto andando via]
ikaros has joined #ocaml
maattdd has joined #ocaml
tianon has quit [Quit: brb, dockerirssitime]
clan has quit [Quit: clan]
<Drup> whitequark: functions declaration, global declarations and instructions are all in the type llvalue, wouldn't it possible to split all that ?
kig has quit [Ping timeout: 240 seconds]
<Drup> and some other stuff I'm discovering each time I read a new function :p
mort___ has joined #ocaml
<whitequark> Drup: classify_value
thomasga has joined #ocaml
<Drup> huum, right, but that's not baked into the typesystem, that's runtime check :p
thomasga has quit [Client Quit]
tianon has joined #ocaml
<whitequark> yes
kig has joined #ocaml
dapz has joined #ocaml
Submarine has quit [Remote host closed the connection]
thomasga has joined #ocaml
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
clan has joined #ocaml
shinnya has joined #ocaml
clan has quit [Client Quit]
oafa has quit [Ping timeout: 240 seconds]
dapz has joined #ocaml
S11001001 has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
thomasga has quit [Quit: Leaving.]
marr has joined #ocaml
yacks has quit [Ping timeout: 264 seconds]
yacks has joined #ocaml
rand000 has quit [Ping timeout: 264 seconds]
rosaele has joined #ocaml
<rosaele> hola
rosaele has left #ocaml []
<Drup> whitequark: was type_conv already broken on trunk when you wrote your ppx tutorial ?
<whitequark> Drup: it was broken, then it was fixed, I think
<Drup> well, it's broken again ! :D
<whitequark> I have type_conv installed on my 4.02.0dev+trunk installation
<whitequark> yeah
ggole has quit []
ikaros has quit [Quit: Ex-Chat]
malo has joined #ocaml
thomasga has joined #ocaml
asmanur has quit [Remote host closed the connection]
tautologico has quit [Quit: Connection closed for inactivity]
thomasga has quit [Ping timeout: 252 seconds]
<ontologiae> Hi
<ontologiae> I need help about class and module
<ontologiae> I'm trying to define a module inside a class, by using the type of the object
Rota has quit [Ping timeout: 252 seconds]
<companion_cube> doesn't sound easy
<companion_cube> do you really need a full module in the class?
<ontologiae> companion_cube: clear ;-)
<ontologiae> It would be great
<ontologiae> I can avoid it, but it would clumsy to write
<companion_cube> I mean, do you need distinct modules for every class?
<ontologiae> I'm making a lib to managing an object by a state machine
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<Drup> I'm not sure that's possible :O
<companion_cube> or could you have one module, defining a polymorphic type that depends on the class?
<ontologiae> No, I define a polymorphic module
<ontologiae> Say StateMachine(A)(E)
<companion_cube> hmm what's a state machine to you exactly?
<companion_cube> a state type and a transition function?
<ontologiae> and I need that A is a module made withe the type of the object
dapz has joined #ocaml
<ontologiae> I made a machinery to define a hierarchical finite state machine
<companion_cube> hmm
<ontologiae> in a module "State", parameterized by E which is a module for the type for the events and A which is a module for the agent.
<ontologiae> And I would like the agent would be an object
<ontologiae> it's a full explanation with code
<companion_cube> wait, the State(A)(E).state_t doesn't depend on A nor E...
<companion_cube> anyway, your approach is probably going not to work, because you'd need a first-class module (so that it's a value)
<companion_cube> and then types cannot "escape" out of a first-class module
<ontologiae> So I have to declare an object and run my machinery by modules
<ontologiae> like Agent.process object;;
<ontologiae> ?
<companion_cube> you didn't explain why you needed so many modules
<companion_cube> couldn't you just parametrize your object with the state type, and the transition function?
<ontologiae> I avoid it because the last time, no one undertood me
<ontologiae> the idea of my lib is the following :
<ontologiae> I try to write a Multi-agent system where
<companion_cube> so far, so good
<ontologiae> agent are animated by a hierarchical finite state machine
<companion_cube> and this needs to have a distinct module for every machine?
<ontologiae> in which transition are a boolean equation which mix events and boolean condition (on the agent for instance)
<ontologiae> Yes, distinct, because I defined operation around the agent
<ontologiae> so because I want to have a lot of different type of agent
<ontologiae> I had to parameterized the agent (and the events)
<companion_cube> many agents, yes, but many state machine?
<companion_cube> +s
<ontologiae> one state machine by agent
<companion_cube> but does the definition of the state machine need to be different?
<ontologiae> No
<companion_cube> then you don't need several modules for the state machine?
<companion_cube> just storing different instances of the state machine
<companion_cube> as values
<companion_cube> not modules
<ontologiae> yes
<ontologiae> but I have to define the state machine with the type of the agent
<ontologiae> like in ocamlgraph
<companion_cube> in which way does the state machine depend on the type of the agent?
<ontologiae> i can define several type of vertex and edge
<companion_cube> but you don't define a vertex type in function of the graph it appears in
<ontologiae> for instance, when there's a change between a state and another, you can define a function which take the agent as parameter
kig has quit [Quit: kig]
clan has joined #ocaml
<ontologiae> to execute a function before the switch, or after
<ontologiae> in fact yes, for the graph
<Drup> I'm mistaken when I think you should just write something on top of ocamlgraph ?
lpw25 has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<ontologiae> I just want to make the same thing as in ocamlgraph : be able to define the agent and the event like I want
<Drup> then why don't you just use ocamlgraph ?
<ontologiae> Drup: no, it's just an example. I take it because I'm new to modules
<Drup> I mean, an automata is just a graph + some operations
<companion_cube> ontologiae: you might pass a function without passing the whole agent
<companion_cube> like, you take a (unit -> unit) value
<companion_cube> which could be (fun () -> my_agent#do_something_cool)
<ontologiae> my code work, it was so a pain
rgrinberg has quit [Ping timeout: 252 seconds]
<ontologiae> companion_cube: it's could work
<companion_cube> it's much simpler
thomasga has joined #ocaml
<ontologiae> yes, it's possible to remove all agent mention in State module
<ontologiae> but in Agent module, it's quite impossible
<ontologiae> looking my code
Simn has quit [Quit: Leaving]
<ontologiae> ahhh, maybe ?
<companion_cube> the point is, if State doesn't depend on Agent, you don't need such complications
<companion_cube> just define State once, and use the resulting module for agents
<ontologiae> It's funny, because before that, my code was very more constrains by agent type, and I though of this trick of unit -> bool function
<ontologiae> So, i have to keep the same path ;-)
<ontologiae> In fact, looking my code, I think you're right
<companion_cube> it will be *much* simpler, trust me
<ontologiae> I can remove all mention of Agent, so I can define my Agent just by E
thomasga has quit [Quit: Leaving.]
<ontologiae> Great, I'm stuck for 3 years with this code
waneck_ has quit [Remote host closed the connection]
<ontologiae> I tried a lot of strategy
<ontologiae> Thank you very much companion_cube !
<companion_cube> you're welcome
<companion_cube> good luck with your code
rgrinberg has joined #ocaml
<ontologiae> thank you
Kakadu has quit [Quit: Konversation terminated!]
Thooms has quit [Quit: WeeChat 0.3.8]
mort___ has quit [Quit: Leaving.]
madroach has quit [Ping timeout: 252 seconds]
tautologico has joined #ocaml
madroach has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
mal`` has quit [Ping timeout: 258 seconds]
mal`` has joined #ocaml
oafo has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
tlockney is now known as tlockney_away
maattdd has quit [Ping timeout: 264 seconds]