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
seangrove has quit [Ping timeout: 255 seconds]
deko-pyon has quit [Quit: Loops are hard, let's GOTO shopping!]
seangrove has joined #ocaml
seangrove has quit [Ping timeout: 248 seconds]
systmkor has quit [Quit: Leaving]
damason has quit [Ping timeout: 255 seconds]
damason has joined #ocaml
ahf_ is now known as ahf
seangrove has joined #ocaml
smandy2 has joined #ocaml
<yunxing> hey if I have a data constructor type foo = Int of int, is it possible to convert Int into a function so that I can map it?
<aantron> yunxing: using something like (fun i -> Int i)
<yunxing> I'm currently using (fun n -> Int n), just wondering if there is any other ways
<yunxing> @aantron cool, thanks
<aantron> there may be some library that can help, but i think not basic ocaml
<yunxing> aantron: I see
manizzle has joined #ocaml
maverous has joined #ocaml
<maverous> if i am doing matching how can i set a variable before an if else statement
<maverous> |(head::tail) -> let x = head+1 if x==2 then blah blah else blah;;
<aantron> let x = head + 1 in if ...
<maverous> ahhh
<maverous> thanks!
<aantron> enjoy :)
cthuluh has joined #ocaml
nuuit has joined #ocaml
teknozulu_ has joined #ocaml
teknozulu has quit [Ping timeout: 244 seconds]
NingaLea_ has joined #ocaml
jeffmo has quit [Quit: jeffmo]
yunxing has quit [Remote host closed the connection]
yunxing has joined #ocaml
maverous has quit [Quit: WeeChat 1.3]
FreeBirdLjj has joined #ocaml
NingaLea_ has quit [Quit: Textual IRC Client: www.textualapp.com]
sh0t has quit [Ping timeout: 250 seconds]
sh0t has joined #ocaml
yunxing has quit [Remote host closed the connection]
alpen has joined #ocaml
damason has quit [Ping timeout: 240 seconds]
damason has joined #ocaml
thEnigma has joined #ocaml
ygrek has quit [Ping timeout: 244 seconds]
<thEnigma> Is there a way to match unordered tuples with patterns?
<thEnigma> Something like matching (a,b) with either (1,2) or (2,1)
<aantron> match a, b with | 1, 2 | 2, 1 -> ...
<thEnigma> Both the elements in the pair are of the same type
<thEnigma> Okay,thanks.
<thEnigma> \
zoobab has quit [Ping timeout: 252 seconds]
ollehar1 has joined #ocaml
zoobab has joined #ocaml
ollehar has quit [Ping timeout: 240 seconds]
ollehar1 is now known as ollehar
ollehar has quit [Ping timeout: 240 seconds]
hunteriam has joined #ocaml
thEnigma has quit [Quit: Page closed]
sh0t has quit [Ping timeout: 250 seconds]
pierpa has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
yunxing has joined #ocaml
nicholasf has joined #ocaml
struk|desk|away is now known as struk|desk
systmkor has joined #ocaml
mac10688 has quit [Ping timeout: 244 seconds]
seangrove has quit [Ping timeout: 240 seconds]
cojy has left #ocaml [#ocaml]
teknozulu_ has quit [Ping timeout: 240 seconds]
johnelse has quit [Ping timeout: 244 seconds]
struk|desk is now known as struk|desk|away
johnelse has joined #ocaml
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 240 seconds]
yunxing_ has joined #ocaml
yunxing has quit [Read error: Connection reset by peer]
struk|desk|away is now known as struk|desk
kushal has joined #ocaml
Mercuria1Alchemi has joined #ocaml
antkong_ has joined #ocaml
teknozulu has joined #ocaml
Mercuria1Alchemi has quit [Ping timeout: 240 seconds]
hunteriam has quit [Quit: Connection closed for inactivity]
struk|desk is now known as struk|desk|away
julien_t has joined #ocaml
nicholasf has quit [Ping timeout: 250 seconds]
julien_t has quit [Ping timeout: 240 seconds]
badon has quit [Read error: Connection reset by peer]
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
toolslive has quit [Ping timeout: 250 seconds]
toolslive has joined #ocaml
badon has joined #ocaml
ygrek has joined #ocaml
nicholasf has joined #ocaml
darkf_ is now known as darkf
nicholasf has quit [Client Quit]
seangrove has joined #ocaml
antkong_ has quit [Quit: antkong_]
ggole has joined #ocaml
Kakadu has joined #ocaml
Algebr` has joined #ocaml
aantron has quit [Remote host closed the connection]
seangrove has quit [Ping timeout: 240 seconds]
<sspi> I was wondering if there is more information on multicore + effects available (besides the posts on http://kcsrk.info/)
toolslive has quit [Remote host closed the connection]
Haudegen has joined #ocaml
octachron has joined #ocaml
nojb has joined #ocaml
malc_ has joined #ocaml
j0sh has quit [Remote host closed the connection]
Simn has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
ygrek has quit [Ping timeout: 276 seconds]
malc_ has quit [Ping timeout: 255 seconds]
Sim_n has joined #ocaml
Simn has quit [Ping timeout: 250 seconds]
copy` has quit [Quit: Connection closed for inactivity]
seangrove has joined #ocaml
Haudegen has quit [Ping timeout: 244 seconds]
thomasga has joined #ocaml
systmkor has quit [Ping timeout: 255 seconds]
seangrove has quit [Ping timeout: 276 seconds]
systmkor has joined #ocaml
thomasga has quit [Quit: Leaving.]
sepp2k has joined #ocaml
<flux> seems like there's a lot of information there :)
<flux> hmm, oh those papers are probably on various subjects
<companion_cube> now I'm eager to have omae compatibility in oasis…
<companion_cube> it could improve my build times so much
<flux> companion_cube, how?
<companion_cube> omake*
<companion_cube> well omake builds in parallel!
<flux> ocamlbuild does as well.. ?
<flux> what doesn't build in parallel?
<companion_cube> ocamlbuild's parallelism is limited at best
<flux> btw, gnu make has this cool new feature -O that unscrambles output from multiple compilers running in parallel
Haudegen has joined #ocaml
<companion_cube> maybe I can also try to replace oasis with omake, following the advice of rgrinberg
infinity0 has quit [Ping timeout: 240 seconds]
<reynir> ooh, -O sounds cool
<reynir> hah, pun not intended
infinity0 has joined #ocaml
<snhmib> hello, i just wrote a object like this: http://pastebin.com/nKNrZS5M
<snhmib> is it possible to write this without going t:typ:type:typ everywhere?
<edwin> companion_cube: would be interesting to see how oasis+ocamlbuild compares with oasis+omake on your project. for ocamlbuild I usually use AlphaFeatures: compiled_setup_ml and ./configure --override ocamlbuildflags '-j\ 0'. I haven't tried the new omake PR for oasis yet
Simn has joined #ocaml
Sim_n has quit [Ping timeout: 240 seconds]
infinity0 has quit [Ping timeout: 248 seconds]
<companion_cube> -j0 picks the parallelism level automatically?
<companion_cube> edwin: heh, I should try this (I already use xocamlbuildargs)
warp has joined #ocaml
Haudegen has quit [Ping timeout: 250 seconds]
infinity0 has joined #ocaml
<edwin> companion_cube: -j0 uses unlimited parallelism, kind of like make -j
slicefd has joined #ocaml
<edwin> I usually avoid make -j cause it runs way too many jobs, but I haven't had problems with ocamlbuild running too many jobs
<edwin> from my _build/_log:
<edwin> # Parallel statistics: { count(total): 20(193), max: 8, min: 2, average(total): 3.650(1.275) }
<adrien> -j isn't -j0
<edwin> I thought it was based on the manpage, what is the difference?
jwatzman|work has joined #ocaml
<companion_cube> -j 0 does improve a bit my build time
<flux> so why is ocamlbuild slow for -j again? is this something that could be addressed with caching?
<companion_cube> I need to compare with omake
<edwin> the way it runs ocamldep could probably be improved
<companion_cube> and I feel like it recompiles too much
<companion_cube> maybe it's also oasis' fault, I'm not sure
<flux> sometimes I wish it compiled more, ie. when I wish to reproduce a file warnings and make a dummy edit & revert it to save the file, but ocamlbuild won't rebuild it.. :)
<adrien> edwin: -j means infinite, -j0 means auto
<adrien> iirc
<adrien> I need to check :P
<adrien> well, I don't have a reference for that actually
<companion_cube> still, ocamlbuild recompiles lots of .cmi that should not
<edwin> I was referring to make -j vs ocamlbuild -j0, if ocamlbuild's -j0 actually means auto then its even better :)
<edwin> there was a blogpost and a bug about ocamlbuild parallelism: http://caml.inria.fr/mantis/view.php?id=5754
<edwin> probably not the only reason why ocamlbuild is slower than omake though
orbifx has joined #ocaml
<orbifx> can output_value only take one type of input? or can it vary during runtime?
Haudegen has joined #ocaml
Sim_n has joined #ocaml
<Drup> orbifx: You should read the documentation of the Marshal module
<zozozo> orbifx: it can take anyhting as argument, so you should be able to do something like: output_value stdout 1; output_value stdout [2;3;4]; ...
<octachron> which mean that it is not really type-safe
<orbifx> Drup: was looking for quick answer to progress with my code, should go back to read it later indeed.
<orbifx> zozozo, octachron: thanks.
<orbifx> I'll put my type-unsafety hard-hat on :P
Simn has quit [Ping timeout: 240 seconds]
<orbifx> Can a type be partially applied?
<companion_cube> marshall isn't safe at all
<orbifx> companion_cube: ?
<companion_cube> well you can make OCaml segfault using Marshal :)
<orbifx> everytime? :P
<flux> just get out what you put in and you're fine.
<octachron> companion_cube, as far as I know, you cannot segfault with just output_value, isn'it? It is the demarshalling that is truly unsafe
<companion_cube> yes indeed
<companion_cube> but never demarshalling makes Marshal slightly useless
<octachron> or in other words, there is exactly one type safe implementation of function of type out_channel -> 'a -> unit: "f _out _ = ()"
<orbifx> so long I match the types correctly I should be fine, right?
<edwin> and if nothing corrupts your data before you input it again
<companion_cube> no, it can write any constant to the channel
<reynir> uh-oh! I made a mistake
<reynir> I was making a quick change in the opam repository and wanted to test it so I used the new opam binary. Now ~/.opam reports a newer version that the opam I have installed
<ggole> octachron: magic polymorphic functions means that isn't really true
<companion_cube> you... you mean (=) is a lie? ;_;
<ggole> eg, you could use = to write a boolean indicating whether the argument is a NaN
<reynir> Any ideas how I can recover?
<flux> reynir, yes, restore backups.. :-)
<octachron> companion_cube, right. rather "f _out _ = g out"
<flux> (sorry)
<companion_cube> heh
<reynir> :(
<reynir> Can't I use the new opam to dump a list of packages, wipe ~/.opam and reinstall?
ia0 has quit [Quit: reboot]
<companion_cube> opam switch export/import, I think
<octachron> ggole, magic polymorphic functions more or less assume that you have not an 'a but an 'a ocaml_value and know something about the ocaml value representation, isn'it?
<companion_cube> be prepared to compile though
<flux> reynir, btw, you could do what I do, for future: put your .opam in git
<flux> reynir, and then forget to ever commit it..
<ggole> Yeah, they break parametricity by inspecting the representation
<companion_cube> not the whole dir?!
<flux> is there some opam hook I could use to auto-commit?
<flux> companion_cube, sure, why not?
<companion_cube> it's big
<companion_cube> putting that many binaries into git...
<flux> not that many gigabytes.
<flux> storage is cheap :
<flux> :)
<companion_cube> hmm
ia0 has joined #ocaml
<reynir> Thanks, I'll try switch export/import :)
<orbifx> Can a type be partially applied? Curried, like a function?
<edwin> you could commit from a cronjob, or use an rsnapshot cronjob to have local backups (it uses hardlinks to share files that haven't changed)
seangrove has joined #ocaml
<edwin> problem is opam might be updating at the same time you snapshot and then it won't be a consistent snapshot
<flux> orbifx, no
<flux> orbifx, well, I suppose it depends what you mean. you mean a constructor?
<flux> constructors cannot be partially applied
<orbifx> flux: yeah
<flux> you can of course create aliases to polymorphic types, but I suppose that's not at all what you mean
<flux> orbifx, typical solution is to create a function for the constructor
<orbifx> flux: I want to call a different constructor on the same value depending on a condition.
<reynir> Wee, compiling 93 packages
<flux> let op a b c = Op (a, b, c)
toolslive has joined #ocaml
<orbifx> flux: op -> Op ??
<flux> orbifx, ?
seangrove has quit [Ping timeout: 240 seconds]
<flux> say your type was type ('a, 'b, 'c) op = Op of ('a * 'b * 'c) then that definition would let you 'partially apply' the constructor
<toolslive> opam depext conf-libev.4-11 states everything was installed, but opam install conf-libev can't seem to find it. (but there is a /usr/include/ev.h) . anybody any ideas?
<orbifx> but op and Op would have to be hardcoded?
<orbifx> can I store the value of the contructor? let c = Contructor ?
kushal has quit [Quit: Leaving]
<ggole> (non-nullary) constructors aren't values in OCaml
<companion_cube> and the type system doesn't support partially applied types
simn__ has joined #ocaml
seangrove has joined #ocaml
Sim_n has quit [Ping timeout: 250 seconds]
teknozulu has quit [Ping timeout: 244 seconds]
<orbifx> okie
<orbifx> thanks
seangrove has quit [Ping timeout: 250 seconds]
mearnsh has joined #ocaml
_andre has joined #ocaml
seangrove has joined #ocaml
<edwin> toolslive: there is a log_file here ~/.opam/repo/default/packages/conf-libev/conf-libev.4-11/files/discover.ml, try to print that for more details
Sim_n has joined #ocaml
simn__ has quit [Ping timeout: 240 seconds]
mearnsh is now known as bounb
bounb has quit [Changing host]
bounb has joined #ocaml
seangrove has quit [Ping timeout: 255 seconds]
bounb has left #ocaml ["0"]
<orbifx> when the compile is complaining "Error: No implementations provided for the following modules", is it asking for .cma file?
<orbifx> what does it refer to by implementation?
aantron has joined #ocaml
darkf has quit [Quit: Leaving]
<orbifx> ok, was the order of the modules.. it's important :P
Haudegen has quit [Ping timeout: 252 seconds]
simn__ has joined #ocaml
Sim_n has quit [Ping timeout: 250 seconds]
Haudegen has joined #ocaml
Sim_n has joined #ocaml
seangrov` has joined #ocaml
simn__ has quit [Ping timeout: 240 seconds]
seangrov` has quit [Ping timeout: 252 seconds]
<aantron> Drup: so what is "wrap" for in tyxml? is it needed for eliom somehow?
<Drup> among other things
<Drup> this is actually documented !
<Drup> (I know, I document only the part that no one uses)
tane has joined #ocaml
<flux> planet.ocaml.org has this link: https://forge.ocamlcore.org/forum/forum.php?forum_id=929 - but it's permission denied. I wonder if here's someone who's able to fix it?-)
<aantron> ah thank you
<Drup> oh, there is a bug in the markup
kushal has joined #ocaml
antkong has joined #ocaml
<Drup> aantron: is it helpful ?
<aantron> perhaps. sanity check: i am looking at list_wrap / Xml_wrap.T.tlist - it seems i will have to replace code that assembles child lists using :: with code that uses Xml_wrap.T.cons (through the (Html5|Svg).Xml.W.cons)
<aantron> -the*
<Drup> Yes
<aantron> oh well. the parse tree dump was briefly beautiful :)
<orbifx> companion_cube: did you tell me yesterday if you libraries support infinit lists?
<companion_cube> yes, they do
<companion_cube> but you shouldn't try to consume an infinite sequence of elements, of course
<companion_cube> use take_while/take or something like this before
<companion_cube> unless you are sure the sequence isn't infinite any more
<Drup> aantron: do your testing with no wraping, we can figure it out later
<companion_cube> orbifx: e.g. Sequence.repeat 0 or Gen.repeat 0 are infinite lists of 0
<orbifx> ok
<orbifx> I might get to use them soon, not sure yet.
<companion_cube> :)
<aantron> Drup: speaking of testing, what is the best way for tyxml besides repeated manual examination of cases?
<aantron> i was considering using ounit or something just for the ppx, but i think you're in a better position to decide this for all of tyxml :)
<Drup> That's the issue, I'm not sure what to test
<Drup> Ounit is not going to work if we also want to test things that are forbidden by type checking
<aantron> it does work, just have to parse compiler output, etc., so its a bit nasty
<Drup> Well, if you can make it work witout making it awfully complicated, okay
<aantron> as for what to test, for the rest of tyxml, you could serialize output and check against expectations, and/or run through some HTML validator
<Drup> The option we choose in js_of_ocaml is to pipe a file to the toplevel and diff the output against the expected one
<Drup> (like in the compiler)
<Drup> this also allows to test error messages and locations for the ppx, which is very important
<aantron> exactly
<aantron> the ppx would greatly benefit from testing i think
<Drup> Oh, we need to test the ppx, at least for locations
<aantron> i will hold off on it for now though, to stay focused on the immediate task
lordf has joined #ocaml
antkong has quit [Quit: antkong]
lordf has quit [Read error: Connection reset by peer]
struk|desk|away is now known as struk|desk
BitPuffin has joined #ocaml
<reynir> companion_cube: Thanks for the tip regard opam switch {ex,im}port, it worked :)
seangrov` has joined #ocaml
toolslive has quit [Ping timeout: 240 seconds]
simn__ has joined #ocaml
<octachron> Drup, what is the best way to report dead links on Eliom main page?
Sim_n has quit [Ping timeout: 250 seconds]
seangrov` has quit [Ping timeout: 244 seconds]
<octachron> thanks
<companion_cube> so, I suppose I will switch to `result` soon
dhil has joined #ocaml
<companion_cube> since the poly variant error type is going out of fashion
nojb has quit [Ping timeout: 240 seconds]
toolslive has joined #ocaml
hanshenrik__ has joined #ocaml
seangrov` has joined #ocaml
hanshenrik_ has quit [Ping timeout: 248 seconds]
kushal has quit [Quit: Leaving]
larhat has joined #ocaml
Jane-PC has joined #ocaml
theblatte has quit [Ping timeout: 244 seconds]
theblatte has joined #ocaml
nojb has joined #ocaml
foolishmonkey has quit [Remote host closed the connection]
foolishmonkey has joined #ocaml
seangrov` has quit [Remote host closed the connection]
seangrov` has joined #ocaml
dariol has joined #ocaml
dariol has left #ocaml [#ocaml]
lordf has joined #ocaml
dhil has quit [Ping timeout: 240 seconds]
struk|desk is now known as struk|desk|away
dhil has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 255 seconds]
seangrov` has quit [Remote host closed the connection]
seangrov` has joined #ocaml
struk|desk|away is now known as struk|desk
Sim_n has joined #ocaml
simn__ has quit [Ping timeout: 240 seconds]
seangrov` has quit [Ping timeout: 252 seconds]
<flux> so few commits on ocaml-multicore lately!-(
sh0t has joined #ocaml
manizzle has quit [Ping timeout: 240 seconds]
<companion_cube> maybe they have a separate branch for effects and work on it instead
Harzilein has joined #ocaml
<Harzilein> hi
<companion_cube> hi
<Harzilein> i was wondering about this kind of question: http://programmers.stackexchange.com/questions/257757/why-implement-a-lexer-as-a-2d-array-and-a-giant-switch in terms of "how can i maintain partial readability in generated lexers" and was wondering if the typical ocamllex style with "and entrypoint" was extended in any project to combine handcrafted with table-driven lexing
<companion_cube> I think you're not supposed to read the code generated by ocamllex
<companion_cube> unless you're an ocamllex developper
<Drup> Harzilein: do you have any reason to handcraft the lexer ?
<Drup> (There are arguments for parser, that I don't find convincing, but they exist. I never heard anyone argue for handcrafting lexers)
simn__ has joined #ocaml
kushal has joined #ocaml
<Drup> tl;dw ?
<companion_cube> rob pike explains how cool it is to hand-write a lexer in Go, if I remember correctly
<Drup> Yeah
Sim_n has quit [Ping timeout: 250 seconds]
<Drup> Right, I don't want to waste time argue with that :)
<companion_cube> you would have to argue with rob pike anyway
<Drup> Precisely my point :D
<companion_cube> it would probably degenerate into error handling, polymorphism and nil
<companion_cube> *shivers*
<Harzilein> i remember how that was mentioned. i think it's some kind of nih drive, so it might not be rational. but imagine i have my hand written toy lexer and some motivation might vanish if i were to rewrite it first, instead of seeing it's still in there and i can flush all the rest and start over ;)
<Harzilein> s/seeing/being able to see/
<companion_cube> you mean it's easier to rewrite rather than modify?
struk|desk is now known as struk|desk|away
jeffmo has joined #ocaml
Associat0r has joined #ocaml
<Harzilein> companion_cube: i don't want to modify the generated lexer, my (largely fictitious) scenario is the other way around: i have some hand crafted primitives that work nicely, but now i want to use table driven lexing for the more tedious stuff. it'd be nice to be able to integrate their logic with each other
Associat0r has left #ocaml [#ocaml]
seangrov` has joined #ocaml
yunxing has joined #ocaml
<companion_cube> Harzilein: sounds difficult
<Harzilein> so you are saying i might not find someone employing such a thing because it'd be tedious in itself?
yunxing_ has quit [Read error: Connection reset by peer]
dhil has quit [Quit: Leaving]
<companion_cube> well I mean, mixing a generated lookup table with hand-written primitive token lexers sounds difficult
<companion_cube> unless, say, the handcrafted tokens start with unambiguous characters, or something like this
pierpa has joined #ocaml
Sim_n has joined #ocaml
simn__ has quit [Ping timeout: 240 seconds]
<orbifx> is there a convention for distinguishing type names for mere values?
<companion_cube> not afaik, but they do not occur in the same places
<orbifx> you mean in expressions? Or in files?
<companion_cube> in expressions
<orbifx> ok
copy` has joined #ocaml
noplamodo has quit [Changing host]
noplamodo has joined #ocaml
eeks_ has joined #ocaml
larhat has quit [Quit: Leaving.]
larhat has joined #ocaml
larhat has quit [Client Quit]
simn__ has joined #ocaml
Sim_n has quit [Ping timeout: 250 seconds]
Mercuria1Alchemi has joined #ocaml
antkong has joined #ocaml
sz0 has joined #ocaml
antkong has quit [Ping timeout: 244 seconds]
seangrov` has quit [Ping timeout: 252 seconds]
seangrov` has joined #ocaml
seangrov` has quit [Remote host closed the connection]
th5 has joined #ocaml
seangrov` has joined #ocaml
Sim_n has joined #ocaml
simn__ has quit [Ping timeout: 240 seconds]
seangrov` has quit [Remote host closed the connection]
seangrov` has joined #ocaml
seangrov` has quit [Remote host closed the connection]
Algebr` has joined #ocaml
<flux> well, there is actually the convention of sharing names.. :)
<Drup> module Foo : FOO = struct let foo : foo = Foo end
<Drup> ♥
shinnya has joined #ocaml
<flux> I foofoo you as well <3
Algebr` has quit [Ping timeout: 248 seconds]
<octachron> Drup, you forgot a ~foo label
hcarty has joined #ocaml
yunxing has quit [Remote host closed the connection]
* ggole pities the foo
<Drup> (this is actually a pretty complete overview of all the syntaxes in ocaml)
<companion_cube> exception%foo, wow
<hcarty> lazy%foo[@foo]
<Drup> Well, it covers all the keywords!
<ggole> as%foo?
slash^ has joined #ocaml
<ggole> Missing! Your test suite sucks!
<companion_cube> let%foo[%foo] module[@foo] Foo = struct%foo[@foo] type foo = Foo[@foo] end
<Drup> ggole: yeah, I didn't added that one
<ggole> I can't imagine it mattering too much...
<Drup> well, I avoided it because it was in infix position
<Drup> For everything else, only the keyword in leading prefix position can be annotated
<octachron> Drup, I am now reassured that "foo" identifiers shall be correctly tested within the compiler. At last, I can breath.
<Drup> :D
lordf has quit [Ping timeout: 244 seconds]
orbifx has quit [Ping timeout: 244 seconds]
lokien_ has joined #ocaml
Jane-PC has quit [Ping timeout: 244 seconds]
<companion_cube> Drup: you forgot to test for bar…
<Drup> companion_cube: contribution welcome
<companion_cube> let's write a test generator for test cases
<companion_cube> (https://xkcd.com/974/)
sepp2k has quit [Quit: Leaving.]
kushal has quit [Quit: Leaving]
Jane-PC has joined #ocaml
<zozozo> companion_cube: do you plan on testing your test generator ?
malc_ has joined #ocaml
<companion_cube> sure, with a random test generator generator à la quickcheck
toolslive has quit [Ping timeout: 250 seconds]
tftio has joined #ocaml
<aantron> Drup: one thing worth testing is compilation, since some of the apparently lesser-used svg attributes have polymorphic variant tags that dont match sets accepted by elements (missing underscores and the like)
warp has quit [Quit: /!\ Session Terminated. https://i.imgur.com/vyxw0mB.gif]
<aantron> im finding some right now and going to add to the pull request
<Drup> aantron: I fixed so many of thoses ...
<Drup> Yes
octachron has quit [Quit: Leaving]
<Drup> Ideally, this should be quite easy to check statically
<Drup> (with your crawler, I mean)
<aantron> well my crawler isnt going to make an effort to check these against element sets, its only goal is to provide the minimum information necessary for the ppx to build a parse tree that passes children to elements correctly, and the like
<aantron> but i suppose it can be modified or expanded upon..
tftio has quit [Client Quit]
<aantron> but it seems to me that it may be better to enumerate if possible, since there are other things worth testing besides the types matching up (like the output of printing)
lokien has joined #ocaml
<Drup> Yes
<lokien> how to substitute a "for i in ..." loop here?
tftio has joined #ocaml
<lokien> List.iter?
<Leonidas> I was thinking of taking data from a socket and putting it in a queue and then running another lwt process to take data out from a queue. That's what I would've done with threads. But when using preemption in lwt, does that even make sense?
<Leonidas> lokien: "here"? where?
<lokien> Leonidas: in ocaml, sorry
<aantron> where in ocaml?
<lokien> in the ocaml code
<lokien> :^(
<Leonidas> lokien: depends, sometimes it's .iter, sometimes it's .map
<aantron> ocaml has for loops also
<Leonidas> sometimes you also just want to reduce/fold.
<Drup> And sometimes it's still for :D
<Leonidas> True :)
<lokien> what about doing something for each char in a string?
toolslive has joined #ocaml
<Leonidas> Though I can never remember the for syntax
<lokien> is string a list of chars?
<aantron> String.iter
<aantron> no it is not
<Leonidas> lokien: no.
<Drup> Leonidas: Lwt_stream
<lokien> why :(
<aantron> lokien: for more efficient representation i guess
ollehar has joined #ocaml
<aantron> also it used to be mutable
<lokien> aantron: ocaml, better than c!
<Drup> String as list of chars is an idea that sounds good but is absolutely terrible in practice
<Drup> (Haskelians are still paying the price of that one)
<lokien> Drup: why is that?
<Drup> It's slow as hell
<Leonidas> Drup: yes, I am getting a Lwt_stream.t out and .iter over it wanting to enqueue, but maybe the idea of enqueing doesn't make sense in the first place.
<aantron> lokien: think how a list is represented and how much you use strings and how
<lokien> Drup: good reason
lordf has joined #ocaml
<Drup> Leonidas: well, if you imediatly launch a task in the background, yes, no need to queue
<Drup> Just launch the task
<Leonidas> Drup: ok, thanks.
<Drup> However, if you want to preserve strict ordering, it's not a bad idea
<Leonidas> no, the ordering does not matter much
alexst has joined #ocaml
<Drup> Lwt.async might help you too
<lokien> eh, I wish I was smart enough to actually use ocaml somewhere
<lokien> thanks guys
<Leonidas> For some reason, everytime I use Lwt, I end up surprisingly satisfied.
<Leonidas> Drup: will look into it, thanks!
<Drup> lokien: you barely started a few weeks ago, you are doing fine. ^^'
<lokien> Drup: I looked at the caml4p tutorial
<lokien> <:expr< $uid:m$.iter $f$ $e$ >>
<Drup> Don't look at camlp4
<lokien> gawd, how are you parsing stuff like this in your head
<lokien> Drup: give me stuff to look at
<Drup> You read RWO already ?
<lokien> no, I was trying to do stuff and dropping to RWO when I needed something
<lokien> examples in RWO are too complicated for me when I'm reading from cover to cover
<Drup> what are you interested in ?
jwatzman|work has quit [Quit: jwatzman|work]
shinnya has quit [Ping timeout: 240 seconds]
<lokien> I was in 2D games, now in whatever, to be honest
<lokien> (too much stuff to figure out in an unpopular language for a beginner)
<lokien> (.. to do 2d games)
<Drup> The cairo API in OCaml is fine, if you like to draw things.
<lokien> too complicated, still. I'd like to do some cli scripts or sth
<lokien> just for fun/to learn
<Drup> You can do that too, the Arg module is easy to use
<hcarty> At this point, what is the best/proper way to use unsigned integers in OCaml? The uint library? ctype's uint support? Pretend that Int32.t and Int64.t aren't signed when I want an unsigned integer?
<lokien> but.. what to do? :D
<hcarty> This is specifically for reading values from disk in some arbitrary raw format.
<ggole> hcarty: do you need unsigned operators or just a bag of a certain number of bits?
<aantron> lokien: as an alternative to Arg, the Cmdliner library is pretty sick to play with
<Drup> aantron: not for a beginner ^^
<Drup> lokien pick a utility you like/use and redo it in ocaml ?
<toolslive> @hcarty what are you doing with the unsigned ints ?
<aantron> i guess i can see how it might be difficult to get at first, but there are examples, and the results are quite nice
<lokien> Drup: but it looks sick
<lokien> Drup: maybe I'll implement some of the unix commands in it?
<lokien> faster than bash!
<hcarty> ggole, toolslive: A bag of bits which need to compare correctly and, in some cases, uses as an offset in a separate file
JacobEdelman_ has joined #ocaml
<Leonidas> Cmdliner is good but it's quite magical. If it weren't for the fact that it compiles, I wouldn't believe my code is doing the right thing
<hcarty> s/uses/be used/
<toolslive> so the sign doesn't matter ?!
<hcarty> The sign does in the lookup case
<lokien> Leonidas: magic in ocaml? ew
tftio has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<hcarty> lokien: It's not actual magic, just feels like it
<Drup> But which color of magic is it ? :]
<toolslive> suppose you use an int, how can it become negative?
<hcarty> Blue, like infinity
<ggole> hcarty: I suppose use ocaml-uint then
<hcarty> toolslive: read 4 bytes as an Int32.t, you could end up with a negative value
<toolslive> then read the 4 bytes into an int.
<lokien> hcarty: oh, I'm fine with that then
<Drup> :purple magic:
<aantron> lol
<hcarty> ggole: I suspect you're correct
<lokien> Drup: I was going to say "if it's purple, I'm fine with that"
<Leonidas> Drup: octarine, silly question :p
<lokien> my man intuition is outstanding
sooheon has joined #ocaml
<hcarty> ggole: And FWIW it looks like ocaml-stdint is the modern/supported incarnation of ocaml-uint
<ggole> Oh, hmm
* ggole writes himself a mental note
Haudegen has quit [Ping timeout: 248 seconds]
lordf has quit [Quit: leaving]
<aantron> i cant wait to be finished dealing with HTML and SVG. most tedious work ive ever done
deko-pyon has joined #ocaml
<lokien> aantron: have you tried js?
<aantron> what do you mean "tried"?
dexterph has joined #ocaml
sooheon has quit [Remote host closed the connection]
<lokien> I meant that for me, js was the most tedious
<lokien> and svg :D
<aantron> you mean writing js, html, svg.. those are annoying, but i am doing something WAY more annoying right now :)
<Drup> aantron: but the next tyxml release will be :great:
<lokien> which is .. ?
<aantron> Drup: it will be, and i want to work on tyxml's "optics" a bit to make it even more :great: :)
slicefd has quit [Quit: WeeChat 1.4]
<Drup> optics ?
<aantron> presentation. docs and the like
<Drup> ah, yes
<Drup> You are totally right
<Drup> and I have no time whatsoever to assist you until 16 march
<aantron> lokien: i translated this horrific parser https://www.w3.org/TR/html5/syntax.html into OCaml at the end of last year
<aantron> now i am using to write something for tyxml
<aantron> = lots of checking back and forth between the html and svg specs and various ocaml files
<lokien> aantron: is it less horrific now?
<aantron> for all the messy, ugly, inconsistent attribute names, types, exceptional situations, etc
<aantron> the ocaml version? its logically as awful as the natural language version, but slightly better than natural language because at least it is possible to compile and test it :)
<aantron> ..and its hidden behind some interface
<Drup> aantron: fontFace
<Drup> This one makes me cross eyes everytime
<aantron> lol
<Drup> ಠ_ಠ
<aantron> Drup: what happens on 16 march? if not secret :)
<aantron> or 15 march :)
<Drup> aantron: icfp deadline
<aantron> ah
<Drup> wow, I think they changed fontFace to font-face
<lokien> fontFace looks like a twitch emote
<malc_>
ggole has quit []
<Drup> aantron: can you repush/rebase your PR ?
<aantron> Drup: what are you subitting, if not secret?
<aantron> okay. thought i just did
<Drup> you did, but jenkins is really unhappy about it
<aantron> i noticed, not sure why. hmm.
Haudegen has joined #ocaml
<aantron> how does one re-push? i could fudge it by twiddling the commit timestamp, but is there some legitimate way you know of?
<aantron> can you just ask jenkins to rebuild?
<Drup> I cannot é_è
<Drup> just rebase on master
<Drup> it should work
<aantron> its already based on master and git push -f after rebase does nothing
<Algebr> does opam have some kind of perl dependency?
<aantron> (after checking the remote of course)
<aantron> anyway i will do an amend
<Drup> aantron: Actually, I'm going to merge the other 2 PR now
<aantron> so.. is the ppx going to be for 4.0?
<Drup> yes
<Drup> Which is going to be next version
<aantron> ok, cool
nojb has quit [Ping timeout: 240 seconds]
<aantron> Algebr: on my os x system it seems to have a python dependency, but not perl
<Algebr> I have this on linux: PERL5LIB=/home/gar/.opam/working/lib/perl5
<aantron> (using macports)
tftio has joined #ocaml
bobthenameless has quit [Ping timeout: 250 seconds]
<aantron> interesting, i have something similar
<aantron> but i have no such directory
<aantron> perhaps it is for packages that have perl scripts included? speculating
<aantron> (i mean no directory as mentioned in my PERL5LIB)
yunxing has joined #ocaml
alpen has quit [Ping timeout: 240 seconds]
larhat has joined #ocaml
bobthenameless has joined #ocaml
tftio has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Drup> aantron: I'm merging https://github.com/ocsigen/tyxml/pull/51 too
<aantron> yep, saw it. thanks
<Drup> That's the other one ^^
<aantron> btw
<aantron> before you do so
<aantron> yes i know its the other one :)
<aantron> i would prefer you not replace `On | `Off by bool
<Drup> Ah ?
<aantron> right now the ppx uses this variant to know that "on" and "off" are the possible values
<aantron> i could still handle it if you made it into a bool, but with a special-case annotation
sh0t has quit [Ping timeout: 250 seconds]
<Drup> huum
cyraxjoe has quit [Quit: I'm out!]
<aantron> right now "bool wrap" means to the ppx "expect strings true or false, and apply string_of_bool"
<Drup> It's really more convenient for users
cyraxjoe has joined #ocaml
<aantron> fair enough
<Drup> I'm fine with annotating tyxml's type with this kind of things
<Drup> like bool wrap [@onoff]
<aantron> everything else will be picked up automatically i think. i might have to make a 1 line change
<aantron> yeah, i already have annotations like that, so it will be fine
<Drup> ok
<Drup> I'm going through the various we added since I did the patch, to replace similar things
<aantron> the main reason for `On `Off in my opinion though, even to the user
<aantron> is that this attribute does require stirngs "on" "off" not "true" "false"
<Drup> I'm happy to see that I'm not the only one that word
<Drup> :D
<aantron> it just helps to train the user somehow :)
<aantron> what do you mean?
<aantron> if the same user is writing html using tyxml, they will have to remember not to write "true" or "false" (though the ppx will yell at them if they do). for consistency, it may make sense to keep it as `On | `Off in the types
<Drup> I keep forgetting words in my sentences
Haudegen has quit [Ping timeout: 276 seconds]
<aantron> using the ppx* i mean
<Drup> Yeah
<Drup> but if you have a bool signals coming from something else, you can plug it directly
<aantron> freaking html people
<Drup> I would agree with you if tyxml was only a static description language, but it's not the case, you can use signals and interactive things
<aantron> great design from the working groups..
<aantron> :)
<Drup> Eh, that's usual
alexst has quit [Ping timeout: 252 seconds]
<aantron> Drup: i wasnt able to parse: "I'm happy to see that I'm not the only one that word"
<Drup> Yes, that's the point, it's a joke x)
<lokien> Drup: what's the recommended way of getting ocaml? I'm on ubuntu. github, to be up-to-date?
<Drup> Certainly not github
<aantron> lokien: ppa/avsm
<lokien> (recent format and I'm reinstalling everything)
<Algebr> avsm does a great service to everyone with that ppa
<lokien> okay, I'll use it :)
<Drup> Yeah, it contains opam too
nojb has joined #ocaml
alexst has joined #ocaml
ollehar has quit [Quit: ollehar]
Haudegen has joined #ocaml
ygrek has joined #ocaml
Denommus has quit [Ping timeout: 244 seconds]
lokien_ has quit [Quit: Connection closed for inactivity]
tftio has joined #ocaml
alexst_ has joined #ocaml
alexst has quit [Ping timeout: 276 seconds]
larhat has quit [Quit: Leaving.]
hanshenrik__ has quit [Ping timeout: 240 seconds]
teknozulu has joined #ocaml
toolslive has quit [Ping timeout: 240 seconds]
Anarchos has joined #ocaml
hcarty has quit [Quit: WeeChat 1.4]
Jane-PC has quit [Read error: Connection reset by peer]
Jane-PC has joined #ocaml
antkong has joined #ocaml
alexst_ has quit [Ping timeout: 244 seconds]
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
toolslive has joined #ocaml
tftio has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
slash^ has quit [Read error: Connection reset by peer]
orbifx has joined #ocaml
antkong has quit [Quit: antkong]
teknozulu has quit [Ping timeout: 244 seconds]
smandy2 has quit [Remote host closed the connection]
alpen has joined #ocaml
yunxing has quit [Remote host closed the connection]
sh0t has joined #ocaml
tftio has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
al-maisan has joined #ocaml
_andre has quit [Quit: leaving]
tftio has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
tftio has joined #ocaml
yunxing has joined #ocaml
sillyotter has joined #ocaml
sillyotter has quit [Client Quit]
malc_ has quit [Quit: ERC (IRC client for Emacs 25.0.50.2)]
<lokien> utop "counter" breaks on solarized light terminal theme :^(
<lokien> and I consider it as a serious issue
<orbifx> :P
<lokien> seriously, invisible counter drives me nuts
<lokien> but I don't know if to fill an issue in the solarized project, or utop
<orbifx> hmm tricky
<orbifx> i doubt utop will change something unless they have done it seriously wrong.
<orbifx> maybe start with solarized.
<lokien> solarized dark is fine, but utop uses the same colour for background and counter text with solarized light.
<aantron> i doubt utop is aware of how the colors would appear in a theme, sounds like a problem with the theme
teknozulu has joined #ocaml
<lokien> oh, it's kinda fine with ubuntu's solarized.
Haudegen has quit [Ping timeout: 276 seconds]
<orbifx> lokien: if you are using tabs you can use a profile suitable for utop
<lokien> orbifx: too much hassle, honestly. now I have the perfect set-up though :D
Mercuria1Alchemi has quit [Ping timeout: 240 seconds]
nojb has quit [Read error: Connection reset by peer]
<orbifx> fixed it?
tftio has quit [Max SendQ exceeded]
<lokien> yeah, I used ubuntu solarized colorscheme for terminal, and regular solarized for vim
<lokien> when I want to loop over a sequence (string) and accumulate some result.. what is the best way to do so?
<lokien> List.iter doesn't look like a good option
<lokien> hm, maybe I'll do this imperatively
<copy`> containers and core both have String.fold
<lokien> copy`: I'll try that, thanks :)
BitPuffin has quit [Ping timeout: 276 seconds]
mac10688 has joined #ocaml
Jane-PC has quit [Quit: Leaving]
Haudegen has joined #ocaml
teiresias has joined #ocaml
<lokien> can I use a tuple as init?
<companion_cube> you can use any type, it's polymorphic
fds has quit [Changing host]
fds has joined #ocaml
antkong has joined #ocaml
<lokien> companion_cube: sweet, sweet ocaml
tobiasBora has joined #ocaml
th5 has quit [Quit: Textual IRC Client: www.textualapp.com]
julien_t has joined #ocaml
Sim_n has quit [Quit: Leaving]
Thooms has joined #ocaml
julien_t has quit [Ping timeout: 240 seconds]
<lokien> guys, what's wrong with that?
<companion_cube> you need to match on characters, not substrings
<companion_cube> '(' and ')'
<aantron> whats the error? using strings instead of chars?
<companion_cube> look at the type of String.fold
<aantron> ^
<lokien> ah, damn.
<lokien> thanks!
<lokien> "This is not a function, it cannot be applied" was tricky
<lokien> it still does not work.
<aantron> lokien: give the error right away
<aantron> it saves a round-trip
<lokien> minute
<thizanne> let (_ : int) = String.fold ...
<aantron> put let _ =
<aantron> before the fold
<aantron> thizanne gives a better option
<thizanne> or it believes you wrote `let parens = "()(" (String.fold ... )`
<aantron> in general, avoid expressions at the structure level
Jane-PC has joined #ocaml
<aantron> (wrap them in let .. = ..)
<lokien> whatwhatwhat
<lokien> oh, it was stupid, yeah
<lokien> it works! you're wonderful :D
yunxing has quit [Remote host closed the connection]
alexst has joined #ocaml
seangrove has joined #ocaml
<lokien> do I keep functions like these in one line? no newlines for |s ?
<aantron> normally you split cases on multiple lines
yunxing has joined #ocaml
<aantron> you can also contract "fun x y -> match y with ..." to "fun x -> function ..."
yunxing has quit [Remote host closed the connection]
yunxing has joined #ocaml
alexst has quit [Ping timeout: 240 seconds]
<lokien> yeah, right. thanks
darkf has joined #ocaml
sh0t has quit [Ping timeout: 240 seconds]
tane has quit [Quit: Verlassend]
troydm has quit [*.net *.split]
nicoo has quit [*.net *.split]
emias has quit [*.net *.split]
freehck has quit [*.net *.split]
eikke has quit [*.net *.split]
relrod has quit [*.net *.split]
lukky513 has quit [*.net *.split]
so has quit [*.net *.split]
foolishmonkey has quit [*.net *.split]
dinosaure has quit [*.net *.split]
john51 has quit [*.net *.split]
low-profile has quit [*.net *.split]
vbmithr has quit [*.net *.split]
artart78 has quit [*.net *.split]
darius93 has quit [*.net *.split]
luzie has quit [*.net *.split]
Jane-PC has quit [*.net *.split]
antkong has quit [*.net *.split]
infinity0 has quit [*.net *.split]
nuuit has quit [*.net *.split]
regnat_ has quit [*.net *.split]
DanielRichman has quit [*.net *.split]
NingaLeaf has quit [*.net *.split]
demonimin has quit [*.net *.split]
Madars has quit [*.net *.split]
dmiller has quit [*.net *.split]
nzyuzin has quit [*.net *.split]
regnat has quit [*.net *.split]
mrvn has quit [*.net *.split]
ousado has quit [*.net *.split]
djellemah has quit [*.net *.split]
darkf has quit [*.net *.split]
seangrove has quit [*.net *.split]
Thooms has quit [*.net *.split]
toolslive has quit [*.net *.split]
alpen has quit [*.net *.split]
bobthenameless has quit [*.net *.split]
lokien has quit [*.net *.split]
jlouis has quit [*.net *.split]
sgnb has quit [*.net *.split]
StatelessCat has quit [*.net *.split]
thizanne has quit [*.net *.split]
acieroid has quit [*.net *.split]
flux has quit [*.net *.split]
Cypi has quit [*.net *.split]
vishesh has quit [*.net *.split]
rpip has quit [*.net *.split]
cschneid has quit [*.net *.split]
bitbckt has quit [*.net *.split]
NhanH has quit [*.net *.split]
oldmanistan_ has quit [*.net *.split]
Asmadeus has quit [*.net *.split]
sigjuice has quit [*.net *.split]
jyc has quit [*.net *.split]
Maelan has quit [*.net *.split]
adrien_znc has quit [*.net *.split]
wagle has quit [*.net *.split]
fds has quit [*.net *.split]
zozozo has quit [*.net *.split]
_habnabit has quit [*.net *.split]
cyraxjoe has quit [*.net *.split]
dexterph has quit [*.net *.split]
deko-pyon has quit [*.net *.split]
sz0 has quit [*.net *.split]
copy` has quit [*.net *.split]
ia0 has quit [*.net *.split]
sspi has quit [*.net *.split]
jeroud has quit [*.net *.split]
Muzer has quit [*.net *.split]
mal`` has quit [*.net *.split]
maker has quit [*.net *.split]
tizoc has quit [*.net *.split]
jmasseo has quit [*.net *.split]
Sorella has quit [*.net *.split]
al-maisan has quit [*.net *.split]
oskarth has quit [*.net *.split]
pootler_ has quit [*.net *.split]
l1x has quit [*.net *.split]
boegel has quit [*.net *.split]
igitoor has quit [*.net *.split]
msch has quit [*.net *.split]
Mandus has quit [*.net *.split]
axiles has quit [*.net *.split]
edwin has quit [*.net *.split]
riveter has quit [*.net *.split]
jun has quit [*.net *.split]
haelix has quit [*.net *.split]
rossberg has quit [*.net *.split]
tg has quit [*.net *.split]
mankyKitty has quit [*.net *.split]
Haudegen has quit [*.net *.split]
mac10688 has quit [*.net *.split]
jeffmo has quit [*.net *.split]
aantron has quit [*.net *.split]
badon has quit [*.net *.split]
damason has quit [*.net *.split]
cthuluh has quit [*.net *.split]
ahf has quit [*.net *.split]
gbarboza has quit [*.net *.split]
MasseR has quit [*.net *.split]
srcerer has quit [*.net *.split]
struk|desk|away has quit [*.net *.split]
iosys has quit [*.net *.split]
cdidd has quit [*.net *.split]
cross has quit [*.net *.split]
xaimus has quit [*.net *.split]
bacam has quit [*.net *.split]
martintrojer has quit [*.net *.split]
mfp has quit [*.net *.split]
polaron has quit [*.net *.split]
mahem1 has quit [*.net *.split]
tokik has quit [*.net *.split]
tokenrove has quit [*.net *.split]
tobiasBora has quit [*.net *.split]
teknozulu has quit [*.net *.split]
orbifx has quit [*.net *.split]
ygrek has quit [*.net *.split]
eeks_ has quit [*.net *.split]
johnelse has quit [*.net *.split]
sheijk has quit [*.net *.split]
hannes has quit [*.net *.split]
thegameg has quit [*.net *.split]
_2can has quit [*.net *.split]
kolko has quit [*.net *.split]
MercurialAlchemi has quit [*.net *.split]
Intensity has quit [*.net *.split]
jbrown has quit [*.net *.split]
Snark has quit [*.net *.split]
clog has quit [*.net *.split]
ohama has quit [*.net *.split]
SHODAN has quit [*.net *.split]
dmbaturin has quit [*.net *.split]
profan has quit [*.net *.split]
smondet has quit [*.net *.split]
orbitz has quit [*.net *.split]
pierpa has quit [*.net *.split]
systmkor has quit [*.net *.split]
Kakadu has quit [*.net *.split]
apache2 has quit [*.net *.split]
cow-orker has quit [*.net *.split]
snhmib has quit [*.net *.split]
wolfcore has quit [*.net *.split]
mj12` has quit [*.net *.split]
danieli has quit [*.net *.split]
nopf has quit [*.net *.split]
tvaalen has quit [*.net *.split]
cat5e has quit [*.net *.split]
caw has quit [*.net *.split]
maufred has quit [*.net *.split]
Harzilein has quit [*.net *.split]
averell has quit [*.net *.split]
seako has quit [*.net *.split]
S11001001 has quit [*.net *.split]
Riviera has quit [*.net *.split]
stephe has quit [*.net *.split]
MorTal1ty has quit [*.net *.split]
yminsky has quit [*.net *.split]
strmpnk has quit [*.net *.split]
emmanueloga has quit [*.net *.split]
lopex has quit [*.net *.split]
iZsh has quit [*.net *.split]
chenglou has quit [*.net *.split]
ggherdov has quit [*.net *.split]
luigy has quit [*.net *.split]
segmond has quit [*.net *.split]
cnu- has quit [*.net *.split]
lpaste has quit [*.net *.split]
adrien has quit [*.net *.split]
def` has quit [*.net *.split]
srax has quit [*.net *.split]
zapu has quit [*.net *.split]
vodkaInferno has quit [*.net *.split]
osheeta has quit [*.net *.split]
tianon has quit [*.net *.split]
theblatte has quit [*.net *.split]
Algebr has quit [*.net *.split]
mietek has quit [*.net *.split]
vpm has quit [*.net *.split]
mattg has quit [*.net *.split]
Ankhers has quit [*.net *.split]
jpdeplaix has quit [*.net *.split]
companion_cube has quit [*.net *.split]
rks` has quit [*.net *.split]
patronus has quit [*.net *.split]
phrst has quit [*.net *.split]
c-c has quit [*.net *.split]
yunxing has quit [*.net *.split]
zoobab has quit [*.net *.split]
deavid has quit [*.net *.split]
Khady has quit [*.net *.split]
AlexRussia has quit [*.net *.split]
swistak35 has quit [*.net *.split]
pgiarrusso has quit [*.net *.split]
stux|RC-only has quit [*.net *.split]
j_king has quit [*.net *.split]
Reventlov has quit [*.net *.split]
gargawel has quit [*.net *.split]
asmanur has quit [*.net *.split]
eagleflo has quit [*.net *.split]
teiresias has quit [*.net *.split]
jerith has quit [*.net *.split]
fold3 has quit [*.net *.split]
jave has quit [*.net *.split]
julienXX has quit [*.net *.split]
Ravana has quit [*.net *.split]
mehdi_ has quit [*.net *.split]
seliopou_ has quit [*.net *.split]
reynir has quit [*.net *.split]
hnrgrgr has quit [*.net *.split]
SimonJF has quit [*.net *.split]
pdewacht has quit [*.net *.split]
nullcatxxx_ has quit [*.net *.split]
Maxdamantus has quit [*.net *.split]
zxqdms has quit [*.net *.split]
stomp has quit [*.net *.split]
gustav___ has quit [*.net *.split]
inr has quit [*.net *.split]
__rlp has quit [*.net *.split]
ski has quit [*.net *.split]
noplamodo has quit [*.net *.split]
tumdum has quit [*.net *.split]
Drup has quit [*.net *.split]
fluter has quit [Max SendQ exceeded]
cartwright has quit [Max SendQ exceeded]
regnat has joined #ocaml
oldmanistan_ has joined #ocaml
sgnb has joined #ocaml
cschneid has joined #ocaml
adrien_znc has joined #ocaml
djellemah has joined #ocaml
flux has joined #ocaml
segmond has joined #ocaml
adrien has joined #ocaml
cnu- has joined #ocaml
al-maisan has joined #ocaml
cyraxjoe has joined #ocaml
dexterph has joined #ocaml
deko-pyon has joined #ocaml
sz0 has joined #ocaml
copy` has joined #ocaml
ia0 has joined #ocaml
Muzer has joined #ocaml
sspi has joined #ocaml
jeroud has joined #ocaml
maker has joined #ocaml
mal`` has joined #ocaml
jmasseo has joined #ocaml
pootler_ has joined #ocaml
tizoc has joined #ocaml
oskarth has joined #ocaml
l1x has joined #ocaml
riveter has joined #ocaml
axiles has joined #ocaml
Sorella has joined #ocaml
rossberg has joined #ocaml
haelix has joined #ocaml
edwin has joined #ocaml
mankyKitty has joined #ocaml
boegel has joined #ocaml
jun has joined #ocaml
igitoor has joined #ocaml
msch has joined #ocaml
Mandus has joined #ocaml
tg has joined #ocaml
mj12` has joined #ocaml
lukky513 has joined #ocaml
relrod has joined #ocaml
so has joined #ocaml
fluter has joined #ocaml
tobiasBora has joined #ocaml
Haudegen has joined #ocaml
mac10688 has joined #ocaml
teknozulu has joined #ocaml
ygrek has joined #ocaml
aantron has joined #ocaml
eeks_ has joined #ocaml
MercurialAlchemi has joined #ocaml
hannes has joined #ocaml
orbifx has joined #ocaml
cross has joined #ocaml
damason has joined #ocaml
Intensity has joined #ocaml
srcerer has joined #ocaml
ahf has joined #ocaml
iosys has joined #ocaml
sheijk has joined #ocaml
thegameg has joined #ocaml
jeffmo has joined #ocaml
MasseR has joined #ocaml
struk|desk|away has joined #ocaml
gbarboza has joined #ocaml
Snark has joined #ocaml
mfp has joined #ocaml
ohama has joined #ocaml
clog has joined #ocaml
mahem1 has joined #ocaml
tokik has joined #ocaml
johnelse has joined #ocaml
bacam has joined #ocaml
_2can has joined #ocaml
polaron has joined #ocaml
profan has joined #ocaml
cdidd has joined #ocaml
SHODAN has joined #ocaml
jbrown has joined #ocaml
tokenrove has joined #ocaml
cthuluh has joined #ocaml
martintrojer has joined #ocaml
dmbaturin has joined #ocaml
smondet has joined #ocaml
kolko has joined #ocaml
orbitz has joined #ocaml
xaimus has joined #ocaml
cartwright has joined #ocaml
julienXX has joined #ocaml
so has quit [Max SendQ exceeded]
troydm has joined #ocaml
nicoo has joined #ocaml
emias has joined #ocaml
foolishmonkey has joined #ocaml
dinosaure has joined #ocaml
john51 has joined #ocaml
low-profile has joined #ocaml
vbmithr has joined #ocaml
darius93 has joined #ocaml
luzie has joined #ocaml
artart78 has joined #ocaml
john51 has quit [Max SendQ exceeded]
srcerer has quit [Ping timeout: 244 seconds]
Drup has joined #ocaml
pgiarrusso has joined #ocaml
eagleflo has joined #ocaml
jerith has joined #ocaml
swistak35 has joined #ocaml
gustav___ has joined #ocaml
teiresias has joined #ocaml
zoobab has joined #ocaml
tumdum has joined #ocaml
zxqdms has joined #ocaml
fold3 has joined #ocaml
mehdi_ has joined #ocaml
stomp has joined #ocaml
Khady has joined #ocaml
j_king has joined #ocaml
yunxing has joined #ocaml
Reventlov has joined #ocaml
Maxdamantus has joined #ocaml
jave has joined #ocaml
hnrgrgr has joined #ocaml
reynir has joined #ocaml
stux|RC-only has joined #ocaml
noplamodo has joined #ocaml
asmanur has joined #ocaml
deavid has joined #ocaml
inr has joined #ocaml
Ravana has joined #ocaml
AlexRussia has joined #ocaml
pdewacht has joined #ocaml
SimonJF has joined #ocaml
nullcatxxx_ has joined #ocaml
__rlp has joined #ocaml
gargawel has joined #ocaml
ski has joined #ocaml
seliopou_ has joined #ocaml
companion_cube has joined #ocaml
vpm has joined #ocaml
mattg has joined #ocaml
mietek has joined #ocaml
rks` has joined #ocaml
patronus has joined #ocaml
phrst has joined #ocaml
c-c has joined #ocaml
Algebr has joined #ocaml
jpdeplaix has joined #ocaml
john51 has joined #ocaml
theblatte has joined #ocaml
SoniEx2 has joined #ocaml
nopf has joined #ocaml
john51 has quit [Max SendQ exceeded]
copy` has quit [Ping timeout: 240 seconds]
jeroud has quit [Ping timeout: 240 seconds]
fold3 has quit [Max SendQ exceeded]
_snhmib has joined #ocaml
SoniEx2 has quit [Changing host]
SoniEx2 has joined #ocaml
fold3 has joined #ocaml
julienXX has joined #ocaml
julienXX has quit [Changing host]
cat5e has joined #ocaml
snhmib has joined #ocaml
maufred has joined #ocaml
tvaalen has joined #ocaml
systmkor has joined #ocaml
Kakadu has joined #ocaml
caw has joined #ocaml
cow-orker has joined #ocaml
pierpa has joined #ocaml
caw has quit [Ping timeout: 255 seconds]
cat5e has quit [Max SendQ exceeded]
systmkor has quit [Max SendQ exceeded]
snhmib has quit [Ping timeout: 255 seconds]
pierpa has quit [Remote host closed the connection]
pierpa has joined #ocaml
fluter is now known as Guest72509
Ankhers has joined #ocaml
john51 has joined #ocaml
Guest72509 has quit [Changing host]
Guest72509 has joined #ocaml
pierpa has quit [Remote host closed the connection]
pierpa has joined #ocaml
freehck has joined #ocaml
eikke has joined #ocaml
badon has joined #ocaml
wolfcore has joined #ocaml
Guest72509 has quit [Quit: WeeChat 1.2]
fluter_ has joined #ocaml
freehck has quit [*.net *.split]
eikke has quit [*.net *.split]
fluter_ is now known as fluter
freehck has joined #ocaml
eikke has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 240 seconds]
SoniEx2 is now known as cat5e
<Drup> seangrove: it's to keep my collaborators on their toes, they never know when I will answer :D
systmkor has joined #ocaml
<lokien> Drup: how would ocaml suit a hackathon/programming contest?
<Drup> I don't know, I don't like hackathons.
<lokien> why?
<Drup> Coding in a hurry to produce crappy code in order to win a contest doesn't fit my definition of "good programming"
<lokien> you can cross the hackathons out and leave just contests :D
<lokien> well. but it's fun sometimes
<fds> I'm struggling to think what would make a programming language good or bad for those things.
<Algebr> lokien: I love hackathons, I made a library to help with hackathons called podge
<Algebr> for when using ocaml
<Drup> lokien: people still do it, so I guess so, but don't ask me, I'm not interested ^^'
<lokien> Algebr: *googles podge* - a short, fat person.
<Algebr> github.com/fxfactorial/podge
<lokien> Drup: okay! I still like you :D
<lokien> Algebr: I'll study it tomorrow, thank you very much
srcerer has joined #ocaml
<companion_cube> http://pqwy.github.io/notty/Notty.html why do people show me this when I want to go to sleep? :/
<lokien> I was asking about hackathons, because I output ocaml code much slower than python/nim code
caw has joined #ocaml
<lokien> companion_cube: what is this?
<lokien> companion_cube: tui library?
ggherdov has joined #ocaml
<companion_cube> yep
<companion_cube> it's pretty nice
<Algebr> lokien: agreed, python is the usual go to for hackathons but it would be nice to use OCaml for hackathons as well
<lokien> companion_cube: another tui lover? sweet
<companion_cube> well I don't have a use case for this (yet?)
<lokien> Algebr: the dream
<lokien> companion_cube: dwarf fortress v2?
<companion_cube> :D
<companion_cube> it would be so much work
<lokien> you have my axe!
<lokien> ('cause my code's not good enough)
<Drup> The UI of dwarf fortress is the trivial part :)
copy` has joined #ocaml
<lokien> yeah. the impressive part is the guy has done it only by himself
hanshenrik has joined #ocaml
<Drup> No, the impressive part is the dwarf AI and the procedural content generation
sh0t has joined #ocaml
MercurialAlchemi has joined #ocaml
<companion_cube> and the set of rules that make the game run?
jeroud has joined #ocaml
<Drup> that set of system is complex, but it's a set of rules, plenty of games have (complex) rules. The procedural content gen, on the other hand ... I don't know any other games that does it like that
john51_ has joined #ocaml
foolishmonkey has quit [Quit: Leaving]
<Drup> It's not only the map, it generates history over a period span of several centuries, to the details of what you dwarfs received as gift for his birthday. Including religions and dance traditions, it's just ridiculous
<seangrove> yminsky: Is janestreet using Jenga internally, or is it still alpha internally?
foolishmonkey has joined #ocaml
john51 has quit [Ping timeout: 252 seconds]
<lokien> Drup: too bad it has the weirdest keybindings in the world
<Drup> I'm sure he is a vi user :D
<lokien> me too :D
orbifx has quit [Ping timeout: 240 seconds]
<lokien> going to sleep though, thank you guys again. goodnight :)
<aantron> night :)
Kakadu has quit [Remote host closed the connection]
<seangrove> Drup: Does https://github.com/mirage/mirage/issues/493#issuecomment-187398678 mean that I can solve the problem on my own right now by creating a device (no idea how to do that yet)? And I don't have to muck about inside of Mirage itself?
<Drup> The bootvar bug needs to be fixed first
<seangrove> I see, I can probably hack that out of the way for right now (don't think I need it when deploying to EC2)
<Drup> But in the meantime, you can use my rough patch
<Drup> It'll prevent you passing new parameters at runtime, but it'll prevent any issue
<seangrove> So I should be able to pin this https://github.com/mirage/mirage/pull/497, rebuild, and have it work?
<Drup> You need to give the option --no-argv at configure time
so has joined #ocaml