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
<Drup> right
<icicled> this is overly complicated for a simple include >_>
<icicled> s/include/conditional
<struktured> icicled: do what drup does in his myocamlbuild.ml, or do it with oasis + true/false build flag which is *set in opam build section using appropriate env variable*
<Drup> struktured: well, I do it with oasis + true/false build flag :D
<struktured> I feal like for different features, I want to do it in one repo with different build flags, but different implementations I want on different repos, usually
<struktured> err, different implementations with different 3rd party deps, especially
<icicled> I'm gonna ask on the ocamlforge bug/feature page for oasis on how to handle the BuildDepends conditional
<icicled> I really think that it should be a feature oasis should handle
<Drup> Pretty sure there is a feature request for that
<Drup> honestly, don't expect an answer, and even less an implementation
<icicled> why's that?
Maelan has joined #ocaml
<Drup> oasis is not actively developed
<icicled> the oasis-devel mailing list has some activity on it
<icicled> I'll give it a shot
<icicled> might as well try
aantron has joined #ocaml
<aantron> icicled: are you still having difficulty with bisect_ppx?
arquebus has joined #ocaml
<Drup> aantron: can I look at your ppx-crawler for tyxml ?
<aantron> meaning the "meta" ppx/"reflector" that runs on tyxml sigs?
<aantron> or the actual ppx itself that runs on the user's markup?
<Drup> the former
<aantron> ok. but it's only done for attributes at this point, and there is a lot left to refactor and rearrange. making a gist
<aantron> out of curiosity, what are you interested in?
<Drup> I'll wait for when you have it integrated inside tyxml and a bit hammered down then
<Drup> no hurry
<aantron> okay then. it is "integrated", just not complete. lots of rough edges and TODOs everywhere
<Drup> So that it triggers a warning if we add things that are not compliants
<aantron> and yeah i am minding the naming, because inconsistency hurts the "crawler" and forces special casing. each time i found an inconsistency (mainly manually at this stage), i put it into a todo file i am keeping. will tell you all of them
<aantron> in addition in a future step it will be finding these automatically
<Drup> Good
<aantron> as a side effect of how it works, i think, but if it doesnt happen as a side effect, i can add it deliberately
<Drup> push a branch somewhere, I might work on it when I have time
<aantron> let me work on it for a while so its in some decent shape. i was going to push a preliminary version that works, but needs improvement, during the next week
<Drup> great
<aantron> i think at this point its so early that i often want to make "pervasive" changes, it would be annoying to collaborate in that situation
<aantron> i can push a branch in some hours if you want to see it for review though. have to go at the moment
<aantron> but i think it will be easier to wait for the writeup in the PR :)
<Drup> As you want ^^
<Drup> Currently there are some attributes that are in several version, and one of the versions "squats" the regular name
<aantron> the ppx would benefit however from having testing in tyxml :)
<Drup> For example, there is "a_for" and "a_for_list" (which should be "a_label_for" and "a_output_for")
<Drup> I'm not sure if I should just remove those or not
<aantron> i saw some like this, like a_x and a_x_list
<Drup> Yeah, same thing
dhil has joined #ocaml
NingaLea_ has joined #ocaml
dhil has quit [Ping timeout: 252 seconds]
shinnya has quit [Ping timeout: 240 seconds]
shinnya has joined #ocaml
shinnya has quit [Ping timeout: 276 seconds]
nojb has quit [Ping timeout: 240 seconds]
nojb_ has joined #ocaml
badon has quit [Quit: Leaving]
NingaLea_ has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<icicled> aantron: I have bisect_ppx working - just having trouble getting it to be conditionally included in the build via a flag w/oasis
nojb_ has quit [Ping timeout: 252 seconds]
lokien_ has quit [Quit: Connection closed for inactivity]
<icicled> just posted to oasis mailing list - let's see what happens
teknozulu has joined #ocaml
tftio has joined #ocaml
badon has joined #ocaml
tftio has quit [Client Quit]
Haudegen has quit [Ping timeout: 276 seconds]
arquebus has quit [Quit: Textual IRC Client: www.textualapp.com]
thEnigma has joined #ocaml
<thEnigma> Hi
<thEnigma> I m trying to create a function that returns the value of a global constant and then increases it by one, but every time I execute it, the value of the global constant is not incremented.
ygrek has quit [Ping timeout: 252 seconds]
<fds> thEnigma: Put your code somewhere we can see it.
<thEnigma> let get_and_inc_plac = (plac_val := !plac_val + 1) ; !plac_val;;
<thEnigma> where plac_val = ref 1;;
<thEnigma> The only time the value of plac_val is incremented is when the function is defined.
<thEnigma> I am thinking that maybe making it lazy would help.
Haudegen has joined #ocaml
<copy`> `get_and_inc_plac` is not a function. You're missing a () after the name
<fds> That ^.
<fds> Which is quite like making it lazy. ;-)
teknozulu has quit [Ping timeout: 240 seconds]
<thEnigma> OK, I tried that but it still keeps returning 2 after the definition
<thEnigma> Oh, now it is working fine.
<thEnigma> Thanks.
teknozulu has joined #ocaml
struk|desk|away is now known as struk|desk
axiles has quit [Ping timeout: 240 seconds]
thEnigma has quit [Ping timeout: 252 seconds]
struk|desk is now known as struk|desk|away
johnelse has quit [Ping timeout: 240 seconds]
yunxing has joined #ocaml
ygrek has joined #ocaml
yunxing has quit [Quit: Leaving...]
yunxing has joined #ocaml
johnelse has joined #ocaml
dpc_ has joined #ocaml
<dpc_> Hi. I'm coming from C world, and I was reading Ocaml tutorial. My question is why `A -> B -> C -> R` is used for function signatures. I've seen it in other functional languages and while I understand that while it technically works some kind of `(A, B, C) -> R` seems more natural to me. Where this notation come from?
jyc has quit [Ping timeout: 240 seconds]
dexterph has quit [Ping timeout: 240 seconds]
<Enjolras> dpc_: because of https://en.wikipedia.org/wiki/Currying
<dpc_> Enjolras, Thanks. Let me take a look.
<Enjolras> the second link is more ocaml related, wikipedia describes the generic concept
relrod has quit [Ping timeout: 268 seconds]
j_king has quit [Ping timeout: 240 seconds]
j_king has joined #ocaml
<dpc_> TIL. Haskell Curry, heh.
jyc has joined #ocaml
<Enjolras> yeah, this guy's research are foundations of a lot of things, hence a lot of things are named after him :)
relrod_ has joined #ocaml
relrod_ has quit [Changing host]
relrod_ has joined #ocaml
<aantron> icicled: okay, please let me know how it goes :) we might want to add oasis instructions to the bisect_ppx docs
<dpc_> Enjolras, The other link is quite long, so I might have missed something but partial function application is the only practical advantage I've found so far.
<dpc_> Can a function be partially applied on non-first argument?
<Enjolras> the anwser is both yes and no
<Enjolras> no for usual function, yes with named arguments
<dpc_> I see.
<Enjolras> let partial ~test ~inc x = if test x then inc x for instance
<dpc_> So I kind of fail to see why to use A -> B -> C -> R over `A, B, C -> R`.
<aantron> you can also create a new closure to achieve the effect without labels, like (fun x -> f x 1)
<dpc_> I get now that i has nice math. properties in lambda calculus etc.
<Enjolras> you can do let inc_if ~test x = partial ~inc:(fun x -> x +1)
<Enjolras> partial applucation using the "second" argument
<Enjolras> dpc_: this is just a notation. It maps well to what is actually going on
<dpc_> Yeah, the new closure was my argument that one can get partial application without Curry Functions.
<Enjolras> because there is no difference between your , and -> conceptually
<Enjolras> so it doesn't make sense to write them differently
<aantron> dpc_: its ultimately just a possibility of the language, that is useful sometimes (like List.fold_left (+) as a toy example). Ocaml functions are commonly declared in curried style, but in SML the basis library uses mainly tupled arguments
<Maxdamantus> a -> (b -> c): a implies that b implies c
<Maxdamantus> (a, b) -> c: a and b implies c
<dpc_> SML == Standard ML?
<Maxdamantus> Both of these are the same statement.
<Enjolras> dpc_: yes
<aantron> yes
relrod_ is now known as relrod
<Maxdamantus> They're also isomorphic types.
<dpc_> I'm actually researching Ocaml, because I'm working with Rust a lot, and it seems Rust copied like everything it can from Ocaml.
<Enjolras> except traits and linear type system :)
<dpc_> Traits are different? There are traits in Rust.
<Enjolras> no traits on ocaml (yet)
<dpc_> Does Ocaml have HKT?
<Maxdamantus> Does Rust? O_o
<Enjolras> depends how you define it
<dpc_> No, it doesn't.
<Enjolras> Maxdamantus: yes and no. No, it doesn't but you can emulate
<Maxdamantus> Okay, haven't missed anything then.
<Maxdamantus> Yeah, that's how I last knew it to be.
<dpc_> But it's like a must-have-feature it will have soon(TM), so I wonder if it's because it wasn't copied from Ocaml yet.
<aantron> they may be inspired by haskell in this case, or something else
<Enjolras> i think traits mostly come from haskell and scala yes
<Enjolras> you can have some sort of HKT in ocaml with module, but that's not really used pervasivly in real world
<Maxdamantus> What maps to traits from Haskell? Just being able to define things in terms of kinded things constrained by classes?
<dpc_> OK, sorry for my ignorance, but what is a relation between SML and Ocaml? :D
<Enjolras> Maxdamantus: traits are basically typeclasses.
<Enjolras> dpc_: they come from the same root, but evolved separatly
<aantron> ^ siblings
<Enjolras> there was a language called ML in the 70's, which was later stanrdized as SML while caml was derived from ML in parallel
<aantron> there was also apparently lazyml which led to haskell
<Enjolras> and miranda
<Maxdamantus> Speaking of laziness .. is there a sensible way of writing this? https://gist.github.com/Maxdamantus/95b514db037719c48604#file-calc-ml-L32
<dpc_> What's the popularity of Ocaml and SML? Are there strong reasons to prefer one over the other?
<aantron> dpc_: regarding your earlier query about partial application, here is one common pattern: type parser : string -> t val float : parser val list_of : parser -> parser let float_list = list_of float (where list_of splits the input string into components and calls its argument parser on each)
<Enjolras> dpc_: ocaml is probably more popular and more widely used than SML, with more libs
<Maxdamantus> (`parser` is of type `unit -> int parser` .. the unit bit is just a hack to make `rec` work)
<Enjolras> besides, this you can google the diff.
<aantron> OCaml is more "popular" than SML, by i think a good margin
<aantron> SML is a bit "ultraconservative" in terms of language evolution. there seems to be a strong emphasis on formalization and research
<aantron> type parser =*
<Maxdamantus> type 't parser = Parser of (state -> 't outcome)
<aantron> (was correcting myself, i think we collided)
<dpc_> aantron, I'm having a very hard time following your example. :)
<aantron> lets say you need to define several parsers, for ints, strings, floats, and lists of each one, and the results of parsing will be of type "t"
<dpc_> Enjolras, this comparison is nice. Thanks.
<dpc_> aantron, OK
<aantron> you can do this by defining 3 parsers "parse_int : int -> t", "parse_string : string -> t", "parse_float : float -> t", and then
<aantron> okay
<aantron> perhaps i need to restart
<aantron> :p
<aantron> each parser parses strings, as ints, floats, strings of a special format, or lists of each one of those
<dpc_> I mean, I understand last one.
shinnya has joined #ocaml
<aantron> so "parse_as_int : string -> t", "parse_as_string : string -> t", "parse_as_float : string -> t"
<aantron> then, to parse the list variants, you define a parser combinator "parse_list : (string -> t) -> string -> t"
<aantron> where parse_list element_parser input = (* ... split input on a delimiter ... *) |> List.map element_parser |> (* ... inject into t ... *)
<aantron> then you can define the remaining 3 parsers as "let parse_as_int_list = parse_list parse_as_int", and so on
<dpc_> Let me chew on it for a moment.
<aantron> ok. its analogous to constructing some object that contains a function pointer in C. you pass in the function to call on each element, and the result is a customized function for parsing lists of that kind of element
<aantron> "object"
<dpc_> Oh, C-speak I understand very easily. :D
<dpc_> I guess my doubt with curring is that it has order. While funciton arguments is irrelevant.
<Maxdamantus> Although in C you can't create new functions at runtime, so you'll end up having some `void *` somewhere.
<dpc_> So `A -> B -> R` could as much be `B -> C -> A -> R`.
<aantron> dpc_: with tupled arguments the order is not irrelevant, there is just no possibility to reorder because you must provide them all
<aantron> and yes the ordering of arguments is a bit weird
<aantron> when writing an ocaml function you learn to think of which argument is most likely to be applied in a partial application, and put that first
<dpc_> Ah, I see. I was wondering about it. "Do people order argument in Ocaml differently?"
<dpc_> So tuples do have order as well, right.
<aantron> well with respect to partial application, a tuple of arguments is 1 argument
<dpc_> OK. Change of subject. I heard that Ocaml is very performant. Why is that?
<aantron> i think you will have to be specific to get a good answer on that :) but basically because it has a good compiler, and some problems that are used in benchmarks have fast solutions with immutable data structures
<dpc_> OK
<dpc_> Thanks for all the answers! I got to go. Hopefully I will have some time to practice some hands-on Ocaml.
badon has quit [Ping timeout: 240 seconds]
badon has joined #ocaml
pierpa has quit [Ping timeout: 252 seconds]
JacobEdelman_ has joined #ocaml
FreeBirdLjj has joined #ocaml
nojb_ has joined #ocaml
nojb_ has quit [Ping timeout: 252 seconds]
teknozulu has quit [Ping timeout: 240 seconds]
dpc_ has quit [Ping timeout: 240 seconds]
zoobab has quit [Ping timeout: 240 seconds]
zoobab has joined #ocaml
shinnya has quit [Ping timeout: 240 seconds]
slash^ has joined #ocaml
axiles has joined #ocaml
nojb_ has joined #ocaml
teknozulu has joined #ocaml
BitPuffin|osx has quit [Ping timeout: 255 seconds]
lokien_ has joined #ocaml
MercurialAlchemi has joined #ocaml
yunxing has quit [Remote host closed the connection]
badon_ has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
tane has joined #ocaml
teknozulu has quit [Ping timeout: 240 seconds]
teknozulu has joined #ocaml
ggole has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
Sorella has quit [Quit: Connection closed for inactivity]
Simn has joined #ocaml
Sim_n has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
Simn has quit [Ping timeout: 240 seconds]
simn__ has joined #ocaml
yunxing has joined #ocaml
Sim_n has quit [Ping timeout: 250 seconds]
Sim_n has joined #ocaml
yunxing has quit [Ping timeout: 250 seconds]
simn__ has quit [Ping timeout: 250 seconds]
simn__ has joined #ocaml
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
Sim_n has quit [Ping timeout: 250 seconds]
tane has quit [Quit: Verlassend]
ygrek has quit [Ping timeout: 255 seconds]
Sim_n has joined #ocaml
simn__ has quit [Ping timeout: 250 seconds]
shinnya has joined #ocaml
tane has joined #ocaml
butts_butts has joined #ocaml
larhat has joined #ocaml
lordf has joined #ocaml
larhat has quit [Quit: Leaving.]
MercurialAlchemi has quit [Ping timeout: 244 seconds]
teknozulu has quit [Ping timeout: 244 seconds]
silver has joined #ocaml
mj12` has quit [Ping timeout: 276 seconds]
mj12` has joined #ocaml
lordf has quit [Ping timeout: 240 seconds]
sfri has quit [Remote host closed the connection]
nojb_ has quit [Read error: Connection reset by peer]
Haudegen has quit [Ping timeout: 240 seconds]
sfri has joined #ocaml
deko-pyon has quit [Quit: The story ends where it began.]
Haudegen has joined #ocaml
lokien_ has quit [Quit: Connection closed for inactivity]
MercurialAlchemi has joined #ocaml
deko-pyon has joined #ocaml
hanshenrik_ has quit [Ping timeout: 240 seconds]
zoobab has quit [Ping timeout: 255 seconds]
struk|desk|away is now known as struk|desk
zoobab has joined #ocaml
Sorella has joined #ocaml
dhil has joined #ocaml
Jane-PC has joined #ocaml
Jane-PC is now known as Sancho-Panza
regnat_ has joined #ocaml
struk|desk is now known as struk|desk|away
struk|desk|away is now known as struk|desk
darkf has quit [Quit: Leaving]
butts_butts has quit [Ping timeout: 244 seconds]
hay207 has joined #ocaml
hay207 has quit [Client Quit]
struktured has quit [Ping timeout: 240 seconds]
slicefd has joined #ocaml
shon has joined #ocaml
lokien_ has joined #ocaml
pgiarrusso_ has joined #ocaml
pgiarrusso has quit [Ping timeout: 252 seconds]
pgiarrusso_ is now known as pgiarrusso
struk|desk is now known as struk|desk|away
stux|RC-only has quit [Quit: Aloha!]
stux|RC-only has joined #ocaml
Guest72522 is now known as c-c
hanshenrik_ has joined #ocaml
butts_butts has joined #ocaml
butts_butts has quit [Ping timeout: 244 seconds]
copy` has joined #ocaml
hnagamin has joined #ocaml
BitPuffin|osx has joined #ocaml
hnagamin has quit [Ping timeout: 244 seconds]
julien_t has joined #ocaml
hnagamin has joined #ocaml
malc_ has joined #ocaml
shon has quit [Read error: Connection reset by peer]
<infinity0> so when i compile with profiling and use gprof, the function names are like camlModule_fun_1234
<infinity0> is there an easy way to figure out which lambda term the 1234 refers to?
<Drup> Not really, and this is one of the many reasons you should name your functions :p
malc_ has quit [Ping timeout: 250 seconds]
malc_ has joined #ocaml
aantron has quit [Remote host closed the connection]
JacobEdelman_ has joined #ocaml
aantron_ has joined #ocaml
pgiarrusso has quit [Quit: pgiarrusso]
pierpa has joined #ocaml
<infinity0> :(
lordf has joined #ocaml
<infinity0> well it could be a bit more systematic like including the name of the outer function
<infinity0> you wouldn't expect everyone to name every sub-expression, sometimes anonymous functions are a good thing
<ggole> Yeah, the name generation is a bit slapdash. It wouldn't be too hard to add line number and position.
Haudegen has quit [Ping timeout: 248 seconds]
pgiarrusso has joined #ocaml
malc_ has quit [Ping timeout: 250 seconds]
malc_ has joined #ocaml
Haudegen has joined #ocaml
m______K_s has joined #ocaml
m______K_s has quit [Client Quit]
butts_butts has joined #ocaml
hnagamin has quit [Ping timeout: 240 seconds]
nuuit has quit [Ping timeout: 252 seconds]
butts_butts_ has joined #ocaml
nuuit has joined #ocaml
sigjuice has quit [Ping timeout: 252 seconds]
butts_butts has quit [Ping timeout: 252 seconds]
pgiarrusso has quit [Ping timeout: 252 seconds]
ggole has quit [Ping timeout: 252 seconds]
axiles has quit [Ping timeout: 252 seconds]
Mandus has quit [Ping timeout: 252 seconds]
ygrek has joined #ocaml
axiles has joined #ocaml
pgiarrusso has joined #ocaml
Mandus has joined #ocaml
dpc_ has joined #ocaml
sigjuice has joined #ocaml
hnagamin has joined #ocaml
hnagamin has quit [Ping timeout: 255 seconds]
teknozulu has joined #ocaml
ggole has joined #ocaml
lokien_ has quit []
hnagamin has joined #ocaml
lokien_ has joined #ocaml
lokien_ has quit [Client Quit]
dpc_ has quit [Ping timeout: 240 seconds]
Sancho-Panza has quit [Read error: Connection reset by peer]
Jane-PC has joined #ocaml
Haudegen has quit [Ping timeout: 255 seconds]
struk|desk|away is now known as struk|desk
Haudegen has joined #ocaml
teknozulu has quit [Ping timeout: 240 seconds]
zoobab has quit [Ping timeout: 248 seconds]
hnagamin has quit [Ping timeout: 240 seconds]
zoobab has joined #ocaml
hnagamin has joined #ocaml
orbifx has joined #ocaml
julien_t has quit [Ping timeout: 248 seconds]
dpc_ has joined #ocaml
Sim_n has quit [Quit: Leaving]
struk|desk is now known as struk|desk|away
dhil has quit [Ping timeout: 240 seconds]
Kakadu has joined #ocaml
julien_t has joined #ocaml
slicefd has quit [Quit: WeeChat 1.4]
zoobab has quit [Ping timeout: 248 seconds]
<orbitz> Does ctypes offer any conversion for PosixTypes.ssize_t?
butts_butts_ has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 240 seconds]
<orbitz> hrm, looks like the newer versions of Ctypes might have omething
<flux> didn't the number tell the offset of the function?-o
julien_t has quit [Ping timeout: 250 seconds]
zoobab has joined #ocaml
Anarchos has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
zoobab has quit [Ping timeout: 276 seconds]
zoobab has joined #ocaml
lokien_ has joined #ocaml
seangrove has joined #ocaml
Algebr` has joined #ocaml
<infinity0> flux: oh like the number of bytes from the front of the file? possibly i'll check that
<infinity0> hm it doesn't appear like it, from my results here
<Anarchos> Could someone be gentle to provide me a Makefile sample using ocamlbuild to build with ounit and bisect_ppx ?
hnagamin has quit [Ping timeout: 244 seconds]
<companion_cube> just write in _tags: <src/*>: package(ppx_bisect) or something?
<aantron_> its a bit convoluted due to conditional compilation
<Anarchos> aantron_ thanks
<aantron_> but look at the target test : and related targets
<aantron_> Anarchos, did you resolve your issue with bisect-ppx-report installation from the other day?
<Anarchos> aantron_ no.
<aantron_> bisect-ppx-report is installed by opam instead of the Makefile, so since you are not using opam, you would have to install it manually. do you have to do this repeatedly? then we should change the installation process
hnagamin has joined #ocaml
zoobab has quit [Ping timeout: 240 seconds]
Jane-PC is now known as Timmy
<Anarchos> aantron_ i guessed it was along those lines, so i installed it by hand.
Timmy is now known as Timmy--
<Anarchos> aantron_ anyway it would be cleaner if the install taget could be self-contained in case opam is not available.
john51 has joined #ocaml
malc_ has quit [Quit: leaving]
<aantron_> where did you install bisect-ppx-report?
hnagamin has quit [Ping timeout: 240 seconds]
ggole has quit []
<icicled> I solved the conditional linking of bisect_ppx based on a flag in oasis: http://sprunge.us/UEfT
<Anarchos> aantron_ i installed it at same place as bisect_ppx
<companion_cube> ah, nice
<icicled> I feel like this should be put up on the bisect_ppx FAQ or something
<icicled> so that new folks know how to get it working with oasis
<aantron_> icicled: taking a look
zoobab has joined #ocaml
snhmib has joined #ocaml
dpc__ has joined #ocaml
<snhmib> hello, i installed a library i want to use and it is in /usr/local/lib/ocaml/site-lib/<dir>
<snhmib> but when i am in the interpreter and try to use it i get: Error: Reference to undefined global
<snhmib> what am i missing?
<icicled> snhmib: you need to load the library first into the interpreter and then use it
<icicled> are you using utop per-chance?
<snhmib> utop?
<snhmib> i guess not
dpc_ has quit [Ping timeout: 240 seconds]
<icicled> what's the library called?
<snhmib> bitstring
<companion_cube> have you tried using ocamlfind?
<companion_cube> (rather than site-lib)
<icicled> thanks aantron_ !
<snhmib> i haven't
<snhmib> all i know about ocaml is 30 minutes of looking at basic tutorials :P
<companion_cube> oh :D
<icicled> snhmib: in the interpreter you can load a library via #load
<snhmib> yea i loaded it
<snhmib> thanks :)
<icicled> punch in: #load "/path/to/bitstring.cmo";;
<companion_cube> also #directory "/path/to/";; so it finds the .cmi
zoobab has quit [Ping timeout: 250 seconds]
<icicled> does something like fssnip exist for ocaml? http://fssnip.net/2Vq
<icicled> hover over keywords in the code example
<icicled> it should bring up type infor
<companion_cube> maybe merlin?
<Drup> higlo does that, iirc
<companion_cube> oh, as a web thing
zoobab has joined #ocaml
julien_t has joined #ocaml
<icicled> yea as a web snippet place
Algebr`` has joined #ocaml
<icicled> and would be neat to forward it to tryocaml
Algebr` has quit [Read error: Connection reset by peer]
MercurialAlchemi has quit [Ping timeout: 244 seconds]
<infinity0> is there a particular reason i can't do xxx |> Constructor but xxx |> (fun x -> Constructor x) works
<companion_cube> it's a long-standing issue, people have been complaining about constructors not being functions for years
<companion_cube> :)
Algebr``` has joined #ocaml
Algebr`` has quit [Ping timeout: 248 seconds]
<icicled> since it would be a new feature wouldn't it be ok?
<icicled> i.e. it won't break backwards compatibility
<infinity0> i guess someone just has to write a patch
<companion_cube> I think the issue is also consistency, for constructors with multiple arguments
<companion_cube> should they be curried, etc.
yunxing has joined #ocaml
<Drup> If it was just a matter of writing the patch, it would be done. XL doesn't want it because it could hides allocation (and there is the arity issue)
zoobab has quit [Ping timeout: 244 seconds]
yunxing has quit [Ping timeout: 276 seconds]
dpc__ has quit [Ping timeout: 244 seconds]
zoobab has joined #ocaml
iosys has quit [Quit: Leaving...]
yunxing has joined #ocaml
iosys has joined #ocaml
Timmy-- has quit [Read error: Connection reset by peer]
zoobab has quit [Ping timeout: 244 seconds]
Timmy-- has joined #ocaml
yunxing has quit [Ping timeout: 250 seconds]
zoobab has joined #ocaml
yunxing has joined #ocaml
john51 has quit [Quit: leaving]
john51 has joined #ocaml
struk|desk|away is now known as struk|desk
Timmy-- has quit [Quit: Leaving]
john51 has quit [Quit: leaving]
john51 has joined #ocaml
yunxing_ has joined #ocaml
yunxing has quit [Ping timeout: 252 seconds]
john51_ has joined #ocaml
john51 has quit [Ping timeout: 240 seconds]
darkf has joined #ocaml
john51 has joined #ocaml
john51__ has joined #ocaml
john51_ has quit [Ping timeout: 240 seconds]
julien_t has quit [Ping timeout: 276 seconds]
john51_ has joined #ocaml
john51 has quit [Ping timeout: 255 seconds]
<icicled> is there an example someplace of using tyxml by itself?
<icicled> a small example demonstrating how to build a html5 document would go a long way
yunxing has joined #ocaml
yunxing_ has quit [Read error: Connection reset by peer]
<icicled> I couldn't find an exmple on the source repo
silver has quit [Quit: rakede]
john51__ has quit [Ping timeout: 255 seconds]
<aantron_> i dont know of one, but i have a todo to improve the first pages someone visiting the repo will see
<aantron_> icicled, i can show you here now, if you would like
john51 has joined #ocaml
john51 has quit [Client Quit]
john51 has joined #ocaml
damason has quit [Ping timeout: 276 seconds]
john51_ has quit [Ping timeout: 244 seconds]
tane has quit [Quit: Verlassend]
john51 has quit [Client Quit]
john51 has joined #ocaml
struk|desk has quit [Remote host closed the connection]
john51_ has joined #ocaml
john51_ has quit [Client Quit]
john51_ has joined #ocaml
john51 has quit [Ping timeout: 244 seconds]
orbifx has quit [Quit: WeeChat 1.3]
Kakadu has quit []
Kakadu has joined #ocaml
<icicled> sure that would be appreciated
lordf has quit [Ping timeout: 276 seconds]
<Algebr```> icicled: http://pastebin.com/v5mg7acA
<Algebr```> followed by: http://pastebin.com/0WpJ9D5N
nojb has joined #ocaml
<Algebr```> I should write a blog post with that
<icicled> thanks Algebr``` that really helps
<Algebr```> yay
<Drup> Algebr```: instead of a blog post, I would prefer a PR ;)
<icicled> should sticky these examples on the source repo
<icicled> yea
<Drup> And I agree, the documentation is really lacking :(
<Algebr```> Drup: to what, to tyxml itself?
<Drup> yes
<Algebr```> okay, I will try to get to it
<icicled> is there a way in utop to print a list of sum type constructors for a given type?
<icicled> e.g. if type foo = Bar | Baz ... something like #print foo ?
<icicled> nvm, found it- #show_type;;
nojb has quit [Ping timeout: 240 seconds]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]