flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
alexyk_ has quit [Read error: 110 (Connection timed out)]
<alexyk> can I redefine [] for my type?
<alexyk> meaning, s.[i]
<mfp> wtf "and 10x as many libraries on hackage.haskell.org than on the ocaml hump."
<mfp> I did a textual search for "hump" and found 634 projects
<mfp> never knew there were that many
<mfp> (vs. 1091 on hackage)
<alexyk> mfp: are you relaying haskell gossip? :)
<mfp> I found it very surprising that there were >600 projects on the Hump
<alexyk> in binary 1100 ~ 600*2...
<mfp> even though the site sucks so badly
<Yoric[DT]> alexyk: you can't but you can probably do something quite similar with pa-do
<Yoric[DT]> Still, time to call it a night.
mjonsson has joined #ocaml
<Yoric[DT]> Cheers everyone.
<mfp> doesn't mirror the tarballs, presents little metadata, etc.
<Yoric[DT]> And a happy new year.
<mfp> night Yoric[DT]
Yoric[DT] has quit ["Ex-Chat"]
<alexyk> I am trying to generalise Sébastien Ferre's suffix trees from strings to general sequences over an alphabet
<alexyk> he uses s.[i] and I hate to rewrite it all as A.get s i
<alexyk> but looks like have to
<alexyk> Happy New Year too! :)
<mfp> alexyk: also surprising because this looks like dons FUDing and I wouldn't expect him to steep so low, so I wonder what stats he's using
<mfp> alexyk: .[x] is expanded to Array.get
<mfp> so put module Array = struct let get t i = .... end before the code with the []
<mfp> and it'll be using your function
<mfp> (unless compiling with -unsafe, which might use unsafe_get, haven't tried it)
<alexyk> mfp: interesting... but if it were using a real Array, I'd be screwed, right?
<mfp> you cannot have two defs active at the same time
<mfp> since no ad-hoc polymorphism
<alexyk> mfp: oh well, better rewrite it
<mfp> so yes, either array or the new func
<mfp> (as with any other function)
<mfp> you could also use "open in"
<alexyk> I also forgot, can I define one append to concat a string and a chat, and another append to concat two strings? Do we have overloading in ocaml?
<mfp> or the manual expansion of it if you don't feel like using the syntax extension
<alexyk> chat=>char
<mfp> nope
<alexyk> arrgh
<mfp> no ad-hoc polymorphism
<alexyk> mfp: does Haskell have it? :)
<mfp> the std. solution is to functorize over some String module or use different functions/operators
<mfp> yes, typeclasses
<alexyk> mfp: right
<mfp> this is funny if you want to trick somebody into believing OCaml has got eval:
<mfp> module Array = struct let get n x = print_endline x end;;
<mfp> ("print_endline").("foo");;
<alexyk> wow
<mfp> in fact, "print_endline".("foo") would do
<alexyk> mfp: I guess one can have an append for both a char and a string by using labeled parameters...
<alexyk> optional
<alexyk> although it's not pretty, but we do know what we supply
<mfp> maybe, but that sounds clunky
<mfp> how is it better than having two functions?
<alexyk> well Ada had overloading in 1983, so I don't feel very pleased I have to make up names
sheijk has joined #ocaml
<alexyk> mfp: prolly not better at all
<mfp> seems such a func cannot be applied without a label anyway
<mfp> s/a label/labels/
<mfp> so it doesn't save any typing over e.g. (^) and (^!)
Camarade_Tux has quit ["Leaving"]
<alexyk> mfp: true
<alexyk> I wonder if even typeclasses can allow to have string->char->string and string->string->string both called append
<alexyk> and same with left char
<sheijk> "- All compiler error messages now include a file name and location, for better interaction with Emacs' compilation mode.
ofaurax has quit ["Leaving"]
<sheijk> " what does that mean, are filenames+linenumbers now in the same line as the error message? (in 3.11 release notes)
<mfp> sheijk: I'm getting location & error message on separate lines with 3.11 (for a trivial syntax error)
<sheijk> hm, k. no happy flymake, yet :)
<mfp> I guess the key word is "all"
<sheijk> does 3.11 break any libraries?
<mfp> i.e., the location not being shown for some errors in <= 3.11 ?
<mfp> a few camlp4 things
<mfp> and some (O)Makefiles: you now have to link against dynlink.cma when using camlp4lib.cma
<mfp> other than that, there are no backwards-incompat modifications listed in Changes
<sheijk> hm, sounds like it's not too dangerous to upgrade :)
<mfp> note that the "camlp4 things" includes typeconv and thus sexplib
<sheijk> i don't use any camlp4 stuff
<mfp> the fix was like 3 lines in typeconv where you had to do <:ctyp< ? >> -> <:ctyp< >> anyway
<alexyk> why is syntax fir module specs different for parameterized vs plain? module type A = sig .. end
<alexyk> module A (B: PARAM) : sig .. end
<alexyk> why = becomes : ??
<alexyk> (am just grokking functors again...)
<alexyk> why is this a syntax error on ;; :
<alexyk> module VISIBLE (A: ALPHABET) : sig val get_visible : A.s -> int * int end;;
<sheijk> mfp: ah, nice. i'd be much more interested in getting otags back, though :)
<sheijk> alexyk: a type is/equals the sig..end part while a concrete module _has_ the type specified by sig..end
<sheijk> like type foo = int and let x : int = 10
<mfp> alexyk: are you typing that on the toplevel? That's an interface...
<alexyk> mfp: ah, so I can't enter interfaces into toplevel?
<mfp> you can do module type X = sig val foo : int end;;
<alexyk> I get syntax error right after that end with ocamlc too
<mfp> works for me
<mfp> did you type exactly that, including "type"?
<alexyk> and I'm copying module NAME (X: PARAM) : sig val f: sometype->othertype end;; from a working French original! :)
<mfp> alexyk: what I'm saying is that that code belongs to a .mli
<mfp> right
<alexyk> mfp: ah, so I can't compile that by placing it in ml?
<mfp> .mli.html
<alexyk> has to separate into mli?
<mfp> it doesn't make sense in that context
<mfp> yes, the interface is specified in the mli
<alexyk> I now have to parameterize a module type with a parameter, = sig becomes : sig
<mfp> what you can do in the .ml, OTOH, is module NAME (X : PARAM) : sig val .... end = struct .... end
<alexyk> and I have to cut it into .mli! Hmm
<alexyk> mfp: I define a parameterizable parameter, it should be left abstract and defined by users
<alexyk> so .mli then
<sheijk> alexyk: you have to provide the definition unless you write a .mli file
<sheijk> "module FOO : sig .. end" does not work because the definition of the module is lacking
<alexyk> well the original contained just a signature in the .ml: http://www.irisa.fr/LIS/ferre/libocaml/suffix_tree.ml
<alexyk> see PARAM
<alexyk> I'm trying to parameterize the string there by A.s
<alexyk> Ferre has:
<alexyk> module type PARAM =
<alexyk> sig
<alexyk> val get_visible : string -> int * int
<alexyk> (** [get_visible s] returns the sizes of the prefix and suffix of [s]
<alexyk> that can be removed from [s] without damage to its meaning. *)
<alexyk> end
<alexyk> I need to basically add PARAM(A: ALPHABET) and replace string by A.s
<alexyk> yet I can't keep = sig, ocamlc complains
<alexyk> and : sig causes a complaint after end
<alexyk> why do I get an error on = sig in:
<alexyk> module VISIBLE (A: ALPHABET) = sig
<alexyk> val get_visible : A.s -> int * int
<alexyk> end
<alexyk> ?
<alexyk> and I can't do module type VISIBLE either...
<sheijk> alexyk: module != module type
jli has left #ocaml []
<mfp> alexyk: this might help... module type A = functor (X : sig end) -> sig end;;
<alexyk> mfp: ok, am trying...
<alexyk> mfp: yay! thx! the well-cooked result:
<alexyk> module type VISIBLE = functor (A: ALPHABET) -> sig
<alexyk> val get_visible : A.s -> int * int
<alexyk> end
mjonsson has quit [Read error: 110 (Connection timed out)]
fschwidom has quit [Remote closed the connection]
munificent has joined #ocaml
Morphous has quit [Read error: 104 (Connection reset by peer)]
<alexyk> if I have module PARAM, module A(P: PARAM) using module B(P: PARAM), so I have to give B to A in addition to PARAM, or can I somehow instantiate B inside of A?
ikaros has quit [".quit"]
<mfp> alexyk: I think you're going to need the "with operator" -> http://caml.inria.fr/pub/docs/manual-ocaml/manual018.html#toc64 /me going zzzZZ now
Morphous has joined #ocaml
munificent has quit [kornbluth.freenode.net irc.freenode.net]
mrvn has quit [kornbluth.freenode.net irc.freenode.net]
tsuyoshi has quit [kornbluth.freenode.net irc.freenode.net]
mrvn has joined #ocaml
munificent has joined #ocaml
tsuyoshi has joined #ocaml
jeddhaberstro has joined #ocaml
slash_ has quit [Client Quit]
jlouis has quit [Remote closed the connection]
<alexyk> how do you access the largest int value?
jeddhaberstro has quit []
<alexyk> how do you define a functor signature and body separately?
mjonsson has joined #ocaml
sporkmonger has joined #ocaml
alexyk has quit []
johnnowak has left #ocaml []
alexyk has joined #ocaml
<hcarty> alexyk: max_int
<alexyk> hcarty: thx! also -- can I define a signature and the body both parameterized by the same module?
sheijk has quit ["n8"]
<hcarty> alexyk: That I'm not sure of... I have worked with functors a bit, but I have never tried to do that
sporkmonger has quit []
alexyk has quit []
alexyk has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
munificent_ has joined #ocaml
munificent has quit [Read error: 104 (Connection reset by peer)]
seafood_ has quit []
seafood has joined #ocaml
det has quit [Read error: 131 (Connection reset by peer)]
det has joined #ocaml
johnnowak has joined #ocaml
proqesi has joined #ocaml
<proqesi> can anyone recommend a good article or book on strict functional programming (only) with ocaml?
<gildor> I started with this book
<gildor> it is quite old but most of what is inside should be ok
<gildor> (but it is more general purpose than "strict" functional programming)
<mrvn> It is not like anything has changed much that needs a newer book.
<gildor> mrvn: BTW you don't have yet commited libaio code to the forge
<gildor> mrvn: have you any problem doing so ?
<gildor> (must admit that I am looking to your lib, because I will probably try it some day)
seafood has quit []
<mrvn> gildor: no. just no time to tidy up the code for commitment yet
munificent_ has quit []
Camarade_Tux has joined #ocaml
proqesi has quit [Connection timed out]
vixey has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
_zack has joined #ocaml
<gildor> Yoric[DT]: hi
<Yoric[DT]> Hi, Happy New Year.
<gildor> you too
<gildor> hope this year will see the beginning of "OCaml everywhere" ;-)
<Yoric[DT]> :)
<gildor> Yoric[DT]: you are good at haskell AFAIK
<Yoric[DT]> Not really.
<gildor> can you recommend me a book for learning Haskell (for a OCaml programmer)
Yoric_ has joined #ocaml
Yoric_ has left #ocaml []
<Yoric[DT]> I've read Real-World Haskell and I liked it very much.
bohanlon has quit [kornbluth.freenode.net irc.freenode.net]
Jedai has quit [kornbluth.freenode.net irc.freenode.net]
cygnus_ has quit [kornbluth.freenode.net irc.freenode.net]
haelix has quit [kornbluth.freenode.net irc.freenode.net]
gaja has quit [kornbluth.freenode.net irc.freenode.net]
<gildor> one of the author is John Goerzen
gaja has joined #ocaml
bohanlon has joined #ocaml
Jedai has joined #ocaml
haelix has joined #ocaml
cygnus_ has joined #ocaml
<gildor> he is also Debian Developer
<Yoric[DT]> Good sign :)
<mfp> does anybody know where to find stats about the Hump?
<mfp> dons' claim on reddit that there are 10x as many libs on Hackage as on the Hump troubled me a bit --- either it's true, or he's FUDing; both would be upsetting
<Yoric[DT]> :/
<mfp> I did a textual search for "hump" (seems to match all projects, with no repeats) and found >630 hits, but it's a very indirect way and real stats would be nice
<mfp> (Hackage has got 1090 packages)
<olegfink> hump seems to have 680 if I understand its update system correctly
<olegfink> or rather, it has 680 contrib IDs
<mfp> the thing Hackage is for sure much better at is giving publicity to projects and creating linkable pages that can be submitted to reddit :P
<mfp> I also see some effort to boost the package count artificially; I mean, regex-base, regex-compat, regex-dfa, regex-parsec, regex-pcre, regex-pcre-builtin, regex-posix, regex-tdfa, regex-tre --- by that criterion, ocamlnet would be split into 100 packages :P
<flux> unfortunately not all packages in hump are up to date - especially considering the situation with camlp4
<flux> there is no centralized location that would try to compile 'all packages' for ocaml whenever a dependant package (or compiler) gets updated
<flux> I don't know if that's the case with hackage either, though
<mfp> you can rebuild all the stuff on hackage using cabal
<flux> but is it being done is another matter?
<mfp> IIRC around 60-70% builds correctly
<mfp> dons does it every once in a while & posts the results to haskell-cafe & other fora
<mfp> hmm
<mfp> I'm thinking that there are 2 factors that contribute to Haskell packages being split into more pieces (as opposed to OCaml's, which tend to be much larger, like ocamlnet)
<mfp> (1) cabal makes it easy to release & install stuff for devels (not so much for end users, since getting cabal-install itself to work is not that easy, but those are not the ones who release things)
<mfp> (2) the "open hierarchy", allowing you to place your modules under Data.Whatever and such
<flux> it would be nice if godi played well with distribution-installed compilers/packages, but I don't think we'll be seeing that
<flux> considering point 2, I think it is more a documentation issue than actual module hierarchy issue
<flux> perhaps there should be an additional field "category" in the META file, which would give a hierarchical view, even if the module names themselves aren't hierarchical
<mfp> Yoric[DT]: never got any feedback about the idea of separating modules from namespaces, right?
<flux> (I was persuaded to that documentation pov by the caml-list traffic)
<flux> in reality deep hierarchies can get boring fast, because you need to either open them (bad, because you can get collisions and it's more difficult to see where a symbol originates from) or you have an alias for them (bad because each module might have different aliases for same symbols)
<flux> IMHO, of course :-)
<mfp> anything beyond 2-3 levels is clearly excessive
<flux> also the packing approach doesn't currently work decently in ocaml for hierarchical purposes, because a) the construction of the pack is centralized and b) when you link in a .cmo, you get everything, compared to a .cma where you get only those .cmo's you actually use
<flux> b has the potential to result in greatly bloated executables, if the library size increases, and you only use it for 'hello world'
<gildor> mfp: BTW, i have made some change to ocaml-autobuild (in particular OASIS parser)
<Yoric[DT]> mfp: not much feedback, no.
ikaros has joined #ocaml
fschwidom has joined #ocaml
<gildor> Yoric[DT]: I like your last proposal with a flatter namespace
hkBst has joined #ocaml
hkBst has quit [Read error: 54 (Connection reset by peer)]
hkBst has joined #ocaml
<Yoric[DT]> gildor: thanks.
<Yoric[DT]> That's the version currently in the repository.
<Yoric[DT]> (with a few adjustments)
<gildor> great
ikaros has quit [Read error: 110 (Connection timed out)]
ikaros has joined #ocaml
jlouis has joined #ocaml
johnnowak has quit []
<kig> you could derive tests and a spec from a function's signature. generate testable values from the types (zero, one, odd, even, extremes) like quickcheck, then call the function with permutations thereof and record the results into a unit test. finally ask the programmer to check if it looks sane.
<kig> and collect runtimes and memory use and curve-fit for an O-class + constant factor
<vixey> kig, ... and you still wouldn't be sure if it was correct :p
<kig> and?
<mrvn> and don't forget all the functions where the arguments are interdependent.
<kig> ok, i'll just go back to feeling silly writing thousands of lines of repetitive unit tests ->
sanity- has joined #ocaml
<mrvn> You could generate a test template and then refine those functions that need better tests.
<sanity-> does Ocaml support portable continuations? (ie. continuations that can be serialized on one computer, transmitted over the network, and resumed on another computer)?
sanity- is now known as sanity
<Smerdyakov> sanity, OCaml does not generally support continuations.
<sanity> Smerdyakov: oh, hmm, I was told something different. Are you aware of any reasonably decent languages that do support portable continuations?
<Camarade_Tux> sanity, the Marshal module documentation states 'If flags contains Marshal.Closures, functional values will be marshaled as a position in the code of the program. In this case, the output of marshaling can only be read back in processes that run exactly the same program, with exactly the same compiled code.'
<Smerdyakov> No. It sounds like a security nightmare.
<mrvn> It is pretty hard to do with binary code.
<sanity> Camarade_Tux: that is reasonable
<sanity> Camarade_Tux: so is Smerdyakov wrong, Ocaml does support continuations?
<Smerdyakov> sanity, are you really talking about first-class continuations (with call/cc) or just first-class functions?
<mrvn> In bytecode you can use the actual source form and wrap that in a transportable closure module.
<sanity> Smerdyakov: call/cc - basically freezing the state of the program and resuming it on a different computer
<Smerdyakov> sanity, OK. None of that in OCaml.
<Smerdyakov> sanity, you can always do just as well by strategic use of CPS, though.
<sanity> Smerdyakov: ok. I know this is OT - but do you know if SML supports portable continuations? (I know it supports callcc)
<Smerdyakov> sanity, SML does not "support call/cc." The language Definition mentions no such thing. Some compilers support it, others don't.
<vixey> what on earth is "portable" about a continuation
<mrvn> vixey: serializable
<sanity> Smerdyakov: gotchya. but SML-NJ supports it, right?
<Smerdyakov> sanity, yes, and MLton.
<sanity> Smerdyakov: do you know if either support portable continuations?
<Smerdyakov> sanity, in neither case is there support for running a continuation on a different machine, or even in a different process.
<vixey> sanity: Have you been reading nonsense about continuation based web servers?
<sanity> vixey: no, I've been writing it
<Smerdyakov> I have to echo vixey's sentiment, though more politely.
<sanity> vixey: ;-P
<Smerdyakov> sanity, I have a feeling you don't understand how continuations are used in reality.
* Yoric[DT] actually likes the idea of web + continuations.
<Smerdyakov> sanity, I'm not aware of any case of "portable continuations" in use anywhere.
<Yoric[DT]> Despite the security and gc nightmare.
<sanity> Smerdyakov: I don't think you know enough about me to come to that conclusion :-)
<vixey> sanity, no thank you
<sanity> vixey: suit yourself
<vixey> sanity, but I will mention that Oz lets you serialize closures and use them across i.e. network boundries
<mrvn> Yoric[DT]: you would pack data used by the continouation into the data you send. No gc nightmare there.
<sanity> vixey: hmmm, ok, I'll investigate that, thanks
<vixey> sanity, but I don't think it has a CWCC so that would mean writing everything in CPS like Smerdyakov mentioned
<sanity> vixey: ok.
<mrvn> Does it have to work across different systems or identical cpu/os?
<sanity> Smerdyakov: yes, my fear is that I'll need to create a new language, which would suck (mission creep etc)
<sanity> mrvn: well, different systems would be greatly preferable.
<Smerdyakov> sanity, I'm confused about why you want this feature.
<vixey> sanity, I suspect you just aren't giving _data_ a chance
<Yoric[DT]> mrvn: as in packing *all* data?
<sanity> Smerdyakov: did you read the locut.us link I pasted above?
<Smerdyakov> sanity, the beginning.
<mrvn> Yoric[DT]: only those reachable from the closure.
<Yoric[DT]> Of course.
jlouis has quit [Read error: 104 (Connection reset by peer)]
<Yoric[DT]> mrvn: but in CPS, I suspect that means [almost] all data.
<sanity> Smerdyakov: skip to the last paragraph in "The Store" section to get to the meat of the concept
<Smerdyakov> sanity, I already read that part. Why do you want to do that?
<mrvn> I've done this for a game once. The job was to have a program that runs and outputs the next turn and may output some data to be used for the next run.
<sanity> Smerdyakov: to allow data to be distributed across multiple servers in a way that is transparent to the programmer
<Smerdyakov> sanity, and you don't think it's a security nightmare to run any code a client sends to you?
<mrvn> sanity: in inhomogenous setups that is really difficult, i.e. expensive
<sanity> Smerdyakov: no, the code is already on the machine, only the stack and program counter are transmitted (in theory)
<mrvn> sanity: and think about what it means when data is bound to 2 continuations that run on different systems.
<sanity> mrvn: yes, I'm thinking I may need to support it at the bytecode level
<Smerdyakov> sanity, that is quite enough opportunity for trouble.
<sanity> mrvn: I've already talked the guy working on the Cat programming language to support portable continuations for it
<Smerdyakov> sanity, programs can send stacks and program counters that were never meant to flow to that point.
<Smerdyakov> sanity, I think the Cat language isn't very highly regarded by people in the know. ;)
* vixey wonders... is there something like JVM except with more types? to rule out the problems Smerdyakov mentions
jlouis has joined #ocaml
<sanity> vixey: exactly, and that is kinda what Cat is
<sanity> Smerdyakov: have any pointers to critiques of Cat?
<Smerdyakov> sanity, no.
smimou has quit [Read error: 110 (Connection timed out)]
<mrvn> sanity: any idea how to make a good multi-hosted GC?
<sanity> Smerdyakov: I'm not settled on Cat yet, but its creator is being very cooperative and that is a *big* benefit in its favor
<sanity> mrvn: only vague ideas
<sanity> mrvn: "Swarm" is an ambitious project :-)
<vixey> sanity, It doesn't look like what I meant
<mrvn> sanity: you could try them out by writing a multithreaded GC for ocaml. :)
<Smerdyakov> sanity, beware being sucked into the world of vanity programming language projects.
<sanity> Smerdyakov: believe me, I'd really prefer to use an existing programming language, but I can't find one that supports portable continuations
<mrvn> sanity: maybe that has a good reason. :)
<vixey> sanity, where is this term "portable" fro
<Smerdyakov> sanity, I think you are unwittingly choosing an undesirable feature whose presence is correlated with crackpotism.
<vixey> Smerdyakov, I will concur with that but more politely :p
<sanity> vixey: not sure, I thought it was a common term, but maybe I made it up
<sanity> Smerdyakov: correlation doesn't imply causality
<sanity> Smerdyakov: portable continuations are rather fundimental to the proposal
ygrek has joined #ocaml
<mrvn> Are they at least signed?
<sanity> mrvn: all code would be signed, and the messaging protocol would be secure when it needs to be
<sanity> mrvn: I'm thinking the approach to code would be a bit like this: http://0install.net/
<sanity> mrvn: ie. you reference code in such a way that the VM can download it if it needs it (and which includes a digital signature)
smimou has joined #ocaml
<vixey> 0install is a terrible idea
<sanity> vixey: why?
<vixey> well think about it
ofaurax has joined #ocaml
vixey has quit ["There exists an infinite set!"]
<sanity> vixey: ?
vixey has joined #ocaml
_JusSx_ has joined #ocaml
sporkmonger has joined #ocaml
pango has quit [Remote closed the connection]
_zack has quit ["Leaving."]
ikaros has quit [".quit"]
pango has joined #ocaml
_JusSx_ has quit ["leaving"]
_JusSx_ has joined #ocaml
itewsh has joined #ocaml
alexyk has quit []
alexyk has joined #ocaml
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
sanity has quit [Read error: 110 (Connection timed out)]
ygrek has quit [Remote closed the connection]
<alexyk> how do I pack a bunch of .cmo's into a .cma? ocamlmklib creates a .cma but loading it wants a dll...so which is not needed
<Smerdyakov> Use OCamlMakefile or some other piece of magic; I always have. :)
fschwidom has quit [Read error: 113 (No route to host)]
alexyk has quit []
sanity- has joined #ocaml
ygrek has joined #ocaml
itewsh has quit ["KTHXBYE"]
proqesi has joined #ocaml
munificent has joined #ocaml
sanity- is now known as sanity
Camarade_Tux_ has joined #ocaml
alexyk has joined #ocaml
ygrek has quit [Remote closed the connection]
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
Camarade_Tux_ is now known as Camarade_Tux
mjonsson_ has joined #ocaml
ygrek has joined #ocaml
thelema_ has joined #ocaml
mjonsson has quit [Read error: 113 (No route to host)]
thelema has quit [Nick collision from services.]
thelema_ is now known as thelema
thelema_ has joined #ocaml
_JusSx_ has quit ["leaving"]
ygrek has quit [Remote closed the connection]
proqesi has quit [Remote closed the connection]
proqesi has joined #ocaml
seafood has joined #ocaml
alexyk has quit []
alexyk has joined #ocaml
alexyk has quit [Client Quit]
alexyk has joined #ocaml
Stefan_vK1 has joined #ocaml
alexyk has quit []
dfritz has joined #ocaml
alexyk has joined #ocaml
hkBst has quit [Read error: 131 (Connection reset by peer)]
<dfritz> Hello all, can someone recommend a place that describes how to create cgi scripts with ocaml? I have installed ocamlcgi but I cannot find any documentation on how to use it.
<Smerdyakov> Did you read its .mli files?
Stefan_vK has quit [Read error: 104 (Connection reset by peer)]
seafood has quit []
alexyk has quit []
ikaros has joined #ocaml
itewsh has joined #ocaml
alexyk has joined #ocaml
munificent has quit []
alexyk has quit []
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
sanity has quit [Read error: 110 (Connection timed out)]
alexyk has joined #ocaml
alexyk_ has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
alexyk has quit [Read error: 110 (Connection timed out)]
jlouis has quit ["Leaving"]
r0bby has quit [Client Quit]
r0bby has joined #ocaml
vixey has quit ["There exists an infinite set!"]