ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.02.1 announcement at http://ocaml.org/releases/4.02.html | Public channel logs at http://irclog.whitequark.org/ocaml
sheijk has joined #ocaml
q66 has joined #ocaml
AltGr has joined #ocaml
mcclurmc has joined #ocaml
manud__ has joined #ocaml
jlouis has quit [Ping timeout: 250 seconds]
jlouis has joined #ocaml
nojb has quit [Quit: nojb]
manud__ has quit [Ping timeout: 244 seconds]
mcclurmc_ has joined #ocaml
lordkryss has quit [Quit: Connection closed for inactivity]
mcclurmc has quit [Ping timeout: 255 seconds]
sheijk has quit [Ping timeout: 255 seconds]
samuel02 has joined #ocaml
samuel02 has quit [Ping timeout: 240 seconds]
thomasga has quit [Quit: Leaving.]
madroach has quit [Ping timeout: 250 seconds]
madroach has joined #ocaml
jabesed has joined #ocaml
pierpa has joined #ocaml
pierpa has quit [Client Quit]
pparkkin has joined #ocaml
pierpa`` has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
pierpa has joined #ocaml
pparkkin has quit [Ping timeout: 255 seconds]
manud__ has joined #ocaml
malc_ has quit [Quit: Lost terminal]
Sim_n has quit [Quit: Leaving]
boogie has quit [Remote host closed the connection]
darkf has joined #ocaml
MrScout_ has joined #ocaml
MrScout has quit [Ping timeout: 255 seconds]
MrScout_ has quit [Ping timeout: 258 seconds]
BitPuffin has quit [Ping timeout: 245 seconds]
chambart has quit [Ping timeout: 256 seconds]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
nadako has quit [Quit: Leaving]
shinnya has quit [Ping timeout: 258 seconds]
MrScout has joined #ocaml
MrScout has quit [Remote host closed the connection]
jabesed has quit [Ping timeout: 244 seconds]
jabesed has joined #ocaml
bytbox has quit [Remote host closed the connection]
samuel02 has joined #ocaml
vfoley- has quit [Remote host closed the connection]
samuel02 has quit [Ping timeout: 265 seconds]
jabesed has quit [Quit: Konversation terminated!]
claudiuc has quit [Remote host closed the connection]
ygrek has joined #ocaml
struktured has joined #ocaml
pparkkin has joined #ocaml
pparkkin has quit [Ping timeout: 255 seconds]
matason has quit [Ping timeout: 272 seconds]
govg has joined #ocaml
samrat has joined #ocaml
fraggle-boate has quit [Ping timeout: 244 seconds]
struktured has quit [Quit: Konversation terminated!]
fraggle-boate has joined #ocaml
struktured has joined #ocaml
jao has quit [Ping timeout: 240 seconds]
samrat has quit [Quit: Computer has gone to sleep.]
pparkkin has joined #ocaml
pparkkin has quit [Ping timeout: 258 seconds]
samuel02 has joined #ocaml
|jbrown| has joined #ocaml
dwoos_ has joined #ocaml
kerneis__ has joined #ocaml
jpdeplaix` has joined #ocaml
avsm has quit [Ping timeout: 255 seconds]
Plazma_ has joined #ocaml
manud__ has quit [Quit: Be back later ...]
govg has quit [Quit: leaving]
tokenrov1 has joined #ocaml
struktured has quit [Remote host closed the connection]
cthuluh_ has joined #ocaml
struktured has joined #ocaml
samuel02 has quit [Ping timeout: 265 seconds]
dmbaturin_ has joined #ocaml
jbrown has quit [Ping timeout: 264 seconds]
dwoos has quit [Ping timeout: 264 seconds]
sgnb has quit [Ping timeout: 264 seconds]
jpdeplaix has quit [Ping timeout: 264 seconds]
rwmjones has quit [Ping timeout: 264 seconds]
kerneis_ has quit [Ping timeout: 264 seconds]
srax has quit [Ping timeout: 264 seconds]
dmbaturin has quit [Ping timeout: 264 seconds]
cthuluh has quit [Ping timeout: 264 seconds]
tokenrove has quit [Ping timeout: 264 seconds]
ohama has quit [Read error: Connection reset by peer]
dwoos_ is now known as dwoos
ohama has joined #ocaml
mbac has quit [Remote host closed the connection]
mfp has quit [Read error: Connection reset by peer]
Plazma has quit [Read error: Connection reset by peer]
mbac has joined #ocaml
mfp has joined #ocaml
rwmjones has joined #ocaml
Plazma_ is now known as Plazma
boogie has joined #ocaml
samrat has joined #ocaml
avsm has joined #ocaml
q66 has quit [Quit: Leaving]
larhat has quit [Quit: Leaving.]
ggole has joined #ocaml
boogie has quit [Remote host closed the connection]
struktured has quit [Remote host closed the connection]
WraithM has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
psy has joined #ocaml
pparkkin has joined #ocaml
manud__ has joined #ocaml
pparkkin has quit [Ping timeout: 240 seconds]
mcclurmc has joined #ocaml
mcclurmc_ has quit [Ping timeout: 265 seconds]
WraithM has quit [Ping timeout: 272 seconds]
ggole_ has joined #ocaml
siddharthv_away is now known as siddharthv
ggole_ has quit [Client Quit]
manud__ has quit [Quit: Be back later ...]
<AltGr> avsm, should opam-in-a-box be uniquely dedicated to teaching, or does it have other uses ?
larhat has joined #ocaml
boogie has joined #ocaml
gdsfh has quit [Quit: Leaving.]
gdsfh has joined #ocaml
WraithM has joined #ocaml
samrat has joined #ocaml
boogie has quit [Ping timeout: 265 seconds]
AlexRussia has quit [Quit: WeeChat 1.1-dev]
ivan\ has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
ivan\ has joined #ocaml
jave has quit [Ping timeout: 255 seconds]
jave has joined #ocaml
* ggole curses whoever deprecated Array.create
WraithM has quit [Ping timeout: 256 seconds]
ggole has quit []
ygrek has quit [Ping timeout: 265 seconds]
pyon-free has quit [Ping timeout: 255 seconds]
pyon has joined #ocaml
<pyon> Why is "ref 1 = ref 1" true in OCaml?
<pyon> Shouldn't reference cells be compared by reference equality?
<adrien> if you want to do so, the operator is (==), not (=)
<pyon> Oh.
<pyon> Thanks!
<pyon> "match 1, 2 with a, b | b, a when a >= b -> a | _ -> 0" --> The REPL says that the pattern "b, a" is unused. Why?
<pyon> Shouldn't it first try "a, b when a >= b" and then "b, a when a >= b" ?
samuel02 has joined #ocaml
MercurialAlchemi has joined #ocaml
samuel02 has quit [Remote host closed the connection]
samuel02 has joined #ocaml
<flux> match 1, 2 with (a, b | b, a) when ..
<flux> I mean, it's the same thing
<flux> the 'when' covers all the cases, not only b, a
<flux> hmm, actually I see what you mean now :)
<flux> but it doesn't really work that way
<pyon> Mmm.
<flux> it only structurally matches for (a, b) and after pattern matching it evaluates the condition
<flux> if the guard fails, it moves to the next pattern
<pyon> AWww.
<flux> I wonder if anyone has even though of your use case when designing the guard clauses :)
bytbox has joined #ocaml
<flux> +t
pparkkin has joined #ocaml
<flux> in principle I could agree, though at the moment it doesn't need to be defined in which order the patter (a,b | b,a) is 'evaluted', whereas in your scenario it woudl matter
<pyon> Ah, true.
<pyon> In my actual code, I have something like "match read e1, read e2 with ((Node n1 as e), Node n2 | Node n2, (Node n1 as e)) where n1.level <= n2.level -> long_code_goes_here | ..."
ggole has joined #ocaml
<pyon> I guess I will have to factor long_code_goes_here outside.
<pyon> According to my program's logic, it happens to make no difference which is n1 and n2 if their levels are equal... but I can see why it would matter in the general case.
pparkkin has quit [Ping timeout: 255 seconds]
govg has joined #ocaml
samuel02 has quit [Remote host closed the connection]
siddharthv is now known as siddharthv_away
ygrek has joined #ocaml
mfp has quit [Ping timeout: 264 seconds]
pparkkin has joined #ocaml
arj has joined #ocaml
dmbaturin_ is now known as dmbaturin
samuel02 has joined #ocaml
pparkkin has quit [Ping timeout: 240 seconds]
natrium1970 has joined #ocaml
samuel02 has quit [Remote host closed the connection]
siddharthv_away is now known as siddharthv
<natrium1970> Suppose I have “type expr = Int of int | Var of string” and I want to create a function “let do_it e var = …” and enfroce the requirement that “var” must be a Var of string. In other words,
<natrium1970> do_it (Int 5) (Var “x”) would be accepted but do_it (Int 5) (Int 2) would fail.
<Unhammer> fail compile-time?
<natrium1970> (I realize that I could just make the “var” parameter have type string for this particular situation.)
<natrium1970> Yes.
<natrium1970> I’m afraid polymorphic variants is probably involved.
<natrium1970> Ocaml only fails at compile-time. At runtime it’s magic.
<Unhammer> well,
<Unhammer> match var with Int _ -> assert false | Var s -> dostuff_with s
<Unhammer> should fail run-time
<Unhammer> or, raise an Assert_failue
<Unhammer> +r
<ggole> natrium1970: your choices are pretty much assert false, or GADTs, or polymorphic variants, or stick a product type on the var and use that
<MercurialAlchemi> it sounds like a bad idea in the first place
<ggole> Unfortunately all of them have their complexities and annoyances.
<MercurialAlchemi> why do you want to do something like that?
<MercurialAlchemi> (as opposed to do_it int string)
<ggole> He might want to invoke operations on an expr inside do_it
<natrium1970> I simplified this example. In reality, expr would have many more possiblities.
<ggole> (Which you can do by wrapping the string in the appropriate constructor, but still.)
<Unhammer> type other = Var of string
<Unhammer> type expr = Int of int | Other of other
<natrium1970> expr actually would be an algebraic expression. And if a variable inside an algebraic expression is Var “x”, it seems reasonable that a variable (in the algebraic language) would have the same form.
<Unhammer> ?
<Unhammer> if you're lexing+parsing stuff, it might make sense to have two sets of types
<Unhammer> one "flat" set like type lexed_expr = Int of int | Var of string | …
<Unhammer> and one with more structure
<natrium1970> ggole: Following your suggestion of GADT’s, I have been looking for information online, but most of it seems to assume I already know GADTs from another language (like Haskell) or the examples are so complex that the basic ideas of GADT’s are obscured.
<natrium1970> Yeah, and basically, I’m trying to work out how to type this elegantly because I go off writing lots of code.
<Unhammer> type parsed_expr = V of literal | X of var (where literal holds stuff like Int_lit of int)
<ggole> If you don't know GADTs, don't go shoehorning them in
<ggole> They can lead to complexity very easily
<natrium1970> I’m just looking at the avaialble options. Don’t worry. I’m sure I will over-plan everything and never get anything useful working. :)
samuel02 has joined #ocaml
octachron has joined #ocaml
samuel02 has quit [Remote host closed the connection]
<natrium1970> Again, I appreciate all the help from all of you.
samuel02 has joined #ocaml
matason has joined #ocaml
psy has quit [Remote host closed the connection]
natrium1970 has quit [Quit: natrium1970]
zelines has quit [Read error: Connection reset by peer]
psy has joined #ocaml
matason_ has joined #ocaml
matason has quit [Ping timeout: 250 seconds]
thomasga has joined #ocaml
manud__ has joined #ocaml
pparkkin has joined #ocaml
pparkkin has quit [Ping timeout: 250 seconds]
rossberg has quit [Ping timeout: 258 seconds]
rossberg has joined #ocaml
nojb has joined #ocaml
mearnsh has quit [Ping timeout: 258 seconds]
mearnsh has joined #ocaml
bezirg has joined #ocaml
rossberg has quit [Ping timeout: 258 seconds]
rossberg has joined #ocaml
mearnsh has quit [Ping timeout: 258 seconds]
mearnsh has joined #ocaml
avsm has quit [Quit: Leaving.]
kakadu has joined #ocaml
rossberg has quit [Ping timeout: 258 seconds]
AlexRussia has joined #ocaml
rossberg has joined #ocaml
rand000 has joined #ocaml
rossberg has quit [Ping timeout: 258 seconds]
mearnsh has quit [Ping timeout: 258 seconds]
rossberg has joined #ocaml
rossberg has quit [Ping timeout: 258 seconds]
mearnsh has joined #ocaml
rossberg has joined #ocaml
ollehar has joined #ocaml
mearnsh has quit [Ping timeout: 258 seconds]
sgnb has joined #ocaml
avsm has joined #ocaml
ikaros has joined #ocaml
fraggle-boate has quit [Ping timeout: 250 seconds]
rossberg has quit [Ping timeout: 258 seconds]
avsm has quit [Client Quit]
mearnsh has joined #ocaml
jonludlam has joined #ocaml
rossberg has joined #ocaml
mearnsh has quit [Client Quit]
mearnsh has joined #ocaml
_andre has joined #ocaml
fraggle-boate has joined #ocaml
nojb has quit [Quit: nojb]
pparkkin has joined #ocaml
rossberg has quit [Ping timeout: 258 seconds]
rossberg has joined #ocaml
Thooms has joined #ocaml
BitPuffin has joined #ocaml
lordkryss has joined #ocaml
AltGr has left #ocaml [#ocaml]
nojb has joined #ocaml
octachron has quit [Ping timeout: 258 seconds]
ingsoc has joined #ocaml
manud__ has quit [Quit: Be back later ...]
zwer_p has quit [Remote host closed the connection]
zwer_p has joined #ocaml
siddharthv is now known as siddharthv_away
pparkkin has quit [Ping timeout: 258 seconds]
samuel02 has quit [Remote host closed the connection]
siddharthv_away is now known as siddharthv
milosn has quit [Remote host closed the connection]
Simn has joined #ocaml
pparkkin has joined #ocaml
dsheets has joined #ocaml
BitPuffin has quit [Ping timeout: 255 seconds]
K_ has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
BitPuffin has joined #ocaml
<Unhammer> let with_timeout secs f =
<Unhammer> Lwt.pick [ f;
<Unhammer> Lwt.bind (Lwt_js.sleep secs) (fun () -> Lwt.fail (Failure "timeout")) ]
<Unhammer> should that work?
milosn has joined #ocaml
<K_> I have a stream of objects (lwt_stream), that would like to parallel process the existing objects in the stream in Lwt threads. I would like that every processed element to be eliminated from the stream immediately. At any time, another thread might add arbitrary number of objects to the stream. Any suggestion?
<Unhammer> (or is there a better way to do Eliom_client.call_ocaml_service with a timeout handler?)
BitPuffin has quit [Ping timeout: 255 seconds]
gdsfh1 has joined #ocaml
gdsfh has quit [Ping timeout: 240 seconds]
zwer_p has quit [Remote host closed the connection]
zwer_p_y has joined #ocaml
gdsfh1 has quit [Client Quit]
skchrko has joined #ocaml
pgomes has joined #ocaml
<Drup> Unhammer: I think it should work.
<Unhammer> I can get it to work if I'm e.g. using a Lwt_js.sleep for "f" as well
<Drup> ?
<Unhammer> but not if "let f = Eliom_client.call_ocaml_service ~service:%check_text_service ()"
<Drup> ah, it probably doesn't yield or something like that :x
<Unhammer> (when I kill my server before the call)
ggole has quit [Ping timeout: 258 seconds]
<Drup> K_: Doesn't Lwt_stream.next do exactly what you want ?
<Drup> Unhammer: patch to add a timeout argument ? ;)
chambart has joined #ocaml
<K_> I am sending the output of Lwt_stream.next to a function that is blocking. I would like to iterate through the rest of the stream while the other function is in blocking state
<Drup> Oh
<Drup> use Lwt_preemptive to detach the blocking computation.
<Unhammer> call_ocaml_service calls raw_call_service which calls Eliom_request.http_(get|post) which calls Eliom_request.send, none of which take a timeout …
pgomes has left #ocaml [#ocaml]
elfring has joined #ocaml
<Unhammer> omg send is like three screenfuls
<Unhammer> I tell a lie. four.
gdsfh has joined #ocaml
<Drup> Is it sill in OCaml ? lucky then. :)
<Drup> Unhammer: before starting that, ask the question on the bugtracker, maybe there is another way.
<Unhammer> mm
<Unhammer> argh pressed enter too fast
octachron has joined #ocaml
ggole has joined #ocaml
ygrek has joined #ocaml
<K_> assume that I have Lwt_stream.next strm >>= blocking funciton. How I can use Lwt_preemptive?
<K_> ans this Lwt_stream is called inside a while_lwt true do
<Drup> hum, it's a blocking function, why is it returning a Lwt.t ?
<Drup> (you coudln't use >>= here otherwise)
<K_> Not sure. Not mine
<K_> why I can't use?
<K_> >>=
<Drup> are you sure it's really blocking ? ^^'
samrat has quit [Quit: Computer has gone to sleep.]
<Drup> K_: try to do "Lwt_stream.iter_p f strm" instead.
<Drup> it should fire all the functions as soon as possible for all the new elements.
<companion_cube> iter_p + Lwt_pool = <3
<K_> yep, I did, and and used junk to get rid of elements in the queue. For some reason, I had out of memory problem after some running time since stream has high input rate
<Drup> K_: I think the issue you have is that, afaik, a while loop waits for the body before starting the next loop
<Drup> and you precisely don't want that.
<K_> that is true
<Drup> you could simply do a recursive function that waits for next and as soon as it gets one, call Lwt.ignore_result (f elem) and recurse
<K_> hmm, I have written it as a recursive function now, but didn't use Lwt.ignore_result
<Drup> it you don't use it, it's going to wait for the thread
<K_> hmm, let me check
<Drup> (on the terminology side, waiting ≠ blocking)
<Drup> (usually, "blocking" means that it's a non-lwt function that takes time and doesn't cooperate, like, let's say, read_line)
<Leonidas> if one googles for "articheck icfp" one finds a paper by a certain "TBJPG Scherer". Well, that's quite a number of first names.
siddharthv is now known as siddharthv_away
hannes has joined #ocaml
nojb has quit [Quit: nojb]
chambart has quit [Ping timeout: 250 seconds]
<hannes> I'm unable to find documentation on whether polymorphic variants are guaranteed to have an ordering (thus, will with type f = [ `A | `B ] always be `B > `A)?
<hannes> (or should I if I want to rely on it, write down my own comparison for f?)
<Drup> They have an ordering, but I don't think you have any guarantee of what the ordering his.
<Drup> is*
<Drup> It should be the same on a fixed version of OCaml, but I wouldn't consider that it can't change along versions :)
<Drup> (basically, polymorphic variants are represented by a number which is the hash of the name and I would not be surprised if the comparison was just comparison on the hashes.)
keen___ has joined #ocaml
<ggole> There are some collisions of human-likely names iirc
<hannes> Drup: iirc variants have a guaranteed ordering, or don't they?
keen__ has quit [Ping timeout: 255 seconds]
<Drup> they have an ordering, you just don't know which one. :p
<Drup> ggole: Doesn't the compiler refuses to compile if it notices a collision ?
<ggole> Yeah, I think so
siddharthv_away is now known as siddharthv
Thooms has quit [Quit: WeeChat 1.0.1]
* Drup imagines ocamlc with a sign "On strike! No to hash collisions! :("
<ggole> Error: Variant tags `oZshTt and `jagJhn have the same hash value.Change one of them.
zwer_p_y is now known as zwer
<Drup> ggole: by curiosity, how did you find them ? :p
<ggole> Googling the subject -_-
<ggole> I assume somebody wrote a search program.
<Drup> ah, I expected you had one lying around x)
<flux> also it only occurs if the polymorphic variants end in the the same type
siddharthv is now known as siddharthv_away
cthuluh_ is now known as cthuluh
<flux> so you can have distinct `oZ.. and `jag.. in your program, but if you write `oZ..=`jag.., it's a compile time error
<flux> so basically only generated programs (ie. bindings) can hit this :)
<ggole> Ah, but you detect it anyway with some evil tricks
<ggole> type wrap = Wrap : 'a -> wrap
<ggole> Wrap `jagJhn = Wrap `oZshTt;; => true
<ggole> This is quite the corner case, but it's still a bit disconcerting.
<flux> Wrap 0 = Wrap []
<ggole> The ugliness here has more to do with the interaction of polymorphic recursion and magic (=), I guess
<flux> funny how Wrap (fun()->()) = Wrap [] -> false but Wrap (fun()->()) = Wrap (fun()->()) -> Exception: Invalid_argument "equal: functional value".
<flux> so I think if you're using the 'Wrap' construct in that way, you must already know the types are equal
<flux> otherwise the results are underspecified
<ggole> It's really a big fat lie that you can have (=) : 'a -> 'a -> bool
<ggole> Ah well, it's undeniably handy when you don't have type classes.
<flux> ..how about it implicits?
<flux> at least you can always get rid of (=) (ie. Core)
<flux> s/it/with/
<ggole> I'm hoping that implicits work out well.
<flux> hmm, actually Core only disabled ==, right?
<ggole> Yeah
<flux> are there Other Folks(TM) trying out the implicits branch?-)
<ggole> Which is a bit strange, since it makes perfect sense for many types
<ggole> They did have it under a more explicit name, which is perhaps a good idea.
sheijk has joined #ocaml
<flux> I would imagine using == instead of = is a really easy bug to make (especially after hacking basically in any mainstream language), and one that's difficult to notice as well
thomasga has quit [Quit: Leaving.]
<ggole> Sure.
<ggole> Easy to typo and thinko alike.
<companion_cube> polymorphic equality is bad anyway
<companion_cube> for once, I like janestreet's idea of aliasing == to `Use_physical_eq_function_instead or something like this
<adrien> :P
<companion_cube> anyway, the right thing to do is to use specialized equality functions
<flux> but it can be such a bother. in particularly when polymorphic types are involved.
<companion_cube> well sure, but you can't compare polymorphic values anyway
<companion_cube> you should ask for an equality function as an argument
<flux> sure you can? it's 'a :)
<companion_cube> (e.g. List.sort does)
<companion_cube> (for comparison, but same thing)
Thooms has joined #ocaml
<flux> well, it's typical to choose a different sorting criteria
<flux> but List.assoc would be more bothersome to use if it accepted a comparison operator
<flux> and you wouldn't be be able to use (=)
<companion_cube> oh, you use List.assoc?
<flux> sure
<companion_cube> http://cedeela.fr/~simon/software/containers/CCList.Assoc.html <--- so my solution is an optional argument
<companion_cube> so you can provide a good equality function if required
davine has joined #ocaml
_5kg has quit [Ping timeout: 240 seconds]
nojb has joined #ocaml
thomasga has joined #ocaml
bytbox has quit [Ping timeout: 255 seconds]
BitPuffin has joined #ocaml
matason_ has quit [Ping timeout: 255 seconds]
samuel02 has joined #ocaml
kaustuv has joined #ocaml
<kaustuv> Can someone help me understand this error message? http://pastebin.com/MhXVUjgK
samrat has joined #ocaml
<Drup> kaustuv: the asnwer is "don't mix subtyping and gadt"
<ggole> kaustuv: you need to annotate a bit more
<dsheets> it's ok, but you need to explicitly declare the type variable polymorphic
<companion_cube> isn't it an issue of polymorphic recursion?
<ggole> let rec untaint : type a . a tree -> [ `good ] tree = function | Taint _ -> failwith "Cannot untaint this tree" | Leaf -> Leaf
<companion_cube> yeah, +1
<ggole> (Which is missing a case, but you can just fix that.)
<Drup> that's ... going to help you a little bit
<Drup> but in the long run ... eww
<kaustuv> ggole: Hmm, OK. Thanks
<kaustuv> But I wish the type would be a bit more precise.
<Drup> I tried, it doesn't really work :(
<ggole> Of course, GADTs lead to exercising the parts of your brain that understand typing :)
<ggole> Or to them turning black and falling off.
<K_> Drup, Is there any limitation on the number of Lwt threads?
<Drup> not as far as I know
srax has joined #ocaml
<Drup> check the documentation ^^'
davine has left #ocaml ["Leaving"]
<kaustuv> I'm afraid Drup was right: http://pastebin.com/KBCTW7qX
<Drup> No, that's just because you tried to change the annotation :)
<Drup> go back the one proposed "type t . t tree -> ..."
<kaustuv> Have you actually tried doing it? It doesn't work for me.
<Drup> works fine here
<kaustuv> Hmm. What version of OCaml are you running? I'm trying this in 4.02.1
pparkkin has quit [Ping timeout: 256 seconds]
<kaustuv> Odd. I see this: http://pastebin.com/csu4wKUC
chambart has joined #ocaml
fraggle-boate has quit [Ping timeout: 264 seconds]
<Drup> you changed it again. :D
<Drup> all the keywords are important, it's "type a . a tree -> ..."
<kaustuv> Is that not synonymous with 'a. 'a?
<Drup> No.
<kaustuv> OK, that's really arcane. I would appreciate details of the differences.
samuel02 has quit [Remote host closed the connection]
<kaustuv> Did you read the "is automatically expanded into" bit at the end of the "Polymorphic syntax" section?
<kaustuv> I guess I see the issue. I need to add (type t) arguments to the fun expression as well.
zwer has quit [Remote host closed the connection]
_5kg has joined #ocaml
zwer has joined #ocaml
emery has joined #ocaml
matason has joined #ocaml
<kaustuv> Also it looks like the type t1. t2 form is not allowed as a general type constructor. It's only a syntactic sugar for let-expressions.
<kaustuv> type foo = { foo : 'a. 'a -> 'a } (* works *)
<kaustuv> type oof = { oof : type t. t -> t } (* rejected *)
fraggle-boate has joined #ocaml
<Drup> it doesn't really make sense in this position anyway
<Drup> this form is polymorphic recursion ('a . 'a ...) *and* introduction of an abstract type
<Drup> you don't need to introduce an abstract type for a signature
<kaustuv> I though OCaml supported this kind of existential quantification
<Drup> that's an universal and yes, it supports it, since you did it with your foo type :)
davine has joined #ocaml
<kaustuv> It's a type variable that's not in argument position, so it's existential surely!
<Drup> no :)
<Drup> this is an existential : "type ex = Ex : 'a -> ex"
<kaustuv> how is that different from the foo case above?
<kaustuv> (suitably modified)
<Drup> you mean, from "type foo = { foo : 'a . 'a }" ?
<kaustuv> yeah
<Drup> well, you can put anything inside ex and nothing inside foo
hyperboreean has quit [Remote host closed the connection]
davine has quit [Client Quit]
<Drup> or, more precisely, you can put inside foo only things that unify with 'a, for all 'a
<kaustuv> That explanation makes the baby Curry-Howard cry
<Drup> why ? :p
<Drup> we can take a more interesting example, if you want
<Drup> inside "type foo = { foo : 'a . 'a -> 'a }" you can put only functions that are polymorphic and of type 'a -> 'a
<Drup> inside "type ex = Ex : ('a -> 'a) -> ex" we can put any function that unifies with 'a -> 'a, for example incr (of type int -> int)
<Drup> (if we assume purity, this means we can only fit the identity inside foo)
<kaustuv> So you're saying that the type of the {} is (\forall a. a -> a) -> foo ?
<Drup> Yes.
<Drup> A universal, as I said.
<kaustuv> So it's a negatively occurring \forall, which is I guess not an \exists
<Drup> arg, I read badly, the forall is outside :)
<Drup> hum
<Drup> I would rather say that "foo = ∀a . a -> a"
<Drup> the fact that there is wrapper doesn't matter.
darkf has quit [Quit: Leaving]
<kaustuv> Ah, so this is more system-F-like polymorphism than traditional ML
<Drup> I suppose you could put it like that, yeah. It's always annoying to manipulate 'a in ML since sometimes it's a unification variable and sometime it's a polymorphic type
govg has quit [Quit: leaving]
<kaustuv> Anyway, back to GADTs, I really want to be able to say:
<kaustuv> type _ tree = Leaf : [ `good ] tree | Stump : [ `bad ] tree
<kaustuv> | Node : 'a tree * 'b tree -> [ 'a | 'b ] tree
<kaustuv> Is something like this doable in OCaml?
<kaustuv> I guess I could have many variants of Node to cover all possibilities, but that doesn't scale for my use case.
<Drup> no, you can't manipulate row variables :/
<Drup> also, note that your type is not covariant
<Drup> is going to cause issues if you want the subtyping properties.
<Drup> It's*
<kaustuv> All right. Thanks.
octachron has quit [Ping timeout: 255 seconds]
bezirg has quit [Ping timeout: 255 seconds]
samuel02 has joined #ocaml
<kaustuv> http://pastebin.com/HW9cWNmQ is a possibility as well, I guess
<kaustuv> Oops, also need the reflexive cases
<Drup> you can also drop the GADT and use smart constructor and a regular (covariant) phantom type
K_ has quit [Ping timeout: 246 seconds]
<kaustuv> That's the code I already have. I was trying to see if I could push some invariants from the code into the types
planetlarg has joined #ocaml
octachron has joined #ocaml
larhat has quit [Quit: Leaving.]
someTS has joined #ocaml
larhat has joined #ocaml
larhat has quit [Client Quit]
<Drup> It works well if you don't need the variance
WraithM has joined #ocaml
<Drup> kaustuv: http://caml.inria.fr/mantis/view.php?id=6653 you might be interested by this.
arj has quit [Ping timeout: 272 seconds]
WraithM has quit [Ping timeout: 265 seconds]
<kaustuv> I'm giving up on this for now, but I wonder if there is something I'm missing here: http://pastebin.com/NtwpVi5x
<kaustuv> Basically, (how) can I constrain the type of the scrutinee in a case arm?
<ggole> kaustuv: you might be able to use a trick like this https://gist.github.com/gsg/e8abe67399bdbcad37c4
<ggole> Oh, seems you know it already
<kaustuv> (Ignore the logic of exclude_bad there, which is incorrect. It's the reflexive case arm that I care about.)
octachron has quit [Quit: Leaving]
<ggole> I think you need to pull the reflexive part into its own type
<ggole> At least, I couldn't make it work when I tried to do that
<Drup> I'm not sure you can do that
<Drup> you would need a runtime type check, no ?
tia__ has joined #ocaml
<kaustuv> Yeah, I guess you're right.
tia__ has left #ocaml [#ocaml]
<kaustuv> It seems that what I want is not full subtyping support, just a (weak?) form of refinement types
<Drup> you really have only two variants ?
<Drup> then you will probably be ok without variance, because you don't need constrained polymorphism, you are polymorphic or not, but nothing in between :)
<kaustuv> Yes, but that's the "many variants of the Node constructor" design I was trying to avoid
<Drup> (the issue will come back if you add `maybe and you try to take [`good | `maybe] tree.
<kaustuv> In my actual use case, the set of "tags" is fixed and indeed has only two cases.
matason has quit [Quit: Later!]
arj has joined #ocaml
axiles has joined #ocaml
arj has quit [Ping timeout: 264 seconds]
shinnya has joined #ocaml
arj has joined #ocaml
davine has joined #ocaml
someTS is now known as chinglish-nihao
Hannibal_Smith has joined #ocaml
davine has left #ocaml [#ocaml]
matason has joined #ocaml
kaustuv has left #ocaml ["ERC Version 5.3 (IRC client for Emacs)"]
bytbox has joined #ocaml
arj has quit [Quit: Leaving.]
samuel02 has quit []
nojb has quit [Ping timeout: 244 seconds]
ikaros has quit [Quit: Ex-Chat]
Thooms has quit [Quit: WeeChat 1.0.1]
mort___ has joined #ocaml
Unhammer has quit [Ping timeout: 264 seconds]
chinglish-nihao has quit []
chinglish__nihao has joined #ocaml
planetlarg has quit [Quit: Ex-Chat]
K_ has joined #ocaml
<_andre> given a type type t = [`A | `B], ocaml doesn't let me do something like this: let f () : [`A] = `A in let g () : [`B] = `B in [f (); g ()]
<_andre> is there any feature in the language that will allow something like that?
<_andre> the idea is to write a function f that only cares about `A without having to have a | _ -> failwith ... case
<whitequark> subtyping
<whitequark> [(f () :> t); (g () :> t)]
<Drup> no need for that ...
<Drup> _andre: replace [`A] by [>`A]
<whitequark> or return [>`A]
<Drup> (and same for `B
<Drup> the > means that "I contains at least some `A, maybe more"
<_andre> yeah i know about >, but it's kind of a lie in that case isn't it? since the function always returns `A
<Drup> It's not really a lie, it's just a way to tell the typesystem that you don't mind having the result of f and g unified into a bigger type.
<whitequark> actually, [>`A] can not ever be a not lie
<Drup> (the typesystem wouldn't let you lie :p)
<whitequark> er, nevermind
<Drup> "can not ever be a not lie" too many negations, cannot compute :O
<whitequark> use a symbolic executor to help you
mort___ has quit [Quit: Leaving.]
skchrko has quit [Quit: Leaving]
jonludlam has quit [Quit: Coyote finally caught me]
<_andre> how about this case? http://pastebin.com/t2swtp8F
<Drup> [< instead of [>
<Drup> you don't want "something bigger than `A
<Drup> because you can't handle it
<Drup> If you let the compiler tell you the type (with merlin for example), you'll see it.
<_andre> the idea was to be able to use f where functions `t -> int` are expected
<Drup> and how do you except f will handle `B ?
<_andre> the point was trying to get a compilation error if `B is passed to f instead of having f raise an exception in that case
struktured has joined #ocaml
<Drup> then you can't possible unify f with "t -> int" ....
<Drup> if a function is of type "t -> int", it necessarily accepts `B.
ollehar has quit [Ping timeout: 264 seconds]
ollehar has joined #ocaml
struktured has quit [Ping timeout: 245 seconds]
mcc has joined #ocaml
<companion_cube> anyone knows how to have ocamlbuild build a library with modules A,B,C, but hide the interface of A?
<companion_cube> so that A is linked (required by B,C) but not exposed to the user?
<_andre> with oasis you can set InternalModules: A, iirc
<mcc> Hi hi… so I have a problem... I want to recursively print an object graph. An object in this graph has a Hashtbl member that could point to another object which could in turn point back to itself.
<mcc> So I need either a builtin function for doing this safely, or a way to explore the entire object graph safely while somehow being aware of which objects I have already visited.
<mcc> In other languages, I can often get a unique ID (such as a pointer in memory) for a given object, so I can just build up a table of "objects I've seen" and not revisit those…?
tharugrim has quit [Ping timeout: 245 seconds]
<Drup> yes, just build a set of the previously visited object
<Drup> you can use "==" for the "pointer equality"
tharugrim has joined #ocaml
slash^ has joined #ocaml
<ggole> You only need identity for mutable things, you could stick an id in those
<mcc> drup: thanks
<mcc> ggole: yeah, i was thinking about that
<mcc> drup: i think i was… if i say a == b on two hash tables, that's "is this the same hash table" not "are these hash tables equal in content"?
ingsoc has quit [Quit: Leaving.]
<Drup> former
<Drup> "a = b" is the later
<ggole> Right. But hashing is a bit problematic then, because you don't want to go and look at the structural bits, but you don't have access to the pointer.
<ggole> So you can make up a unique int and use that as identity.
<whitequark> hashconsing!
<Drup> ^
<ggole> Doesn't work for things with identity.
<mcc> oh… huh
<ggole> Well, not so much "doesn't work" as "doesn't apply"
<mcc> drup: ok so the = vs == thing… if I use Set or Hashtbl from the standard library… which standard of equality do they use for keys? = or ==?
<Drup> =
rz has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
<ggole> You can use the functor part of Hashtbl to get the exact equality operation you want.
<mcc> oh, ok
<whitequark> Hashtbl.Make(struct let equal = (==) let hash {id} = id end)
<whitequark> or something.
<ggole> Yep
shinnya has quit [Ping timeout: 258 seconds]
<mcc> cool
<mcc> what is let hash {id} = id
<mcc> i mean i don't think i understand what the pattern matcher will do in that circumstance
<ggole> It's record destructuring
<ggole> Picks the field id out of the argument
<mcc> i see. so this functor assumes the id is part of the record
<ggole> Eg let hash (r:table) = r.id
<ggole> Funny you bring this up, I was writing a similar thing today
<whitequark> mcc: this instantiation
<whitequark> you control how the hash is computed
<whitequark> that's the whole point
<ggole> Although now I look at it, hash doesn't shortcut
jpdeplaix` is now known as jpdeplaix
shinnya has joined #ocaml
chaptastic has quit []
K_ has quit [Quit: Page closed]
divyansh_ has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
Hannibal_Smith has quit [Quit: Sto andando via]
chambart has quit [Ping timeout: 272 seconds]
q66 has joined #ocaml
tane has joined #ocaml
rand000 has quit [Ping timeout: 255 seconds]
enquora has joined #ocaml
axiles has quit [Quit: Quitte]
dsheets has quit [Ping timeout: 258 seconds]
kakadu has quit [Quit: Page closed]
Unhammer has joined #ocaml
malc_ has joined #ocaml
sgnb has quit [Remote host closed the connection]
sgnb has joined #ocaml
samuel02 has joined #ocaml
mcc has quit [Quit: This computer has gone to sleep]
Arsenik has joined #ocaml
mfp has joined #ocaml
divyansh_ has quit [Quit: Textual IRC Client: www.textualapp.com]
gasche has quit [Ping timeout: 265 seconds]
gasche has joined #ocaml
ollehar has quit [Ping timeout: 256 seconds]
_whitelogger has joined #ocaml
SomeDamnBody has joined #ocaml
<SomeDamnBody> So, I having trouble adding a variable to a let bound function
<SomeDamnBody> basically, I have:
<SomeDamnBody> let some_variable_bound_before = something;;
<SomeDamnBody> let some_func prog = function | match_cases... | end_cases;;
<SomeDamnBody> and somewhere in some_func, it uses some_variable without it being passed, meaning the let some_variable must be defined before some_func
<SomeDamnBody> but I have a need to move some_variable outside, and therefore want to pass it into some_func
thomasga has quit [Quit: Leaving.]
keen___ has quit [Read error: Connection reset by peer]
keen___ has joined #ocaml
<Leonidas> SomeDamnBody: so, where is the problem?
<Leonidas> what do you mean by "move it outside"? Outside of what?
larhat has joined #ocaml
<SomeDamnBody> The problem is I want to redfine some_func as
<SomeDamnBody> let some_func prog some_variable_bound_anywhere arg = match arg with | cases... ;;
<SomeDamnBody> but the compiler keeps rejecting it, because the function some_func is used with a List.fold_left
<Leonidas> SomeDamnBody: yes, you can do that?
<SomeDamnBody> let me show you the error...
<Leonidas> ah, then you need to use currying
contempt has quit [Read error: Connection reset by peer]
<Leonidas> let some_func some_variable_bound_anywhere prog = function … ;;
<Leonidas> and then pass (some_func value_of_that_variable) as the function to fold_left.
<SomeDamnBody> right
<SomeDamnBody> I tried to.
<SomeDamnBody> line 67, characters 9-26:
<SomeDamnBody> Error: This expression has type
<SomeDamnBody> Arch.arch option -> Iltrans.prog -> Iltrans.cmd -> Iltrans.prog
<SomeDamnBody> but an expression was expected of type
<SomeDamnBody> Arch.arch option -> Iltrans.prog -> Arch.arch option
<SomeDamnBody> Type Iltrans.cmd -> Iltrans.prog is not compatible with type
<SomeDamnBody> Arch.arch option
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
<SomeDamnBody> the List.fold_left:
<Leonidas> SomeDamnBody: there is something else wrong, because it used to return Iltrans.prog and now it returns Arch.arch option
<SomeDamnBody> List.fold_left (apply_cmd arch (Ast prog)) pipeline
<SomeDamnBody> apply_cmd definition:
<SomeDamnBody> let rec apply_cmd arch prog = function
<companion_cube> you should use pastebin
<SomeDamnBody> ok...
milosn has quit [Remote host closed the connection]
<companion_cube> not sure what the problem is, but maybe you wanted let rec apply_cmd arc prog = match prog with ...
contempt has joined #ocaml
<companion_cube> the type error seems to complain that there is one excedentary argument
<SomeDamnBody> well if you read the definition, I think that there is an unnamed variable that "function" keyword introduces
<companion_cube> yes
<companion_cube> function .... is like fun x -> match x with ...
<SomeDamnBody> so, removing that, it would be let rec apply_cmd arch prog arg = match arg with
<SomeDamnBody> and then the rest
<companion_cube> yes
<SomeDamnBody> but I don't understand how adding a single variable introduces an issue
<SomeDamnBody> I tried doing the replacement...
<companion_cube> so the issue is elsewhere
<SomeDamnBody> it will give this error:
<SomeDamnBody> (with this definition: let rec apply_cmd arch prog cmd = match cmd with)
<SomeDamnBody> Error: This expression has type
<SomeDamnBody> Arch.arch option -> Iltrans.prog -> Iltrans.cmd -> Iltrans.prog
<SomeDamnBody> Arch.arch option -> Iltrans.prog -> Arch.arch option
<SomeDamnBody> but an expression was expected of type
<SomeDamnBody> Type Iltrans.cmd -> Iltrans.prog is not compatible with type
<SomeDamnBody> Arch.arch option
<companion_cube> do you have a .mli ?
<companion_cube> (btw, you might want to merge the inner matches into the outer match)
<companion_cube> (match cmd, prog with AnalysisAst f, Ast p -> ...)
<SomeDamnBody> well... this is how it was written. That would be good, I agree that you're right, but I get paid, and elegance comes after functionality
<SomeDamnBody> do you think maybe named variables would help?
<companion_cube> sure :)
<companion_cube> so, do you have a .mli ?
<SomeDamnBody> ... I can derive one
<companion_cube> no, I was just checking
<SomeDamnBody> you don't want what would be derived?
<companion_cube> no, it's just that the error could have been a mismtch between .ml and .mli
chaptastic has joined #ocaml
<companion_cube> what I don't understand is why ocaml expects the type to be a binary function
<SomeDamnBody> Do you think it could be the restrictions placed on function as a keyword, in that it allows only one argument? so adding an argument violates that, then it needs to be rewritten but when it's rewritten it's no longer polymorphic?
samuel02 has quit [Remote host closed the connection]
<SomeDamnBody> I would have thought that currying was in the right order
<companion_cube> it's clearly a definition of a ternary function, and the compiler does infer that the function takes 3 arguments (and is well typed?)
<companion_cube> but for some reason it wants the function to be binary
<SomeDamnBody> well, List.fold_left should the the function approproiately
<SomeDamnBody> I mean, i only gave 2 arguments...
<companion_cube> even weirder, because then List.fold_left expects a binary function and you give it a unary one (two arguments already applied)
<companion_cube> try annotating each relevant function with its type and see where it fails
<SomeDamnBody> companion_cube, do you think giving them as named arguments would help?
jabesed has joined #ocaml
Anarchos has joined #ocaml
<companion_cube> I'm don't think so
<companion_cube> -'m
kakadu has joined #ocaml
davine has quit [Ping timeout: 272 seconds]
typedlambda has quit [Ping timeout: 250 seconds]
<SomeDamnBody> ok... one sec
typedlambda has joined #ocaml
elfring has quit [Quit: Konversation terminated!]
<SomeDamnBody> actually, I think the type checker concludes the correct arguments
<SomeDamnBody> because I just got the exact same error:
_andre has quit [Quit: leaving]
<SomeDamnBody> companion_cube, ^
typedlambda has quit [Ping timeout: 250 seconds]
rand000 has joined #ocaml
<Leonidas> yes, that would've been odd, usually the type checker is pretty good at its job
<companion_cube> strange
<companion_cube> so it must be at some place where you use the function
<SomeDamnBody> Leonidas, yes, ocaml's type checker pushes the bounds on what can be realistically expected-I took a class the prof said that the only time it forces you to supply a type is if it's impossible to know
<companion_cube> indeed, in some cases you need to provide the type
<Drup> s/some cases/with GADTs/
<Drup> (ok, and polymorphic recursion ... that doesn't happen often)
<SomeDamnBody> well here's where I use it:
<SomeDamnBody> let f = (Iltrans.apply_cmd arch (Ast prog)) in
<SomeDamnBody> let processed_prog = (List.fold_left f Iltrans.pipeline) in
rgrinberg has joined #ocaml
<SomeDamnBody> I have no idea...
nadako_ has joined #ocaml
chinglish__nihao has quit [Ping timeout: 265 seconds]
<companion_cube> the type of f is a unary function, isn't it?
chaptastic has quit []
manud__ has joined #ocaml
<SomeDamnBody> well apply_cmd is bound to two variables...
typedlambda has joined #ocaml
<SomeDamnBody> the let definition with the let apply_cmd arch prog = function...
malc_ has quit [Quit: leaving]
<SomeDamnBody> should mean that it is waiting to receive each of the elements from pipeline in fold left
shafire has joined #ocaml
<shafire> hi
<shafire> does ocaml support automatic parallelism?
<Drup> not really
<SomeDamnBody> shafire, check out jocaml
<shafire> thanks
<shafire> I am looking into MirageOS, maybe I can use it with jocaml :)
<Drup> not a chance, no ;)
<SomeDamnBody> oh wait...
<Drup> jocaml compiles ocaml to jvm
<Drup> you're never going to use that with mirage :D
<SomeDamnBody> Drup, what? Mirac...
<SomeDamnBody> ??!?!?
<SomeDamnBody> jocaml does that?
<SomeDamnBody> I thought that was the purpose of the ocamljava project
<Drup> let me check, maybe I'm confusing something
<SomeDamnBody> shafire, there are other OS elision cloud mechanisms that perform what mirage does, and they can supply you a jvm to use
<Drup> shafire: anyway, mirage is not built to do parallelisation, so ...
<shafire> SomeDamnBody: I found osv.io, do you know another one?
<SomeDamnBody> Drup, if you don't like jocaml, you can build your own communication primitives with zmq
<SomeDamnBody> I use the shit out of ZMQ, and there's a nice binding to it
<Drup> SomeDamnBody: it's not that I don't like it
<Drup> it's just that you're not going to use that with mirage
<whitequark> Drup: it's ocamljava
<whitequark> jocaml is join calculus
<Drup> ah, right !
<SomeDamnBody> turns out, the let binding to pass arch should allow prog to be passed in the list.fold left line lol
<SomeDamnBody> idk what osv.io is
<Leonidas> jocaml seems abandoned, too
<nicoo> Drup: You are confused, jocaml is ocaml with join-calculus
<nicoo> which allows to express some //ism
<nicoo> Damn, whitequark was faster
<Drup> still message passing based ?
<SomeDamnBody> Drup, zmq?
<Drup> no, jocaml.
<SomeDamnBody> yes, zmq is a nice mechanism that facilitates message passing well. Altering mechanisms to be from program internal to hit a different machine is a string prefix exchange
<SomeDamnBody> yes jocaml is message passing based
<SomeDamnBody> it's far more mathematical though
<SomeDamnBody> being the only implementation that I know of of the pi-calculus
samrat has quit [Ping timeout: 255 seconds]
<SomeDamnBody> it allows you to express mathematically the architecture of the network
tokenrov1 is now known as tokenrove
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
samrat has joined #ocaml
<rgrinberg> Drup: did ocsigen purge away oasis???
<Drup> purge away ?
<rgrinberg> get rid of
<Drup> why do you think that ?
<rgrinberg> oh nvm it looks like eliom never used it
<Drup> eliom can't use it
<Drup> there are several issues with oasis that prevents it
slash^ has quit [Read error: Connection reset by peer]
<Drup> you basically can't define eliom libraries with oasis
<rgrinberg> Can you define js_of_ocaml libs with oasis?
<Drup> yes, that's fine
<Drup> the issue is the fact that with eliom, you have modules with the same name in the module tree
<Drup> and with oasis, you can't install them both
<Drup> (there are other issues, dues mostly to oasis's lack of flexibility)
<Drup> but this one is the really big one
samuel02 has joined #ocaml
<rgrinberg> yeah I think I ran into that issue myself btw with cohttp. I wanted to have Cohttp.S and Cohttp_lwt.S but oasis did not let me. (was a while ago, could be confused now)
SomeDamnBody has quit [Ping timeout: 245 seconds]
<Drup> no, that's not the same module name
<Drup> I mean, *really* the same name ;)
samuel02 has quit [Remote host closed the connection]
<Drup> just two implementations, one for client and one for server
ggole has quit []
igstan has joined #ocaml
<pyon> How does (<) work on non-numeric types?
<pyon> non-numeric and non-string
<rgrinberg> I see. That's a bummer
<Drup> rgrinberg: tyxml is still with eliom :)
<Drup> with oasis*
<rgrinberg> yeah that's what gave me the false impression btw
<rgrinberg> i assumed that since tyxml used oasis everything else did
<Drup> I think dinosaure tried to change ocsigen's build system, but didn't succeeded :D
<Drup> ocsigenserver*
<Drup> js_of_ocaml's one work ok, so no real need to change it
<rgrinberg> assemblage will save us all…
<rgrinberg> us or our grandkids
<Drup> :D
<Drup> I will happily replace eliom-distillery when assemblage finally arrives.
davine has joined #ocaml
davine has quit [Quit: Leaving]
samrat has quit [Quit: Computer has gone to sleep.]
<nicoo> pyon: It calls compare in all cases
<nicoo> pyon: And compare is evil C code that ... does thigs
<nicoo> (somewhat like Hashtbl.hash, but compares instead of hashing)
jonludlam has joined #ocaml
Thooms has joined #ocaml
SomeDamnBody has joined #ocaml
MrScout has joined #ocaml
reventlov is now known as Reventlov
nadako_ is now known as nadako
samuel02 has joined #ocaml
ddosia has joined #ocaml
Unhammer has quit [Remote host closed the connection]
samuel02 has quit [Ping timeout: 264 seconds]
<companion_cube> jocaml isn't on jvm
samuel02 has joined #ocaml
<whitequark> you're the third one :p
<Drup> =')
samuel02 has quit [Ping timeout: 256 seconds]
<companion_cube> just to be sure :p
MrScout has quit [Ping timeout: 258 seconds]
<pyon> nicoo: So, basically, I should only use (<) on ints, floats and strings, right?
<pyon> (Well, also arrays and tuples of them.)
rgrinberg has quit [Quit: Leaving.]
<nicoo> companion_cube: Yell it at him in meatspace. That's the only way to be sure
manud__ has quit [Quit: Be back later ...]
<nicoo> pyon: No, you can use compare on lots of things, as long as you only care about having some total order (mostly, to build datastructures on top of it)
_5kg has quit [Ping timeout: 250 seconds]
ddosia has quit [Quit: Leaving.]
<Drup> (typical example: Map)
_5kg has joined #ocaml
larhat has quit [Ping timeout: 240 seconds]
Anarchos has joined #ocaml
larhat has joined #ocaml
rgrinberg has joined #ocaml
<pyon> I want something like "type conatural = Finite of nat | Omega".
<pyon> Where "Omega > Finite n" for any n.
SomeDamnBody has quit [Ping timeout: 265 seconds]
<Drup> pyon: define your own comparison function
<Drup> it's the only way to be sure.
<Drup> the polymorphic comparison is implementation defined and there is no guarantee about it.
manud__ has joined #ocaml
ddosia has joined #ocaml
<ddosia> Hello. I am interesting in source code for Core's String.rtrim and in ?drop argument in particular. Only thing I found is ~/.opam/4.02.1/lib/core/core_string.ml, which contains only one line of code "include Core_kernel.Core_string"
<ddosia> and seems there is no source code for Core_kernel
<ddosia> ocaml is installed through opam
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
Reventlov is now known as Reventlov
<Drup> ddosia: "opam source pkg" allows to get the source of a package
<ddosia> Drup: what package should I specify?
<Drup> no idea, not a core user.
<Drup> probably core_kernel.
sheijk has quit [Ping timeout: 255 seconds]
samuel02 has joined #ocaml
<ddosia> thanks, that is helpful
milosn has joined #ocaml
Arsenik has quit [Remote host closed the connection]
tane has quit [Quit: Verlassend]
<ddosia> s/String.rtrim/String.rstrip/g
kakadu has quit [Quit: Konversation terminated!]
libertas has joined #ocaml
matason has quit [Quit: Leaving...]
samuel02 has quit [Ping timeout: 244 seconds]
<companion_cube> rgrinberg: now that ppx_deriving and ppx_import are there, won't you reconsider your choice of using core? ;)
<rgrinberg> Sure, containers is almost there for me...
<rgrinberg> But i'd also rather not leave core users in the dust. In an ideal world type_conv/deriving would be compatible and always available under deptopts
<Drup> for that, someone would need to fix camlp4
<Drup> good luck to the someone in question :/
<companion_cube> Janestreet should migrate type_conv to ppx, I think
<rgrinberg> i think they are doing that
<rgrinberg> it's too early to abandon 4.01 though
<companion_cube> should be too hard to replace "with sexp" into "[@@deriving sexp]"
<companion_cube> shoulnd't
<companion_cube> I'm playing with a ppx_deriving_cconv, also ;)
<rgrinberg> i'm definitely reconsidering async as opposed to core though
<rgrinberg> seems like JS has been dragging their feet making async portable
thomasga has joined #ocaml
<companion_cube> Lwt has a lot of traction those days
<rgrinberg> yep. i'm thinking of porting opium to lwt and gutting async
<ddosia> rgrinberg: thanks
thomasga has quit [Read error: Connection reset by peer]
thomasga has joined #ocaml
AlexRussia has quit [Ping timeout: 240 seconds]
<ddosia> I want to test just compiled code in utop. I run utop as: `utop -I _build` to add my files there, now it does suggestions on my module names and contents, but fail to run any functions with this error:
<ddosia> Bob.response_for;; Error: Reference to undefined global `Bob'
<flux> #load "bob.cmo";;
<ddosia> basically how do you use REPL to test code you just wrote?
<flux> I run toplevel in emacs and send fragments or code, or whole buffers, to it
<flux> if I need to do testing involving multiple modules, I can load then with #load
<flux> or, I think, nowadays there is some new directive that loads a module source code in a similar fashion #load does..
<rgrinberg> you can also compile custom top levels AFAIK but it's a hassle
ivan\ has quit [Ping timeout: 255 seconds]
<ddosia> flux: if I understood my current problem correctly, toplevel caught module description but not caught it's implementation?
<flux> if you have a framework and you want to do tests with that interactively, it can be a good option
<flux> ddosia, toplevel doesn't load executable code automatically
<flux> it will however find the list of available interfaces automatically from the given directories
<flux> and it will look inside the .cmi files to find what the interfaces are
<flux> but the actual values are not loaded
<ddosia> there is not bob.cmo file, only cmi, cmt, and other
<flux> oh, well maybe you can load .cmt
<flux> or maybe you should arrange it so that you have .cmo around
<flux> likely the only option
samuel02 has joined #ocaml
<Drup> rgrinberg: you don't want to rewrite it as an eliom overlay ? =')
<Drup> eliom-easy :p
<Drup> (the server part)
<ddosia> flux: ah I just compile to bytecode and now it is there
<rgrinberg> Drup: definitely not if my goal is portability...
<Drup> ?
ivan\ has joined #ocaml
<rgrinberg> well if I'm trying to get rid of all non ocaml dependencies. AFAIK eliom has quite a few
<companion_cube> rgrinberg: I heard Async.Pipe is nice, what is it exactly?
<Drup> rgrinberg: almost not anymore
<Drup> rgrinberg: the only non-ocaml dependency we have least is almost gone (it's ocamlnet)
<Drup> left*
<companion_cube> what's it used for?!
<Drup> some parser, and pcre :>
<Drup> and some various stuff
jao has quit [Ping timeout: 255 seconds]
<rgrinberg> Drup: once you guys switch to cohttp i will consider ok? :D
<Drup> it works, cumulus ran on it for a while
AlexRussia has joined #ocaml
pparkkin has joined #ocaml
<rgrinberg> companion_cube: Reading type is a pretty good way to learn for sure https://github.com/janestreet/async_kernel/blob/master/lib/pipe.ml#L183. also the header here: https://github.com/janestreet/async_kernel/blob/master/lib/pipe.mli#L1
<rgrinberg> If i had to compare to something in Lwt I would say its most similar to a bounded stream
<rgrinberg> Drup: how come it's not used by default then?
<Drup> a mix of lack of time and manpower ?
rz has quit [Quit: Ex-Chat]
<rgrinberg> ah, I misinterprted "it works"
<Drup> dinosaure finished it during is internship, but with multiple patches on cohttp/conduit
<Drup> his*
<rgrinberg> I think we did take his patches up
<rgrinberg> eventually
<Drup> yes, but later, and he was not in his internship in ocsigen anymore
<Drup> and nobody really got the time to review the whole thing
<Drup> it's tested (I used it in and cumulus used it) but not review :/
pparkkin has quit [Ping timeout: 255 seconds]
<rgrinberg> does it at least rebase cleanly on master?
<Drup> it's barely out of sync anyway ...
<rgrinberg> ah, oops. i read the ahead/behind commits in reverse
<rgrinberg> Drup: why don't you guys have nice readme's for github
<rgrinberg> :'(
<Drup> that's a very good question
<Drup> I did one when I started maintaining tyxml
<rgrinberg> also the ocsigen readme still mentions godi
<Drup> ahah :D
<rgrinberg> that's a crime in some states
<rgrinberg> :D
<Drup> patch welcome, I suppose
manud__ has quit [Quit: Be back later ...]
<Drup> rgrinberg: I'm not sure what should be put in the readme in fact, since we have already the various main pages for each projects
<rgrinberg> as a rule: 1) how to install 2) small snippet 3) how to run it
<Drup> might as well distribute links to the website and the tutorials
<Drup> putting code in that is a recipe for deprecated content. ;)
pparkkin has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 256 seconds]
<rgrinberg> :)
<flux> "All problems in computer science can be solved by adding more layers of indirection - except the problem of too many layers of indirection" (I don't remember who) ;)
<Drup> rgrinberg: I know, and I would do the same for most libraries that can be describes in a few word
rand000 has quit [Quit: leaving]
<rgrinberg> the example isn't there to describe or explain. It need not be explained at all. It's there to give flavor and show how you can quickly get started
samuel02 has quit [Remote host closed the connection]
<rgrinberg> btw you guys might want to break that contributors list across the different repos
testcocoon has quit [Ping timeout: 264 seconds]
<Drup> And it's not uptodate at all :(
AlexRussia has quit [Ping timeout: 240 seconds]
AlexRussia has joined #ocaml
sheijk has joined #ocaml
BitPuffin has quit [Ping timeout: 255 seconds]
Thooms has quit [Quit: WeeChat 1.0.1]
manud__ has joined #ocaml
manud__ has quit [Quit: Be back later ...]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]