<goltrpoat>
so ive been playing with F# (at the first glance, a .net-centric ocaml dialect), and, in particular, porting my old parser combinator library from haskell. now, i'm sure this isn't how it's usually done, but does ocaml have the concept of a monad in any form, and/or monad-style notation?
<goltrpoat>
(to make things more interesting, F# doesn't have functors, so i can't even implement monads if i wanted to)
<goltrpoat>
and on a different note, is there a way to define an infix operator? eg, a +++ b in (+++) : type -> type -> type
<Smerdyakov>
There is no concept of monad built into the OCaml language or in the standard library.
<Smerdyakov>
As for your second question, try let (+++) x y = x - y
<goltrpoat>
yeah that's how i defined it.. does it actually work as an infix expression though?
<goltrpoat>
oh duh. just the way i typed it
<goltrpoat>
was trying x (+++) y, heh
<goltrpoat>
thanks
ramenboy has joined #ocaml
<ramenboy>
if I create a GTree in lablgtk2, is it safe to modify its contents from multiple threads simultaneously, or do I need a mutex?
<dylan>
There is a camlp4 extension for monad syntax.
ramenboy has quit ["BitchX Lite I said!"]
ski has quit [Read error: 110 (Connection timed out)]
ski has joined #ocaml
mikeX has quit ["leaving"]
CosmicRay has joined #ocaml
<goltrpoat>
what's the list comprehension syntax in ocaml?
<dylan>
there isn't one.
<dylan>
But there is a camlp4 extension for it
<goltrpoat>
doh
CosmicRay has quit ["Client exiting"]
<Smerdyakov>
Most list comprehension patterns have trivial compilations to uses of functions in the OCaml standard library.
<dylan>
especially with a filter-map.
<goltrpoat>
yah, ends up with a bit more code in some cases though
dylan is now known as beetlejuice
<Smerdyakov>
Probably not more tokens... maybe more characters.
<goltrpoat>
eg let (>>=) (Parser p) f = Parser (fun input -> concat [Parser (f v) input' | (v, input') <- p input])
beetlejuice is now known as dylan
<dylan>
That was, um, well, ignore that.
<goltrpoat>
actually i guess that's an example of having neither monad syntax nor list comprehensions
<Smerdyakov>
goltrpoat, then what was that | character?
<goltrpoat>
sorry.. haskellish pseudo-syntax there
<Smerdyakov>
goltrpoat, it wasn't a list comprehension?
<goltrpoat>
it was
<goltrpoat>
p input is a list [(a,b)], the list comprehension picks tuples (v, input') out of that, and the left hand side of the comprehension does stuff to it
<goltrpoat>
i can write it with a map and something to simulate <- i guess
<dylan>
However, if we were writing the Ast, we'd be writing scheme. :)
<goltrpoat>
hehe
<Smerdyakov>
Even better, use a mapConcat function and get a simpler AST.
<dylan>
list comprehensions are a pain in the ast?
<dylan>
list comprehensions make more sense in haskell because they're related to the monads.
<goltrpoat>
well, lists are monads in haskell
<dylan>
fascinating.
<Smerdyakov>
goltrpoat, I don't like that way of saying it. An algebraic structure that includes lists as one element is a monad.
<Smerdyakov>
You need to specify the monad operations, not just the type.
<Smerdyakov>
And maybe there are other monads over lists.
<goltrpoat>
dylan: Prelude Monad> liftM (*5) [1,2,3] gives [5,10,15], etc.
<goltrpoat>
smerdyakov: not sure i follow
<goltrpoat>
a monad is not "an algebraic structure that includes lists as one element"
<Smerdyakov>
goltrpoat, right, but "the list monad" is.
<goltrpoat>
i'm saying that the list type in haskell is an instance of a monad
<Smerdyakov>
goltrpoat, and I'm saying that that isn't true, as far as I'm concerned.
<goltrpoat>
with the corresponding operations defined
<goltrpoat>
it's a monad with plus and zero
<Smerdyakov>
goltrpoat, a tuple of list and the monad operations is a monad.
<goltrpoat>
yes
<Smerdyakov>
goltrpoat, but the list type constructor by itself is not a monad.
<goltrpoat>
i didn't say apples are the only fruit there is, i said apples are an instance of fruit :)
<dylan>
fruit, monads, operations...
* dylan
giggles.
<Smerdyakov>
goltrpoat, it's like it's improper to say that "permutations form a group" without specifying what group operations you mean.
<goltrpoat>
maybe the disconnect is in the fact that i'm saying that haskell lists are an instance of the haskell monad type, with the associated operations defined by the list type. not that lists are monads in and out of themselves, without specifying those operations.
<Smerdyakov>
Right. You should have said instead "Haskell defines a monad that uses lists."
<goltrpoat>
im just using "is a" to mean an instance of that type class
<goltrpoat>
anyway.. semantics
bohanlon has joined #ocaml
<Smerdyakov>
Is an instance of that type class in the default instance context... ;)
<goltrpoat>
it's an instance of that type class in the context of Data.List having the line "instance Monad [] where {- stuff -}" hanging around somewhere :)
<psnively>
Hashtbl.add factories "alpha" {construction_function = fun () -> "foo"}
<psnively>
Gives me
<psnively>
This field value has type unit -> string which is less general than
<psnively>
'a. unit -> 'a
<Smerdyakov>
It's unusual to use OCaml's OO features.
<Smerdyakov>
What made you choose to use them?
<psnively>
The file format models an archive of objects, including inheritance. To have a parallel structure in O'Caml seemed intuitively reasonable.
<psnively>
I have no control over the file format.
<Smerdyakov>
That really depends on the format details and what you plan to use the data for.
<psnively>
However, the thought has occurred to me that employing polymorphic variants, along the lines of "Code Reuse Through Polymorphic Variants," might ultimate prove easier.
<Smerdyakov>
Polymorphic variants are crap. :P
<psnively>
Quite right. I'm attempting to develop an editor, ultimately, for this file format.
<psnively>
So in the end, I just need the data for each object in an identifiable way, and such that I can change the values and eventually write them back correctly with respect to the format.
<psnively>
Hmm. I quite like polymorphic variants.
<Smerdyakov>
Why not use regular variants?
<psnively>
Because it's needlessly difficult to remain open with regular variants.
<psnively>
Hence "Code Reuse Through Polymorphic Variants." :-)
<Smerdyakov>
Are you sure that it makes sense to map a pre-existing object hierarchy to types?
<psnively>
Am I sure? No, but it certainly would make life easier for the poor programmer!
<psnively>
It seems to me that it shouldn't be this hard to come up with a function that returns an object of a certain class or a subtype of that class.
<Smerdyakov>
Maybe. Clearly if all you want to do is read objects and then write them back out, bit arrays are an excellent representation; it all depends on your goals.
<psnively>
I believe I indicated that I needed to be able to change the objects meaningfully. :-)
<Smerdyakov>
Just think of reading a fle with English text. Someone could come along and say that this is naturally represented as OO objects customized to English grammar, but in fact it's usually most sensible just to treat them as strings.
<psnively>
Part of the problem is that there actually isn't one file format; there are N file formats, all related to each other (because the objects are related, but different).
<psnively>
Right. But if you need to be able to change the English sentences and have them remain English sentences...
<Smerdyakov>
Can you give a pared-down example that expresses the essence of your file format(s) and the operations you need to do?
<psnively>
Again, I'm attempting to develop an editor for these objects (and their subclasses, and their subclasses' subclasses, ad infinitum).
<psnively>
It's very hard to describe; the format is rather complex.
<psnively>
But again, it doesn't seem like it should matter, and in fact serializing the objects in and out isn't the problem. Constructing them polymorphically (that is, having one function that returns the right type given input X) is.
<Smerdyakov>
I'm trying to understand why an essentially dynamically typed representation isn't the right idea.
<psnively>
But again, this may be the perfect application for polymorphic variants.
<psnively>
Um, if I wanted that, I'd not be working in O'Caml. Besides, we're talking about hundreds of different classes per archive type, and there are (today, more in the future) dozens of archive types that have to be kept distinct. I'd like the type system's help with that. :-)
<psnively>
I mean, if C++ is the right tool for the job, OK, but I have a tough time believing that relative to O'Caml.
<Smerdyakov>
OK. Just don't expect me to take your word for it without more detail. :)
<psnively>
Now it just has Delphi sources for reading/writing them (which is cool, but not as helpful to me).
<psnively>
So the detail I can offer is that I'm trying to read/write:
<psnively>
Unreal
<psnively>
Unreal Tournament
<psnively>
UT2003
<psnively>
UT2004
<psnively>
Deus Ex
<psnively>
Rune
<psnively>
Eventually, UT2007
<psnively>
Gears of War
<psnively>
etc. etc. etc.
<psnively>
"packages," which contain serialized objects.
<Smerdyakov>
Well, back to your original question, I didn't even know it was legal to have "'a. unit -> 'a" inside a record type.
<Smerdyakov>
Clearly (fun () -> "foo") doesn't have that type.
<Smerdyakov>
So I'm not sure why you expected that to type-check.
<psnively>
Right. So in some sense, I got the polymorphism wrong. I can store a polymorphic function in a record; I can't say that a record can contain functions of many different types.
<psnively>
Hey, it's an experiment.
<Smerdyakov>
Do you understand why that function doesn't have that type?
<psnively>
Certainly.
<Smerdyakov>
Why don't you just use the parent class type as the result of construction?
<psnively>
Because the parent class type is unknown.
<Smerdyakov>
How can you expect to use the result, then?
<psnively>
Hmmm. Is there some way that I can parameterize both a function definition and a class definition simultaneously, with the constraint that the type variables are equal?
<psnively>
Well, of course, the parent class type is known by the time the constructor is actually invoked.
<Smerdyakov>
You can parameterize both in the usual way and use the same type variable for two uses in some context..
<psnively>
So:
<psnively>
Actually, I think I tried that and it didn't work either...
<Smerdyakov>
I'm still struggling to understand at a basic level what it is you are doing.
<Smerdyakov>
Could you please write a small example capturing the essence of your problem?
<Smerdyakov>
Just writing out the types of the values you want to produce would be very illuminating, I think.
<psnively>
class ['uobject] archive = object method load : string -> 'uobject end
<psnively>
That is, an archive is parameterized by the (base) class of objects it contains.
<Smerdyakov>
OK
<psnively>
I need a method, call it "load," that, given a name (string), returns a 'uobject of the appropriate (sub)class.
<Smerdyakov>
Can you write out the type of the value you want?
<psnively>
Who cares? I mean, sure: class base = object end :-)
<Smerdyakov>
So are you saying that you don't know how to write the 'load' method?
<psnively>
Correct.
<Smerdyakov>
Is 'archive' a single concrete class or an abstract class that will have an implementation for each 'uobject type?
<psnively>
The name parameter can name an object of any class in the hierarchy. Hence the difficulty.
<Smerdyakov>
Alternatively, why not make it a class type instead of a class and use abstract classes?
<ketty>
so, the return type is dependant on what string you give to the method?
<psnively>
Well, I wouldn't call it abstract. A single archive contains M objects of N different classes, but the classes have a hierarchical structure.
<ketty>
like printf??
<psnively>
ketty: in essence, yes.
<Smerdyakov>
psnively, then you are out of luck with OCaml's type system.
<ketty>
forget it :)
<psnively>
Use abstract classes for what?
<Smerdyakov>
psnively, each 'uobject type has its own archive class.
<psnively>
Oh pish-posh. Printf exists, marshal/unmarshal exist. Don't be ridiculus.
<psnively>
Ridiculous, even.
<Smerdyakov>
psnively, both are implemented with special language support or C code.
<psnively>
Printf isn't done in C, that much I know.
<psnively>
Not sure about marshal/unmarshal.
<Smerdyakov>
Right. Printf format strings are built into OCaml.
<ketty>
supposedly printf uses Obj.magic
<Smerdyakov>
ketty, type-checking uses special language support.
<psnively>
Really? There's a very nice general dump/print function in ExtLib that doesn't even use Obj.magic (it does use Obj.obj and Obj.repr).
<Smerdyakov>
psnively, oh, so you don't mind if your implementation is not provably type-safe?
<Smerdyakov>
(by the compiler)
<psnively>
I already know I'll need Obj.obj and Obj.repr for the object manipulation stuff.
<psnively>
Actually, Obj.obj and Obj.repr are completely safe. Obj.magic, not.
<psnively>
But of course, you can't do "provably type-safe" file I/O anyway.
<Smerdyakov>
Sure you can.... OCaml just doesn't provide support for it. :)
<psnively>
"Provably type-safe I/O" over a format you don't control isn't even a coherent concept.
<Smerdyakov>
Right. You have to control it. :)
<psnively>
Sure, then you just tag the data that goes outside the runtime. See Acute, HashCaml...
<Smerdyakov>
Why don't you give archive a constructor that takes an unmarshalling function as an argument?
<Smerdyakov>
And marshalling for the real thing, but your example just does 'load.'
<psnively>
Well, it's have to take N unmarshaling functions, wouldn't it? One for each class that I need to marshal/unmarshal?
<Smerdyakov>
Isn't any object of class 'archive' specialized to one object format?
<psnively>
One BASE type.
<Smerdyakov>
A base type and all its subclasses don't have a single data format, with tags to indicate which you're getting?
<psnively>
Nope.
<Smerdyakov>
How odd. I've never heard of something like that before./
<psnively>
That would be C++. :-)
<psnively>
C++ doesn't tag its data. Typically in C++, you overload operator>> and operator<< and just call the underlying operator on your data members, in order.
<Smerdyakov>
Can you explain when and why the 'load' method is used?
<psnively>
The assumption being that you know what your position in the stream is when you do so, so it's safe. And it actually works fine, once you know you're dealing with the right stream type.
<psnively>
What's so hard about this? I need to say "there's an object of class X or one of its subclasses in this archive. It's named 'foo'. Please give it to me."
<Smerdyakov>
How is this possible if what class object you will get is not computable from the file? If it _is_ computable, then what you have is effectively a _single_ format for a class and all its subclasses.
<psnively>
This whole conversation would be a good argument in favor of dynamically-typed languages, but C++ isn't a dynamically-typed language...
<psnively>
Oh, it is computable from the file, in the sense that the object name will take me to data that indicates, among other things, the class of the object.
<Smerdyakov>
OK, so there is a single format for a class and all its subclasses, and you don't need N 'load' procedures.
<psnively>
So of course I can determine the class of the object at runtime. But that just leads to my question.
<psnively>
No, there isn't a single format for a class and all its subclasses.
<Smerdyakov>
Sure there is.
<Smerdyakov>
We have a mapping format from classes to representations.
<psnively>
How could there be? The subclasses have more data than the base class (which, ultimately, has none, actually).
<Smerdyakov>
The representation for class C and all its subclasses is:
<Smerdyakov>
(name of subclass C', format(C'))
<psnively>
format(C') is not provided in the archive.
<psnively>
It is assumed (of course, because it's known statically by the code that wrote the archive in the first place).
<Smerdyakov>
I'm not saying that the format schema is the second element of the tuple representation.
<Smerdyakov>
I'm saying that a value of that format is the second element.
<psnively>
OK, then how does this help? :-)
<Smerdyakov>
It shows how you have a single representation for a class and all its subclasses.
<Smerdyakov>
The representation includes a tag telling you which subclass it is.
<Smerdyakov>
So you can write a complete and correct unmarshalling function that handles all subclasses of a class.
<psnively>
OK, I think I see what you mean.
<Smerdyakov>
It's type is simply 'unit -> baseClass'
<Smerdyakov>
'string -> baseClass', I mean.
<psnively>
Unfortunately, that won't work because O'Caml doesn't do downcasts.
<Smerdyakov>
There are tricks using exceptions to do downcasts.
<psnively>
OK, I'm listening.
<Smerdyakov>
But a desire to do downcasts shows poor OO design, anyway. :P
<Smerdyakov>
I don't remember the tricks. I never use OCaml OO.
<Smerdyakov>
I think you have to define an exception that takes the subclass as an argument.
<Smerdyakov>
The real subclass has a method that throws that exception.
<Smerdyakov>
The other subclasses throw Failure.
<psnively>
Hmmm.
<Smerdyakov>
But, again, it is a sign that you screwed up somewhere if you want downcasts.
<Smerdyakov>
I'd probably use regular variants for solving this problem myself.
<psnively>
Forgive me, but there's nothing whatsoever wrong with wanting to go from a type to a subtype.
<psnively>
And in fact, that's one thing that polymorphic variants are really good at. :-)
<psnively>
If I only had to deal with one archive type (that is, a fixed set of object types contained in it), regular variants would be perfect.
<Smerdyakov>
There's something wrong with any operation whose possibility for runtime failure isn't ruled out by the compiler.
<Smerdyakov>
In your concrete case, is the problem that anyone can invent his own new object types, and your code needs to be able to handle them all?
<psnively>
Right. I'm saying that by runtime, all the types involved are known, and I'm just asking for what amounts to a selection function that returns a value of a known type (by runtime), but that type is (obviously) not known at compile time because it depends upon the parameter to the function.
<psnively>
Yep.
<Smerdyakov>
But surely your code can only have fundamentally different handling of a finite set of classes.
<Smerdyakov>
You can put the rest in a constructor "I didn't know what this is."
<psnively>
Certainly. The caller can pass a name of an object that doesn't exist in the archive.
<Smerdyakov>
I'm talking about an archive-independent issue.
<Smerdyakov>
You choose which classes to support and give the rest default handling.
<psnively>
Obviously, I have to.
<Smerdyakov>
I don't believe this leads to any functionality problems.
<Smerdyakov>
And so regular variants are ideal.
<psnively>
Hmmm, no, regular variants aren't open.
<Smerdyakov>
You have one constructor used for all unknown classes.
<psnively>
But what happens when a class becomes known?
<Smerdyakov>
You add a constructor for it.
<psnively>
Ah. Right. No, it's not OK to have to recompile the code to handle new cases.
<psnively>
You really should read "Code Reuse Through Polymorphic Variants." :-)
<Smerdyakov>
What kind of "handling" can you achieve without recompiling the code?
<psnively>
Arbitrary, if you also use open recursion. Really, read the paper.
<Smerdyakov>
Before I do, can you describe a particular example of a new class and how you manage to handle it without any new compilation?
<psnively>
You mean using the OO features, or polymorphic variants?
<psnively>
Oh! I think I got it! Thank you!
<psnively>
Geez, I'm a moron.
<psnively>
OK, let's try this. You're probably familiar with the subject/observer pattern?
<Smerdyakov>
Not really. Can you first describe the new class and the end-user-visible functionality associated with it?
<psnively>
Well, let's use this as a simple conceptual case. Let's say I want a class that does stuff, and maintains a list of observers to notify when it does this stuff.
<Smerdyakov>
OK.
<psnively>
But both my subject class and my observer class need to remain extensible.
<psnively>
In fact, I'd like subclasses of my subject class to be able to call different methods on the observer (sub)class than the base class does, but the base class can keep calling the methods it does.
<Smerdyakov>
How are you going to add subclasses without running the compiler?
<psnively>
I'm not. Bear with me.
<psnively>
class ['S] observer = object end
<psnively>
The only requirement is that they be separately compilable, sorry.
<psnively>
OK, here's how we can use these classes I just made, as an example.
<psnively>
class ['O] window =
<psnively>
object (self)
<Smerdyakov>
OK, now you've said the crucial fact! I think you can stop the example, at least for my sake.
<psnively>
inherit '[O] subject
<psnively>
LOL
<psnively>
OK
<Smerdyakov>
Why do you care about separate compilation for your concrete program?
<Smerdyakov>
Especially when program-shaking changes will happen very rarely (with the introduction of new classes)?
<psnively>
That actually won't be that rare. Multiple new Unreal-technology titles ship per year.
<Smerdyakov>
"Once a day" is rare from my perspective.
<psnively>
Heh. OK
<Smerdyakov>
Given how quickly the OCaml compiler runs.
<psnively>
In any case, I think I was being too doctrinaire about having a hashtable of functions to construct the objects. I can have an object that is a factory for the objects.
<psnively>
There will probably be other thorns, but I think I can work them out.
<Smerdyakov>
I think you should reconsider your separate compilation requirement, since it interferes with effective static checking in this case.
<psnively>
But it doesn't; that's the great thing about it.
<Smerdyakov>
Seeing as how you haven't been able to express what you're trying to do yet in an open way that the compiler likes... ;)
<psnively>
Well, then let me finish the example, or better yet, also read "On the (un)reality of virtual types."
<Smerdyakov>
And I would argue that closed datatypes inherently allow more static checking than open types.
<Smerdyakov>
So closed types are always better when circumstances allow.
<psnively>
I can't help that the file format in question contains serialized C++ objects. :-)
<psnively>
"We show, mostly through detailed examples, that object-oriented programming patterns known to involve the notion of virtual types can be implemented directly and concisely using parametric polymorphism. A significant improvement we make over previous approaches is to allow related classes to be defined independently. This solution is more flexible, more general, and we believe, simpler than other type-safe solutions previously pro
<psnively>
"Allow related classes to be defined independently... more flexible, more general... simpler than OTHER type-safe solutions..."
<psnively>
OK, I will continue to study. :-)
<psnively>
Hmmm. The cow/animal example in "On the (un)reality of virtual types" is probably significant somehow. I must think.
ketty has quit ["Leaving."]
psnively has quit []
finelemon has joined #ocaml
finelemo2 has joined #ocaml
finelemo1 has quit [Read error: 110 (Connection timed out)]
finelemon has quit [Read error: 110 (Connection timed out)]
ketty has joined #ocaml
<jer>
there a faq i can read that explains the rational behind multiple addition, subtraction, etc operators for ints and floats (that is, why it was decided they couldn't just be polymorphic)
Thorn has joined #ocaml
<Thorn>
hello
<jer>
Thorn, hi
<Smerdyakov>
jer, why did you mention arithmetic operators just now?
Schmurtz has joined #ocaml
<jer>
Smerdyakov, i'm bored, and havn't read anything that explained the rationale behind that decision; so i just asked
<Smerdyakov>
jer, as far as I can see, you didn't ask a question.
<jer>
oops, i forgot an "is" infront of my statement, my fault
<Smerdyakov>
jer, a question mark would help, too.
<jer>
visualize those two thingsi n there then
<Smerdyakov>
Just think about what type, say, the plus operator would have.
<Smerdyakov>
The type system would need an extension to make that expressible.
<jer>
well i was just thinking a way to handle it would be to check the top of the lvalue against the type of the rvalue; if they don't match, throw an error. that is, don't try and perform any automatic conversion like other operating systems, i don't see you losing anything here. which is why i was curious
<jer>
s/top of/type of/
<ketty>
jer, i suggest you look up how sml do it. and we'll see if you still think it is a good idea ;)
* jer
was hoping not to have to go on a wild goose chase to find my answer, but ok
* ketty
is gone watching anime ^^
<Smerdyakov>
jer, I asked you about what type you would give the plus operator. How does what you said answer that?
<Smerdyakov>
jer, in OCaml, infix operators are just regular old functions. They need to be given types that express completely how to check validity of uses. You can't just throw in special rules for some operators without going against the ML philosophy.
<jer>
Smerdyakov, you know what; that's fine.. i'm not asking this question to troll or otherwise incite people into thinking i'm taking a short at the language. i'm *GENUINELY CURIOUS*. And I'mm sorry if my 15 years imperative programming has made adapting to FP a little slow and coming, and ML in particular; but for god sakes man, lighten up.
<jer>
Smerdyakov, you want a type definition, i cannot give you one
<Smerdyakov>
jer, you've misread me if you think a call to "lighten up" is appropriate.
<jer>
perhaps i did, but oyu're coming off as a prick
<Smerdyakov>
I'm answering your question.
<Smerdyakov>
Rather, I _have_ answered your question. I don't think there's anything more to it.
<pango>
jer: actually, if you want to see what it would look like, you can give gcaml a try
<jer>
pango, thank you, i will
<pango>
(in fact gcaml does more than that, because it tries to give general adhoc polymorphism, not just for arithmetic operators)
Snark has quit ["Leaving"]
mikeX has joined #ocaml
goltrpoat has joined #ocaml
<goltrpoat>
slightly confused.. i'm getting the following error: error: FS0034: Module 'Parser' contains val ( >>= ) : 'a Parser -> ('a -> pstring -> ('b * pstring) list) -> 'b Parser, but its signature specifies val ( >>= ) : 'a Parser -> ('a -> 'b Parser) -> 'b Parser
<goltrpoat>
but Parser is Parser of (pstring -> ('a * pstring) list)
<goltrpoat>
shouldn't that typecheck?
Schmurtz has quit [Read error: 113 (No route to host)]
<goltrpoat>
i.e. it seems like it can't match pstring -> ('b * pstring) list to Parser
<goltrpoat>
but that's exactly what Parser looks like
<goltrpoat>
or does it just want the type constructor explicitely
<goltrpoat>
nevermind, fixed it. it was the other way around, i had an extraneous type constructor
wimp has joined #ocaml
jcreigh has joined #ocaml
wimp has quit [Client Quit]
wimp has joined #ocaml
wimp has quit [Client Quit]
wimp has joined #ocaml
CosmicRay has joined #ocaml
wimp has quit ["Leaving"]
jcreigh has quit [Read error: 110 (Connection timed out)]
cmeme has quit [Connection timed out]
smimou has quit ["bli"]
goltrpoat has quit [Read error: 110 (Connection timed out)]