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 []
alexyk has joined #ocaml
Israel_ has quit [Read error: 110 (Connection timed out)]
Alpounet has quit ["Quitte"]
komar_ has joined #ocaml
psnively has quit []
alexyk has quit []
jknick has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
flux has quit [Remote closed the connection]
flux has joined #ocaml
travisbrady has quit []
ched_ has quit [Read error: 110 (Connection timed out)]
ched__ has joined #ocaml
prigaux has quit [anthony.freenode.net irc.freenode.net]
bacam has quit [anthony.freenode.net irc.freenode.net]
Ori_B has quit [anthony.freenode.net irc.freenode.net]
TaXules has quit [anthony.freenode.net irc.freenode.net]
xevz has quit [anthony.freenode.net irc.freenode.net]
jlouis_ has quit [anthony.freenode.net irc.freenode.net]
holgr has quit [anthony.freenode.net irc.freenode.net]
bernardofpc has quit [anthony.freenode.net irc.freenode.net]
delroth has quit [anthony.freenode.net irc.freenode.net]
ReinH has quit [anthony.freenode.net irc.freenode.net]
tarbo2 has quit [anthony.freenode.net irc.freenode.net]
tsuyoshi has quit [anthony.freenode.net irc.freenode.net]
gim has quit [anthony.freenode.net irc.freenode.net]
patronus has quit [anthony.freenode.net irc.freenode.net]
maskd has quit [anthony.freenode.net irc.freenode.net]
flux has quit [anthony.freenode.net irc.freenode.net]
m3ga has quit [anthony.freenode.net irc.freenode.net]
kaustuv has quit [anthony.freenode.net irc.freenode.net]
sgnb has quit [anthony.freenode.net irc.freenode.net]
Hadaka has quit [anthony.freenode.net irc.freenode.net]
patronus has joined #ocaml
delroth has joined #ocaml
bernardofpc has joined #ocaml
gim has joined #ocaml
tsuyoshi has joined #ocaml
tarbo2 has joined #ocaml
ReinH has joined #ocaml
holgr has joined #ocaml
jlouis_ has joined #ocaml
acatout has quit [anthony.freenode.net irc.freenode.net]
prigaux has joined #ocaml
xevz has joined #ocaml
TaXules has joined #ocaml
bacam has joined #ocaml
Ori_B has joined #ocaml
flux has joined #ocaml
m3ga has joined #ocaml
kaustuv has joined #ocaml
sgnb has joined #ocaml
maskd has joined #ocaml
Hadaka has joined #ocaml
acatout has joined #ocaml
alexyk has joined #ocaml
ulfdoz has quit [Read error: 110 (Connection timed out)]
Israel_ has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
travisbrady has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
Israel___ has joined #ocaml
Israel_ has quit [Read error: 60 (Operation timed out)]
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
gl has quit [Read error: 110 (Connection timed out)]
mfp has quit [anthony.freenode.net irc.freenode.net]
mal`` has quit [anthony.freenode.net irc.freenode.net]
sbok has quit [anthony.freenode.net irc.freenode.net]
bind_return has quit [anthony.freenode.net irc.freenode.net]
Mr_Awesome has quit [anthony.freenode.net irc.freenode.net]
sbok has joined #ocaml
sbok has quit [Killed by reynolds.freenode.net (Nick collision)]
mfp has joined #ocaml
mal`` has joined #ocaml
Mr_Awesome has joined #ocaml
bind_return has joined #ocaml
sbok has joined #ocaml
sbok_ has joined #ocaml
julm has quit [Read error: 60 (Operation timed out)]
julm has joined #ocaml
lanaer has quit [Remote closed the connection]
sbok has quit [Success]
Israel___ has quit []
lanaer has joined #ocaml
<travisbrady> I built a native executable with ocamlopt that has some printf's sprinkled throughout but the output shows up all at once, is the buffering switch somewhere?
<brendan> stdout is normally buffered. You can put ! at the end of your printf string though
<brendan> or print to stderr
Camarade_Tux has joined #ocaml
<travisbrady> hmm, eprintf still seems buffered
<travisbrady> where do i put the !'s?
<brendan> at the end of the format string
<brendan> printf "foo!"
<travisbrady> hmm, still no luck, just getting bangs in the actual output
<brendan> sorry, %!
<det> flush stdout
<brendan> or that
<brendan> but %! should work
<det> will cause all buffered output as of yet to be flushed
jm has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
<travisbrady> brendan, det: thank you, the %! worked
<brendan> great
<det> Printf.printf "foo%!" is the same as Printf.printf "foo"; flush stdout
<brendan> only less typing :)
<det> but messy
Ched has joined #ocaml
<travisbrady> i'm just learning but OCaml's Printf definitely looks like a strange and wonderous creature
<Camarade_Tux> you probably got it right then ;)
<det> I wonder if it is possible to define your own printf (using ocaml's printf) that flushed after every call
<Camarade_Tux> I remember somebody "overwriting" a function in Array not that long ago on the mailing-list but I don't have enough to remember how exactly
<Camarade_Tux> (basically redefined the module)
<olegfink> # let printf f = let a = Printf.printf f in flush stdout; a ;;
<olegfink> val printf : ('a, out_channel, unit) format -> 'a = <fun>
<det> Wouldn't that flush before printing ?
<olegfink> no, works as advertised here.
<det> let printf2 format = let f = Printf.printf format in fun x -> f x; flush stdout
<det> I think this is what you need
<olegfink> try [Printf.printf "a"; Unix.sleep 2; Printf.printf "b"] and [printf "a"; Unix.sleep 2; printf "b"]
<olegfink> det: your printf is ('a...) format -> unit, Printf.printf is ('a...) format -> 'a
<det> # let printf f = let a = Printf.printf f in (print_string "\nflush\n"; a);;
<det> val printf : ('a, out_channel, unit) format -> 'a = <fun>
<det> # printf "%d\n" 5;;
<det> flush
<det> 5
<det> - : unit = ()
<brendan> does that work for more than one argument?
<det> replacing the flush with a print statement, it does indeed happen before printing
<det> Yeah, mine doesnt work either.
<det> only with 1 argument
<olegfink> hrm, why does it happen?
<det> because Printf.printf <format> doesnt do any printing
<det> it just returns a closure
<olegfink> what's with 1 argument?
<olegfink> # printf "%d %d\n" 42 666 ;;
<olegfink> 42 666
<det> a argument is for my version
<det> both of ours are broken
<det> your's flushes before
<det> mine only allows 1 argument
<olegfink> indeed.
<olegfink> but [format] is so much fun.
<olegfink> well, actually the only use for it I've seen outside of formatting functions is for typing dynamic loadables in ocaml-dlopen
ched__ has quit [Read error: 110 (Connection timed out)]
<olegfink> ahaha
<olegfink> det: # let printf f = Printf.printf (f^^"%!");;
<det> Ahh
<det> I didnt know (^^) existed
<olegfink> iirc (^^) is just (^) with funny type annotations
<brendan> didn't know that one either, nice
<brendan> formats are awesome
<olegfink> yeah, that's it
<olegfink> external format_to_string :
<olegfink> ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string = "%identity"
<olegfink> the same in the other direction
<olegfink> (^^) is fun fmt1 fmt2 ->
<olegfink> string_to_format (format_to_string fmt1 ^ format_to_string fmt2)
Camarade_Tux has quit ["Leaving"]
jm is now known as julm
m3ga has quit ["disappearing into the sunset"]
gl has joined #ocaml
<flux> det, let flush_printf fmt = Printf.ksprintf (fun s -> (* print string, flush, whatever *)) fmt
ikaros has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
smimou has joined #ocaml
jamii has joined #ocaml
Alpounet has joined #ocaml
schmx has joined #ocaml
alexyk has quit []
_zack has joined #ocaml
ikaros has quit [Remote closed the connection]
th5 has joined #ocaml
<th5> How can I use a .cmi file in the toplevel? (I have an .mli file without a .ml that I want to use)
<flux> you need to have the .cmi-file in your search path
<julm> and you use its name with a cap at the beginning
<flux> how come you have an .mli without a corresponding .ml?
<julm> that is possible indeed
<flux> or you mean a package has installed those files for you?
<th5> messing around with the source of an existing project
<julm> if you only need to declare types no need for a .ml
<th5> file mostly defines types
<flux> julm, really? I didn't know that
<julm> yep
<flux> I've just used an .ml in those cases, then I can add a function too if I need to
<th5> I'm trying to #load a bunch of .cmo's though and need this one .cmi - what directive should I use?
<flux> #directory
<flux> so you won't tell the individual .cmi-files, you tell a location where ocaml can find them from
<th5> is #directory ".";; automatically there?
<flux> yes
<th5> I don't think I'm explaining myself properly. I'm not trying to use Module.junk directly in the toplevel. I'm trying to load a cmo that was compiled against this file. I get a 'Reference to undefined global "Modulename"' when trying to load the cmo
* th5 might have an xy problem
<flux> that's not because of a missing .cmi-file, but missing .cmo (or .cma)-file
<flux> a missing .cmi-file would cause error "Unbound value"
<th5> ok thanks
sgnb has quit [Read error: 54 (Connection reset by peer)]
sgnb` has joined #ocaml
angerman has joined #ocaml
barismetin has joined #ocaml
bind_return has quit [anthony.freenode.net irc.freenode.net]
mal`` has quit [anthony.freenode.net irc.freenode.net]
Mr_Awesome has quit [anthony.freenode.net irc.freenode.net]
mfp has quit [anthony.freenode.net irc.freenode.net]
mfp has joined #ocaml
mal`` has joined #ocaml
Mr_Awesome has joined #ocaml
bind_return has joined #ocaml
det has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has joined #ocaml
ulfdoz has joined #ocaml
det has joined #ocaml
robocop has joined #ocaml
<robocop> hello.
<robocop> I've you got an exemple to search/replace with regex in ocaml ?
<flux> I'd use the Pcre module
<Yoric[DT]> Which is annoying as heck, but fast.
<flux> in which case it might be like Pcre.replace ~pat:"hello" ~tmpl:"world" "hello world"
<flux> yoric[dt], what's annoying about it, except perhaps the arrays?
<robocop> ths module flux : http://sourceforge.net/projects/pcre-ocaml ?
<flux> robocop, do you run debian or ubuntu?
<flux> or fedora
<flux> or something else :)
<Yoric[DT]> flux: the semantics of side-effects.
<Yoric[DT]> Oh, sorry, I meant Str.
<Yoric[DT]> I have barely used Pcre.
<robocop> flux: archlinux.
<flux> robocop, hmm.. and it doesn't have that module already?
<robocop> ha, yes, it's in aur :)
<robocop> adn how I can open it in the top-level ?
<flux> robocop, easy way: first, do #use "findlib";;
<flux> put that into your ~/.ocamlinit if you like
<flux> then: #require "pcre";;
<robocop> hum :
<robocop> # #use "findlib";;
<robocop> Cannot find file findlib.
<flux> you don't have findlib?! install it :-)
<flux> can be called 'ocamlfind'
<Yoric[DT]> Yeah, install findlib, definitely.
m3ga has joined #ocaml
thelema has joined #ocaml
<robocop> okey, it's intalled.
schmx is now known as schme
<flux> robocop, ..and?
<robocop> and...
<robocop> # #use "findlib";;
<robocop> Cannot find file findlib.
<flux> hmm
<robocop> :p
<flux> ah
<flux> it was #use "topfind";;
<flux> I needed to run ocaml myself and my muscle memory typed it in for me ;-)
<robocop> yes, that's work !
<robocop> thanks for your help.
<robocop> Ha, I've got a problem with your regex : http://paste.pocoo.org/show/120528/
smimou has quit ["bli"]
<flux> it should've had been ~templ, not ~tmpl
<robocop> okey, thanks.
gdmfsob has joined #ocaml
<robocop> and if I want to compile in a file, ocamlbuild know this :p ?
<flux> with ocamlbuild you want to have some stuff to make it work with packages neatly
<flux> put that and a _tags-file with contents like <*>: pkg_pcre into your directory ocamlbuild yourproggy.byte should build it for you
<flux> "and ocamlbuild.."
<robocop> okey, thanks, I'm going to test.
mishok13 has quit [Read error: 145 (Connection timed out)]
Alpounet has quit ["Quitte"]
<robocop> flux: he doesn't know Ocamlbuild_plugin : Unbound module Ocamlbuild_plugin
<flux> don't know about that
<flux> works for me (ocamlc 3.10.2 and some 3.11.x)
<robocop> I compile with ocamlbuild.
<robocop> it's a problem ?
<flux> robocop, so what is your command line?
<flux> you're not supposed to build myocamlbuild.ml if that's what you're doing
<flux> no
<flux> ocamlbuild yoursourcefile.byte
<flux> not myocamlbuild.byte (or .native)
<robocop> ha, okey.
<robocop> He will search myocamlbuild.ml
<robocop> ?
<flux> ocamlbuild automatically uses certain files, one beind myocamlbuild
<robocop> okey, thanks.
<flux> actually it builds and I suppose executes it
<robocop> okey, that work.
ulfdoz has quit [Read error: 110 (Connection timed out)]
<robocop> thanks a lot for your help flux.
<flux> glad to be of help
<flux> happy hacking with ocaml :)
<robocop> just a last question : if I want to get the token, what's the syntax ? (exemple in php : $1, $2, etc...)
<robocop> (in the result).
<flux> last token of what?
<robocop> exemple in php : $text = preg_replace('#\[b\](.+)\[/b\]#isU', '<strong>$1</strong>', $text);
<robocop> $1 correspond to (.+)
<flux> it works just as you wrote it
<flux> I imagine preg means "pcre regular expression"
<flux> so it's the same library
<flux> Pcre.replace ~pat:"(hello)" ~templ:"$1 and $1" "hello world";;
jeremiah has quit [Read error: 110 (Connection timed out)]
<robocop> okey, thanks :p
<flux> I haven't really looked, but apparently you can use ~itempl for more advanced substitutons.. take a look at pcre.mli for documentation, or find a .html file of it
<robocop> it did not work just now...
<robocop> :p
<flux> well, my example still works, right?
<robocop> yes, it's works.
<robocop> but this doesn't work : http://paste.pocoo.org/show/120532/
<flux> the expression needs to be parenthesized
<flux> replace "(define|if)"
<robocop> ha, okey.
<flux> ..so it knows into which subexpression it refers to
<flux> just like in php :)
<robocop> thanks.
<flux> but now I'm off to get some lunch
jeanbon has joined #ocaml
<robocop> goof lunch.
kaustuv has quit ["ERC Version 5.3 (IRC client for Emacs)"]
jeanbon has quit ["EOF"]
yziquel has joined #ocaml
acatout has quit [Read error: 113 (No route to host)]
robocop has left #ocaml []
argv[0] has joined #ocaml
schme has quit [Read error: 113 (No route to host)]
argv[0] is now known as mishok13
LeCamarade|Away is now known as LeCamarade
m3ga has quit ["disappearing into the sunset"]
gdmfsob has quit [Read error: 110 (Connection timed out)]
gdmfsob has joined #ocaml
mishok13 has quit [Read error: 60 (Operation timed out)]
<det> mrvn, hey
Axioplase has joined #ocaml
mishok13 has joined #ocaml
_andre has joined #ocaml
acatout has joined #ocaml
jm has joined #ocaml
jm has quit [Client Quit]
julm has quit ["Quitte"]
julm has joined #ocaml
gdmfsob has quit [Read error: 110 (Connection timed out)]
_andre has quit [Read error: 60 (Operation timed out)]
_andre has joined #ocaml
travisbrady_ has joined #ocaml
travisbrady has quit [Read error: 104 (Connection reset by peer)]
prigaux is now known as pixel_
ikaros has joined #ocaml
thelema has quit [Read error: 60 (Operation timed out)]
olegfink has quit [Remote closed the connection]
ikaros has quit ["Leave the magic to Houdini"]
<rwmjones> reddit is half-down at the moment ... how else am I supposed to waste time at work!
_zack has quit ["Leaving."]
itewsh has joined #ocaml
rjack has joined #ocaml
yziquel has quit [Read error: 113 (No route to host)]
Associat0r has joined #ocaml
ulfdoz has joined #ocaml
bombshelter13_ has joined #ocaml
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
jeanbon has joined #ocaml
_zack has joined #ocaml
Axioplase has quit ["/quat"]
thelema has joined #ocaml
pixel_ is now known as prigaux
itewsh has quit [Remote closed the connection]
ikaros has joined #ocaml
jli has joined #ocaml
<jli> Unix.getlogin seems to always throw an exception for me
olegfink has joined #ocaml
LeCamarade is now known as LeCamarade|Away
<jli> does it work for others?
<julm> works for me
<julm> what's the exception thrown?
maxote has quit [Read error: 110 (Connection timed out)]
<jli> Exception: Unix.Unix_error (Unix.ENOENT, "getlogin", "").
<jli> in getlogin.c, it seems to do a straight call to getlogin()
<jli> I'm testing to see if the syscall works in C directly
<flux> saw that problem some time ago on ubuntu 8 and 9
<flux> didn't file a bug at that time, though :)
<julm> looks like the C getlogin() returns a NULL pointer
<flux> (never filed an ocaml bug..)
<flux> hmm
<flux> at that time iirc it worked for yoric
maxote has joined #ocaml
<flux> maybe it's better to use geteuid and getpwuid
<flux> now that I look, who doesn't list my TTY in the list
<flux> and the manual page of getlogin leads me to think that it makes use of the same information
<jli> okay, looks like it's not an OCaml issues
<jli> getlogin(3) is just returning null pointers
<jli> okay, problem solved, unix sucks :)
alexyk has joined #ocaml
th5 has quit []
smimou has joined #ocaml
yziquel has joined #ocaml
Israel_ has joined #ocaml
travisbrady_ has quit []
vbmithr has joined #ocaml
ikaros has quit ["Leave the magic to Houdini"]
youscef has joined #ocaml
youscef has left #ocaml []
travisbrady has joined #ocaml
Camarade_Tux has joined #ocaml
Camarade_Tux has quit ["Leaving"]
Camarade_Tux has joined #ocaml
barismetin has quit [Remote closed the connection]
christos__ has joined #ocaml
BiDOrD has quit [Read error: 110 (Connection timed out)]
BiDOrD has joined #ocaml
christos__ has quit []
alexyk has quit []
alexyk has joined #ocaml
smimou has quit ["bli"]
Snark has joined #ocaml
alexyk has quit []
Amorphous has quit [Read error: 110 (Connection timed out)]
yziquel has quit ["Leaving"]
Amorphous has joined #ocaml
BiDOrD has quit [Read error: 110 (Connection timed out)]
Israel_ has quit []
komar___ has joined #ocaml
komar___ is now known as komar__
Camarade_Tux has quit ["Leaving"]
komar_ has quit [Read error: 110 (Connection timed out)]
alexyk has joined #ocaml
malc_ has joined #ocaml
<malc_> rwmjones: here?
alexyk has quit []
komar_ has joined #ocaml
Israel has joined #ocaml
komar__ has quit [Read error: 113 (No route to host)]
jeanbon has quit ["EOF"]
palomer has joined #ocaml
romildo has joined #ocaml
jbjohns has joined #ocaml
<romildo> Hi.
<romildo> I want to learn camlp4, but it seems that the tutorials are out of date.
<romildo> What documentation do you recommend for learning camlp4?
<hcarty> romildo: http://brion.inria.fr/gallium/index.php/Camlp4 -- From what I've heard others say, this wiki and the camlp4 source are the best references currently available
<romildo> hcarty, thanks for the link. I will look at it.
<hcarty> romildo: Best of luck. I haven't used camlp4 much, but there are several folks here and on the list who know what they are doing
ikaros has joined #ocaml
<palomer> I've used it a little bit
_zack has quit ["Leaving."]
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
rjack has quit ["leaving"]
komar__ has joined #ocaml
<romildo> I started reading the "Using Camlp4" from the wiki http://brion.inria.fr/gallium/index.php/Camlp4
<romildo> I have created a syntax extension skeleton, as explained in the wiki. Here is the pa_calculator.ml file: http://paste.pocoo.org/show/120654/
<romildo> When compiling pa_calculator.ml on my gentoo linux box, I get the following:
<romildo> $ ocamlc -I +camlp4 camlp4lib.cma -pp camlp4of.opt pa_calculator.ml
<romildo> File "pa_calculator.ml", line 1, characters 0-1:
<romildo> Error: Error while linking /usr/lib64/ocaml/camlp4/camlp4lib.cma(Camlp4):
<romildo> Reference to undefined global `Dynlink'
<romildo> What is going on here?
<julm> it is apparently looking for a Dynlink module
<mbishop> haha wut
<julm> try to add dynlink.cma on you command line perhaps
jbjohns has quit [Read error: 104 (Connection reset by peer)]
<mbishop> that code is actually sml, although it's use seems sparse
<romildo> Adding dynlink.cma does not solves the problem. Still same error with it.
komar_ has quit [Read error: 113 (No route to host)]
<julm> romildo: ocamlc -I +camlp4 dynlink.cma camlp4lib.cma -pp camlp4of.opt pa_calculator.ml
<julm> dynlink.cma before camlp4lib.cma
<julm> it's ocamlc not gcc, dependencies go first
Israel has quit []
jeanbon has joined #ocaml
alexyk has joined #ocaml
<romildo> yes, that was my mistake.
jeanbon has left #ocaml []
Snark has quit ["Ex-Chat"]
yziquel has joined #ocaml
<romildo> As I have not programming in Ocaml for some time now, I have not taken the time to read about dynlink. So I do not know why it is needed here.
<yziquel> has someone got examples of code using Batteries.Future.Logger?
<julm> dynamic linking
<julm> loading ocaml binaries at runtime
<julm> part of Camlp4's modularity
<julm> (and slowness)
<romildo> But now I am just interested inlearning camlp4 to write a syntax extension. Later on I take a look at dynamic linking.
<romildo> Just a question about it: is it mandatory, or can I use camlp4 without dynamic linking?
<julm> I've checked all /usr/local/lib/ocaml/camlp4/camlp4*.cma with ocamlobjinfo and they all require DynLink
<palomer> google code now has mercurial support
<julm> but even though DynLink is required, it may be that it is not actually used at all for what you're doing
<julm> I don't know, if you want more insight try to ask ertai
<mfp> romildo: are you sure you have to link against camlp4lib.cma?
<mfp> that code is provided by camlp4o(rf,oof,), which dynlinks your pa_whatever.cmo
<mfp> romildo: so there's no need for you to worry about dynlink at all --- it's camlp4o and friends which use (and are linked against) it
<mfp> ah you're using it as a parser, not an extension
<palomer> why does camlp4 use dynlink?
<mfp> palomer: it uses it to load the syntax extensions
<mfp> e.g. when you do camlp4o pa_do.cmo
<mfp> it dynlinks pa_do.cmo
<romildo> mfp, I am not sure, as I've said before, I am just starting learning camlp4. I am trying the first example from the "Syntax extension tutorial" in the camlp4 wiki.
<mfp> romildo: what do you want to achieve? an extension to the OCaml syntax, or a parser from scratch?
<mfp> if the former, you only have to generate a pa_whatever.cmo, which will be loaded by camlp4o when you pass the -pp "camlp4o pa_whatever.cmo" option to ocaml{c,opt}
<palomer> ah, I see
<mfp> if the latter, you'll have to link against dynlink.cma and camlp4lib.cma
<mfp> the easiest way is to use ocamlfind ocamlc -package dynlink,camlp4.lib -o parser myparser.ml -linkpkg
<romildo> I want an extension to Ocaml. I want to modify the enum extension http://www.annexia.org/tmp/enum/ that was posted in the ocaml_beginers mailing list some months ago to automatically generate conversion functions between enum and strings.
<palomer> don't you need -syntax camlp4o ?
<palomer> what does the f in camlp4orf stand for?
<mfp> palomer: I just use -pp camlp4orf
<romildo> But I am not yet modigyin the enum extension, as currently I do not know camlp4. I am first trying examples from the tutorial.
<mfp> (forgot it since I was pasting from an OMakefile, and the OCAMLFLAGS were set in the parent dir)
<palomer> mfp, when compiling your extension?
<mfp> yes
<palomer> -pp camlp4orf == -syntax camlp4o ?
<mfp> palomer: IIRC that f stands for "full"
<mfp> -syntax camlp4o builds a -pp "camlp4o stuff.cmo ..." option
<mfp> according to the options specified in the packages
<romildo> palomer, From the wiki, "the ending "f" means full, that is all standard extensions (parsers, grammars, quotations, macros, and list comprehensions)."
<mfp> camlp4orf is camlp4o + several extensions
<mfp> yup
<palomer> ah, righto, when I build my extension I use -pp camlp4orf
<palomer> when I use my extension, I put -syntax camlp4o
_andre has quit ["leaving"]
<yziquel> what logging module would you recommend? Batteries.Future.Logger, or http://www.wingnet.net/~jesse/ocaml/logger/, or Bolt http://bolt.x9c.fr/ ?
schme has joined #ocaml
Israel_ has joined #ocaml
romildo has quit ["Leaving"]
thelema has quit [Read error: 110 (Connection timed out)]
Israel_ has quit []
bombshelter13_ has quit [Success]
angerman has quit []
ikaros has quit ["Leave the magic to Houdini"]
bombshelter13_ has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
slash_ has joined #ocaml
julm has joined #ocaml
psnively has joined #ocaml
sbok_ is now known as sbok
alexyk has quit []
yziquel has quit [Read error: 110 (Connection timed out)]
komar__ has quit [Read error: 60 (Operation timed out)]
Camarade_Tux has joined #ocaml
jeremiah has joined #ocaml
Lomono has joined #ocaml
schme has quit [Read error: 113 (No route to host)]
smimou has joined #ocaml
Camarade_Tux has quit ["Leaving"]
komar__ has joined #ocaml
psnively has quit [anthony.freenode.net irc.freenode.net]
maxote has quit [anthony.freenode.net irc.freenode.net]
jknick has quit [anthony.freenode.net irc.freenode.net]
kig has quit [anthony.freenode.net irc.freenode.net]
mattam has quit [anthony.freenode.net irc.freenode.net]
thelema has joined #ocaml
psnively has joined #ocaml
maxote has joined #ocaml
jknick has joined #ocaml
kig has joined #ocaml
mattam has joined #ocaml
mattam has quit [Remote closed the connection]
mattam has joined #ocaml
malc_ has quit ["leaving"]
psnively has quit []
loufoque has joined #ocaml
smimou has quit ["bli"]
Alpounet has joined #ocaml
<Alpounet> Hi
<Alpounet> what can cause "Unbound module Sdlevent" on a computer, but not on another ?
<Alpounet> ocaml and/or SDL installations right ?
<hcarty> Alpounet: Most likely, yes
<Alpounet> hcarty, by the way, have you more time now ?
<hcarty> Alpounet: Now, or later this week at least
<Alpounet> it was to talk a little about newhope
<Alpounet> but that can be done on the ML
<Alpounet> anything new about the project you proposed ?
<hcarty> Alpounet: As long as you don't mind my end of the conversation being slow at times, now is probably ok
<hcarty> Still no news from the Cairo folks
<hcarty> I'll ping them in the next day or two in #cairo to see if there is something holding the process up
<hcarty> If it's too much of a problem there then I'll setup (possibly) temporary git on the forge
<Alpounet> 'k
<hcarty> Anything on your end?
<Alpounet> not yet
<Alpounet> I don't have that much time currently, but it should get better by the end of June
<Alpounet> exams coming :-)
<gildor> hcarty, Alpounet: do you think xml-light is worth newhope ?
<hcarty> gildor: Probably so. Would you be able to keep it up, at least for the near-term?
<Alpounet> gildor, it is IMO, yes.
<gildor> hcarty: I think so, there is patch to apply from debian and CVS already contains bug fixes
m3ga has joined #ocaml
<gildor> what worry me is that upstream cannot even change xml-light homepage
<gildor> (even for a small redirection to newhope)
<hcarty> gildor: Adding it to newhope + an announcement to the Hump, feed and mailing list (or some subset of those) is probably a good idea then
<Alpounet> yeah
<Alpounet> gildor, they can't ? huh ?
<gildor> indeed, but I would like to begin newhope with a cooperative upstream ;-)
Israel has joined #ocaml
<gildor> anyway, I will set up what is required to transfer the project and see what I can do
Israel has quit [Client Quit]
<hcarty> gildor: Yes, it would be unfortunate to have trouble upstream from the first adopted project
<gildor> I think I will begin working on it, and then get back to him later to see if he agrees on a hump + announce
<Alpounet> looks great
<Alpounet> how many ready bug fixes are there already ?
<gildor> don't know because there was no bug tracking
<Alpounet> ok.
<gildor> but at least there is a META file
<gildor> which is something lacking
jamii has quit [Read error: 60 (Operation timed out)]
<jli> if a module has a type t = {recordfield: othertype}, is it possible to build records with the {recordname with recordfield=somethingelse} syntax?
<jli> am I able to reference the name "recordfield"?
<Yoric[DT]> 'night everyone
<Alpounet> gn Yoric[DT]
Yoric[DT] has quit ["Ex-Chat"]
<gildor> good night
<hcarty> jli: That is possible, if I understand what you are asking
<hcarty> type t = { x : int; y : int } let foo = {x = 1; y = 2} let bar = { foo with y = 3 };;
<jli> hcarty: yup, got it. the problem was because I was trying to do (fun one, two -> ...) for a fn that takes a 2-tuple
<jli> thanks
slash_ has quit [Client Quit]