mfurr changed the topic of #ocaml to: OCaml 3.08.2 available! | Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A tutorial: http://merjis.com/richj/computers/ocaml/tutorial/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
m3ga has quit ["Client exiting"]
smkl has quit [Read error: 238 (Connection timed out)]
smkl has joined #ocaml
<dan2> mrvn: ping
gim has quit []
<dan2> anybody have experience using swig and ocaml together?
smkl has quit [Read error: 238 (Connection timed out)]
zzorn_afk has quit ["They are coming to take me away ha ha"]
bzzbzz has joined #ocaml
smkl has joined #ocaml
bzzbzz has quit ["leaving"]
ez4 has quit ["Quitting!"]
smkl has quit [Read error: 238 (Connection timed out)]
TFK has quit [""Windows XP crashed./I am the Blue Screen of Death./No one hears your screams." -- Peter Rothman (http://www.infiltec.com/j-c]
Smerdy has joined #ocaml
Smerdyakov has quit [Nick collision from services.]
Smerdy is now known as Smerdyakov
smkl has joined #ocaml
budjet has joined #ocaml
budjet has quit [Remote closed the connection]
Submarine has joined #ocaml
vezenchio has joined #ocaml
smkl has quit [Read error: 238 (Connection timed out)]
mlh has joined #ocaml
smkl has joined #ocaml
magnus-- has joined #ocaml
smimou has joined #ocaml
zzorn has joined #ocaml
mrsolo_ has quit [Read error: 60 (Operation timed out)]
<mflux_> hmm.. this code fails to compile: type box = [ `Vbox of int | `Hbox of int ] and packing = [ box ]
<mflux_> if I replace the 'and' with 'type', it does, but I would like to define something recursive
<mflux_> the rror is 'The type constructor box is not yet completely defined'
<mflux_> any suggestions?
<mflux_> well, I can always use the non-variant approach, but I would expect it to clutter the code more..
smkl has quit [Read error: 238 (Connection timed out)]
smkl has joined #ocaml
<Demitar> mflux_, I get a syntax error instead. :)
<Demitar> (At the closing square bracket around box.)
<dan2> can anybody get to the humps right now?
mlh has quit [Client Quit]
<dan2> or caml.inria.fr
<Submarine> caml.inria.fr answers for me
<Submarine> er... actually it does not
dan2 changed the topic of #ocaml to: OCaml 3.08.2 available! | Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A tutorial: http://merjis.com/richj/computers/ocaml/tutorial/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/ | caml.inria.fr down
gim has joined #ocaml
smkl has quit [Read error: 238 (Connection timed out)]
<dan2> hmm
<dan2> is it possible to create variadic functions in ocaml
<Submarine> not really
<Submarine> unless you do strange things like those fior Printf.printf
<dan2> Submarine: how easy is it to make a list operation that will take the items in the list and add a space inbetween them and create a string
<Submarine> that's trivial
<dan2> Submarine: good, care to show me how? :)
<Submarine> isn'it Listconcat or String.concay?
<Submarine> or .join?
<dan2> Submarine: but that won't add whitespace inbetween them
<Submarine> otherwise
<Submarine> fun [] -> "" | h::t -> let buf = Buffer.create 10 ; Buffer.add_string buf h; Buffer.add_string buf separator; List.iter (fun s -> Buffer.add_string buf s; Buffer.add_string buf separator) t
<dan2> ok
<dan2> let create_s# let create_string_of_list a =
<dan2> match a with
<dan2> | [] -> ""
<dan2> | h::t -> let buf = Buffer.create 10;
<dan2> Buffer.add_string buf h;
<dan2> Buffer.add_string buf " ";
<dan2> List.iter (fun s -> Buffer.add_string buf s; Buffer.add_string buf " ") t;;
<dan2> Submarine: the ocaml compiler doesn't like it
<Submarine> howso?
<dan2> complains about the double ;;
<dan2> List.iter (fun s -> Buffer.add_string buf s; Buffer.add_string buf " ") t;;
<dan2> This expression has type unit but is here used with type string
<dan2> Submarine: ahh, it has to do with the return type
<Submarine> use Buffer.contents
<dan2> Submarine: ok
kdka has joined #ocaml
<dan2> Submarine: how do you exit a match
<Submarine> exit a match?
<dan2> match context with
<dan2> |"" -> c := Hashtbl.find agistor "agi_context"
<dan2> | context -> c := context
<dan2> how do I make another match
<dan2> after that one
<Submarine> parentheses?
<dan2> Submarine: huh?
<Submarine> (match ... with ... | ... -> ...)
<dan2> Submarine: will begin/end work?
<Submarine> idem
bzzbzz has joined #ocaml
kdka has quit []
smkl has joined #ocaml
Herrchen has joined #ocaml
Submarine has quit ["Leaving"]
mflux has joined #ocaml
mflux_ has quit [sterling.freenode.net irc.freenode.net]
MikeJS has joined #ocaml
<dan2> hmm
<dan2> is there a way to compile a regex and store it in a database?
Submarine has joined #ocaml
<pango> dan2: by using the Marshal module to serialize your regular expressions type, it's probably doable
<mflux> demitar, you need to use -pp camlp4o
<dan2> pango: ok
mattam has joined #ocaml
CosmicRay has joined #ocaml
smimou has quit [Remote closed the connection]
smimou has joined #ocaml
hangman4 has joined #ocaml
Herrchen has quit ["bye"]
mrvn_ has joined #ocaml
CosmicRay has quit ["Leaving"]
mrsolo_ has joined #ocaml
mrvn has quit [Read error: 110 (Connection timed out)]
mrvn_ is now known as mrvn
pango has quit [Nick collision from services.]
pango has joined #ocaml
<mrvn> To run the 32bit installer with a 64bit kernel and install 64bit debs.
<mrvn> ups
smkl has quit [Read error: 238 (Connection timed out)]
smimou has quit ["?"]
Riastradh has quit [Remote closed the connection]
Riastradh has joined #ocaml
Riastrad1 has joined #ocaml
Riastradh has quit [Nick collision from services.]
Riastrad1 is now known as Riastradh
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
smkl has joined #ocaml
vezenchio has quit ["haibane · renmei"]
mrsolo has joined #ocaml
<dan2> how do you create a type like this
<dan2> 'a = <poly>
<mellum> What's it supposed to do?
<dan2> mellum: its from marshall, but the concept looks interesting
<Submarine> # Obj.magic 1;;
<Submarine> - : 'a = <poly>
<dan2> whats Obj.magic do>
<mellum> Doesn't seem very useful, except to cause crashes.
<Submarine> Obj.magic is a universal cast from 'a to 'b
<Submarine> mellum, of course, it's useful!
<mellum> It pokes a hole into the type system. It's evil.
<mflux> mellum, how else would you go about crashing if you don't have that?
<mrvn> # List.hd (Obj.magic 1);;
<mrvn> zsh: segmentation fault ocaml
<mrvn> Very usefull to cause segfaults.
<Submarine> there are programs that are provably type-correct, but that OCaml cannot type
<Submarine> example: export some code using impredicative polymorphism from Coq
<mellum> Submarine: It's better to work around that differently, usually
ne1 has joined #ocaml
<Submarine> or: write the OCaml interpreter
<Submarine> (rather: the toplevel)
<mflux> I use Obj.magic to get the file descriptor number out of Unix.file_descr, for debugging
<dan2> where in the manual does it describe using the abstract type system
<mflux> (btw, someone on the channel suggested that to me, thanks ;))
<Smerdyakov> dan2, the section on the module system, no doubt.
mrsolo_ has joined #ocaml
<dan2> Smerdyakov: actually I was referring to things of type <abstr>
<Smerdyakov> dan2, never heard of it. Sounds like something generated for debug output or compiler error messages.
<Submarine> dan2, these are types that the module system hides away from you
<dan2> Submarine: right, thats what I want to do
<dan2> Submarine: I want to create a type I can hide away from the user
<Smerdyakov> dan2, I told you: look at the module system documentation.
<Submarine> then write a .mli
mrsolo has quit [Read error: 113 (No route to host)]
<Submarine> and don't specify the internals of your type in the .mli
<dan2> Smerdyakov: I did that
<dan2> Submarine: but I specify them in the module right?>
<dan2> or .ml
<Smerdyakov> dan2, I suggest that you read the tutorial section on the module system from start to finish.
<Smerdyakov> dan2, you should find your answer.
maml has joined #ocaml
<maml> caml.inria.fr is not down.
<dan2> maml: it was all day
dan2 changed the topic of #ocaml to: OCaml 3.08.2 available! | Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A tutorial: http://merjis.com/richj/computers/ocaml/tutorial/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
smimou has joined #ocaml
Octoploid has joined #ocaml
<dan2> why am I getting these warnings
<dan2> File "agi.ml", line 83, characters 58-61:
<dan2> Warning: This optional argument cannot be erased
<dan2> File "agi.ml", line 108, characters 73-75:
<dan2> Warning: This optional argument cannot be erased
<pango> you cannot end with an optional argument, or there will be an ambiguity (is the argument missing on purpose, or the function currified)
* Submarine does not use optional arguments
smkl has quit [Read error: 238 (Connection timed out)]
<dan2> pango: I got it fixed, thanks
<dan2> pango: whats your reccomended ocaml build system
<pango> what do you mean ?
<dan2> omake, ocamlconf ...
<dan2> configure/make ...
<pango> So far my own project aren't big enough so it matters
<dan2> I've got a pretty bid project
<dan2> big*
<dan2> currently using omake, but I'm thinking about moving away
<dan2> it doesn't provide features like install and clean which would be really useful
Submarine has quit ["Leaving"]
<Demitar> omake is like make not like automake.
<dan2> Demitar: hmm
<dan2> Demitar: I need something like automake
<Demitar> And there I have no recommendations. :)
<Demitar> But I have some plans, which would involve unification of ocamlconf/ocamldep and similar. ;-)
<dan2> ocamlconf was fair, but it seemed broken
<dan2> I could never get it to install native files correctly
<dan2> or install the .mli
<dan2> Demitar: another screwup of ocamlconf was that it would combine all the other libraries into each other libraries
<Demitar> dan2, go use OCamlMakeFile or something similar then.
<Demitar> I use a custom makefile mostly atm.
Octoploid has left #ocaml []
zno has joined #ocaml
smkl has joined #ocaml
mlh has joined #ocaml
budjet has joined #ocaml