Alpounet changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.1 out now! Get yours from http://caml.inria.fr/ocaml/release.html - Answer OCaml Meeting 2010 poll https://forge.ocamlcore.org/survey/survey.php?group_id=77&survey_id=1
jules_ has quit ["Leaving"]
BigJ has joined #ocaml
thrasibule has joined #ocaml
aij has quit ["testing"]
aij has joined #ocaml
aij has quit [Client Quit]
aij has joined #ocaml
Mr_Awesome has joined #ocaml
tmaedaZ is now known as tmaeda
ikaros_ has quit [Remote closed the connection]
bzzbzz has joined #ocaml
valross has joined #ocaml
peddie_ has joined #ocaml
peddie_ has quit [Client Quit]
middayc has quit ["ChatZilla 0.9.85 [Firefox 3.5.5/20091102152451]"]
bzzbzz has quit ["leaving"]
ski_ has joined #ocaml
tmaeda is now known as tmaedaZ
<yziquel_> let phi f x = f (x ()). Each time f (x ()) is called, x () gets evaluated. In some sense it is similar to (f x), except that the value of x is computed each time. Is it possible to mess around with tags of caml values so that we have (x : 'a) that gets evaluated every time our code stumbles on x?
<yziquel_> That would be very useful to bind C global variables whose content might change depending of a given status (R interpreter up and running, or not yet initialised, such as the R_NilValue symbol for the NULL value in R).
<thelema> x must have type unit -> 'a in the above, no?
<yziquel_> in the above, yes.
<thelema> phi has type ('a -> 'b) -> (unit -> 'a) -> 'b
<yziquel_> but i want x : 'a. Not x : unit -> 'a.
<thelema> and you want it to be ... evaluated each time it's used?
<yziquel_> yes.
<orbitz> then you want unit -> 'a
<thelema> what do you mean by evaluated?
* thelema thinks maybe 'a ref would suffice
<infoe> i've just started going through the book "Purely Functional Data Structures" to get some clue on idiomatic fp... the book is written with SML and has an excersize very early on called "suffixes" ('a list -> 'a list list) such that suffixes [1;2;3;4] would return [[1;2;3;4];[2;3;4];[3;4];[4];[]] I've written this in F# but it is using a helper function to reverse the list (I know this is in both ocaml and F# but i'm implementing everythin
<infoe> my code is here: http://codepad.org/7CF2vhMq
<infoe> and i have a suspicion that i could write this without the rev helper
<infoe> im curious if that suspicion is founded or unfounded
<yziquel_> R_NilValue is a symbol (global variable in libR.so, or rather, a global pointer). It gets initialised when the Rf_embeddedinit() function is launched, which starts up the R interpreter. What I want is val null : R.sexp that each time OCaml stumbles accross, it looks up the value of R_NilValue, and gives it to f.
<infoe> in F# the (|>) is a pipe defined as let: (|>) f g = g f
<yziquel_> I really dislike wrapping a constant with a type of unit -> R.sexp.
<infoe> not sure what that is in ocaml, but thats the whole reason why im doing these in both languages
<infoe> s/as let:/as: let/
<yziquel_> so I was wondering if purple magic as in Lazy might help.
<thelema> infoe: |> has the same definition in ocaml
<thelema> yziquel_: I don't see how lazy would help, because lazy is only evaluated once.
<thelema> Can you trigger some code to update a ref when R is done initializing?
<infoe> cool
<infoe> thelema: can this particular problem be solved without the rev helper?
<yziquel_> thelema: I could. I could also use React.signal. But that's sort of beside the point that it would be a pain to use OCaml to make R less "static"... Having NULL as a signal seems to me like "() might change value".
<thelema> infoe: you need one more [in]
<yziquel_> I really want to use OCaml to type R packages. If I leave the user the opportunity to change the value of NULL because it's a ref, I'm far offtrack.
<thelema> infoe: if you can stand the code not being tail recursive, you can drop the rev
<infoe> thelema: yes, one more [in] for ocaml... in F# the [in] is suplerfuous, i just threw it in there to look right for you guys but forgot the other one
<thelema> yziquel_: then you'll have to either go with [unit -> 'a] or an accessor function
<orbitz> yziquel_: is it possible you want to use 'a option and define a function to translate your option to a Nil value or the actual value?
<yziquel_> thelema: how is an unevaluated x () represented internally in OCaml.
<yziquel_> ?
<orbitz> yziquel_: it's just a function taking type unit
mrvn has quit [Read error: 110 (Connection timed out)]
c0m has joined #ocaml
<yziquel_> I guess I'll have to look into the source of the vm.
<infoe> thelema: in that code why would something like (xs' :: (x :: xs)) not work, for xs' i get expected 'a list but give 'a list list
<infoe> hm i think it makes sense actually nevermind
<thelema> yziquel_: [x ()] is instructions to take x and apply it to (). [x] is a function pointer, [()] is the integer 1
<yziquel_> thelema: thanks. i just noticed that the Lazy module contains much less OCaml than it used to...
<infoe> actually no it doesnt, why can the last element of a list point to the first of a list list, but not the other way around
<yziquel_> i was thinking of messing around like this.
<thelema> yes, lazy got integrated into the compiler for performance
<thelema> infoe: a :: b :: c requires that a and b have the same type foo, and c has type foo list.
ua has quit [Read error: 110 (Connection timed out)]
<infoe> alright
<thelema> yziquel_: I guess you could implement your own lazy that re-evaluates every time, but you'll end up with an accessor function - better to do it without so much magic
<infoe> so it is impossible to turn it around
<yziquel_> thelema: what do you mean by an accessor function?
<thelema> yziquel_: get_val null
<yziquel_> hmmm.. no. typing it is a constant is more important to me.
<yziquel_> s/is/as/
<c0m> anyone write a parser for pcf before in f#
<yziquel_> when the vm sees a forward tag, it just follows it to whatever it points to?
<thelema> I don't think so, but maybe...
<thelema> yziquel_: what value is forward tag?
<thelema> 250
<thelema> well, it's used for lazy values...
<yziquel_> 250
<thelema> Forward_tag: forwarding pointer that the GC may silently shortcut.
<thelema> the GC will magically change things from [forward_tag] to the value pointed to according to its fancy
<yziquel_> not good
<thelema> unless it's a float.
<yziquel_> thelema: you're right. cannot avoid the accessor function.
mrvn has joined #ocaml
ua has joined #ocaml
<mrvn> re
caligula__ has joined #ocaml
caligula_ has quit [Connection timed out]
Alpounet has quit [Read error: 60 (Operation timed out)]
Alpounet has joined #ocaml
ulfdoz has joined #ocaml
thrasibule has quit [Read error: 110 (Connection timed out)]
yetifoot has joined #ocaml
ulfdoz has quit [Read error: 110 (Connection timed out)]
ttamttam has joined #ocaml
yetifoot has left #ocaml []
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
thelema_ has joined #ocaml
orbitz_ has joined #ocaml
c0m_ has joined #ocaml
Mr_Awesome has quit [card.freenode.net irc.freenode.net]
BigJ has quit [card.freenode.net irc.freenode.net]
thelema has quit [card.freenode.net irc.freenode.net]
smimram has quit [card.freenode.net irc.freenode.net]
mal`` has quit [card.freenode.net irc.freenode.net]
peddie has quit [card.freenode.net irc.freenode.net]
svenl has quit [card.freenode.net irc.freenode.net]
c0m has quit [card.freenode.net irc.freenode.net]
r0bby has quit [card.freenode.net irc.freenode.net]
det has quit [card.freenode.net irc.freenode.net]
tab has quit [card.freenode.net irc.freenode.net]
eydaimon has quit [card.freenode.net irc.freenode.net]
orbitz has quit [card.freenode.net irc.freenode.net]
bacam has quit [card.freenode.net irc.freenode.net]
mehdid has quit [card.freenode.net irc.freenode.net]
diml has quit [card.freenode.net irc.freenode.net]
avysk has quit [card.freenode.net irc.freenode.net]
mattam has quit [card.freenode.net irc.freenode.net]
Ori_B has quit [card.freenode.net irc.freenode.net]
nimred has quit [card.freenode.net irc.freenode.net]
c0m_ is now known as c0m
tab has joined #ocaml
r0bby has joined #ocaml
peddie has joined #ocaml
nimred has joined #ocaml
Ori_B has joined #ocaml
bacam has joined #ocaml
mattam has joined #ocaml
mehdid has joined #ocaml
eydaimon has joined #ocaml
ikaros has joined #ocaml
det has joined #ocaml
mal`` has joined #ocaml
BigJ has joined #ocaml
diml has joined #ocaml
Yoric[DT] has joined #ocaml
svenl has joined #ocaml
Mr_Awesome has joined #ocaml
smimram has joined #ocaml
ygrek has joined #ocaml
_zack has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
dmentre has joined #ocaml
ikaros has quit ["Leave the magic to Houdini"]
verte has joined #ocaml
ua has quit [Read error: 113 (No route to host)]
Ched has quit [Read error: 148 (No route to host)]
ygrek has quit [Remote closed the connection]
rwmjones-afk is now known as rwmjones
ua has joined #ocaml
Yoric has joined #ocaml
avysk has joined #ocaml
Pimm has joined #ocaml
Yoric has quit []
_andre has joined #ocaml
ygrek has joined #ocaml
<Camarade_Tux> woot, I can probably actually use ocamlnet's equeue-gtk2 instead of dbus-glib \o/
<Camarade_Tux> (which means I won't have to make the bindings for dbus-glib right now :)
<flux> :)
<flux> it's nice to be able to reuse code, it's always less code to write :)
<flux> (well, unfortunately not always..)
<Camarade_Tux> plus the interface should be better :)
<Camarade_Tux> I'm still commited to ocaml-gir but the part using libffi is annoying to write :P (like if this type is X bytes then, else if it is Y bytes then, else if it is Z bytes then...)
<Camarade_Tux> (hmm, I don't have an omega here ='( )
Snark has joined #ocaml
Modius_ has quit [Read error: 104 (Connection reset by peer)]
Modius_ has joined #ocaml
albacker has joined #ocaml
valross has quit [Remote closed the connection]
Yoric has joined #ocaml
schme has quit [Read error: 110 (Connection timed out)]
schme has joined #ocaml
verte has quit ["~~~ Crash in JIT!"]
ski_ has quit ["Lost terminal"]
mishok13 has joined #ocaml
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
Alpounet has quit [Read error: 110 (Connection timed out)]
Yoric has quit []
flux has quit [Remote closed the connection]
flux has joined #ocaml
c0m has quit [Read error: 110 (Connection timed out)]
flux has quit [Remote closed the connection]
flux has joined #ocaml
kaustuv has joined #ocaml
_zack has quit ["Leaving."]
orbitz_ has quit [Client Quit]
orbitz has joined #ocaml
zhijie has quit ["Leaving."]
elanonimo has joined #ocaml
zhijie has joined #ocaml
<thelema_> Can someone here help me test godi-aaa-batteries?
thelema_ is now known as thelema
zhijie has quit [Remote closed the connection]
ygrek has joined #ocaml
Yoric has joined #ocaml
flx has joined #ocaml
flux has quit [Read error: 104 (Connection reset by peer)]
flx is now known as Guest89849
_zack has joined #ocaml
ikaros has joined #ocaml
zhijie has joined #ocaml
yziquel_ has quit [Ping timeout: 180 seconds]
Yoric has quit []
Guest89849 has quit [Remote closed the connection]
flux has joined #ocaml
flux has quit [Remote closed the connection]
flux has joined #ocaml
Alpounet has joined #ocaml
flux has quit [Remote closed the connection]
<thelema> First tarball of aaa-batteries released - get at http://github.com/thelema/AAA-batteries/downloads
Pimm has quit [Read error: 60 (Operation timed out)]
<Alpounet> yaaaaaaay
<Alpounet> cheers thelema
* thelema waits for the angry mob to storm his lab for releasing such a piece of junk that doesn't work anywhere.
<albacker> i think this might help us all
* Alpounet un-taring the archive
<Alpounet> thelema, it may take some time. I have a very minimal ocaml environment here on my arch
flux has joined #ocaml
* thelema wonders if aaa-batteries even depends on ocamlnet
<thelema> camlzip is included in aaa-batteries, under libs/camlzip
<thelema> it's even patched to use findlib.
<Alpounet> thelema, should I build camlzip from there ?
<thelema> if it's convenient
<Alpounet> if it's in my packages I won't
<Alpounet> it'd be great to have a version shipping all the dependencies with it
* Alpounet running omake
<thelema> The right way to do that would be the ocaml community distribution - merging all of this into the ocaml source tree
<thelema> oh yeah, there's no install-doc yet - I've not written that.
<Alpounet> hmm
<Alpounet> Fatal error: exception Failure("hdoc/AvlTree.html: No such file or directory")
<Alpounet> it explains that :-)
<thelema> huh, hdoc/AvlTree.html is output... I dunno what it'd be needed for
Submarine has joined #ocaml
<Alpounet> hmm
<Alpounet> it's in the "doc" target, or seems to be
<thelema> ok, I'll loook into that.
<thelema> ah, doc should require all
<thelema> but this isn't sufficient...
* Alpounet running 'omake all install' for the moment
<Alpounet> ok, looks fine
<thelema> ok, the directory hdoc/ must exist
<Alpounet> I only have doc/
<thelema> mkdir hdoc
<thelema> I'm adding this to the OMakefile
Pimm has joined #ocaml
<Alpounet> it'd be great to register batteries @ ocamlfind
dmentre has quit ["Leaving."]
<thelema> @ ocamlfind?
<thelema> aaa installs with ocamlfind
<Alpounet> oh yeah right
<Alpounet> I mistyped :x
<Alpounet> thelema, with hdoc/ created, the doc target runs fine
<Leonidas> I seem to be unable to use the 'when' clause in 'match'. I'm reading the ORA book as well as some random site on the internet about it, but I can't get it to work, ocaml complains about the syntax.
<Alpounet> Leonidas, paste your code.
<thelema> Leonidas: match 3 with x when x mod 2 = 1 -> "odd" | _ -> "even"
<thelema> you just need another |
<Leonidas> ahh, I'm blind!
<Alpounet> :)
<thelema> brb after lunch
<Leonidas> thelema: thank you. I was already thinking whether the ORA book covering ocaml 2 is outdated :)
kaustuv has quit [Read error: 113 (No route to host)]
eydaimon has quit [Read error: 60 (Operation timed out)]
eydaimon has joined #ocaml
Mr_Awesome has quit [Read error: 60 (Operation timed out)]
<Alpounet> thelema, except install-doc, the build & install are just fine
<thelema> excellent. Hopefully I can get the docs online - I'm wrestling with github pages now
<Alpounet> heh
<Alpounet> good luck
<thelema> online docs should be a good 90% solution
<thelema> ok, omake now merged into aaa core
<thelema> yay, somehow it just figured out about the new page, and should be online in 10 min.
_zack has quit ["Leaving."]
Modius_ is now known as Modius
ttamttam has quit ["Leaving."]
ikaros has quit [Read error: 104 (Connection reset by peer)]
ulfdoz has joined #ocaml
Ched has joined #ocaml
_unK has joined #ocaml
<hcarty> thelema: Congratulations on a first release!
<thelema> hcarty: thanks. I've still got a lot of polishing to get it anywhere near the quality of batteries
<hcarty> thelema: Should aaa be installable alongside Batteries?
<thelema> yes.
<hcarty> I'll give it a try as well then
<thelema> they're not usable together - they both provide a module called Batteries
mishok13 has quit [Read error: 110 (Connection timed out)]
<thelema> but they install completely in parallel
<thelema> hcarty: I appreciate any feedback on installation.
<thelema> doc and doc-install don't work in the .0 tarball - I'll likely put a .1 tarball out in a bit.
<thelema> once I get doc-install working
ikaros has joined #ocaml
<hcarty> "omake all" and "omake install" for now?
<thelema> yes
<hcarty> Well, that's certainly a quick build :-)
<thelema> yup. doc building takes about the same time.
* thelema is surprised by omake's efficiency
jcaose has joined #ocaml
* Alpounet too
<thelema> hmm, omake says it 's failing to install, but it seems to succeed
<Alpounet> hcarty, to have the 'doc' target working you just need to do a 'mkdir hdoc' before running 'omake doc'
<hcarty> Alpounet: Thanks for the tip
<Alpounet> that's what thelema added in the .1
<thelema> I plan on install-doc and tests as well in .1
<Alpounet> great
<hcarty> thelema: I see references to IO - is the IO system in aaa?
<thelema> yes
<hcarty> thelema: Hooray! :-)
<thelema> The print system requiring camlp4 magic isn't in aaa.
<thelema> but the base IO system has been good enough for me.
<hcarty> thelema: .0 builds and installs cleanly here (GODI, OCaml 3.11.1, 64bit, Ubuntu 9.10)
<thelema> hcarty: I assume you didn't use godi to install it, right?
<hcarty> The camlp4'd print system is very nice, but it still needs polish
<hcarty> thelema: Correct. I omake'd it directly.
<hcarty> thelema: I can try with the godiva spec file as well
<thelema> hcarty: thank you for any and all bug reports you have. If you don't get a quick response from me here, put suggestions here: http://github.com/thelema/AAA-batteries/issues
<thelema> hcarty: I know nothing about godiva - everything non-obvious was made up.
<hcarty> thelema: Are you opposed to, at some later point, adding back the camlp4 magic pieces as optional and not-on-by-default components?
<hcarty> thelema: Or would you prefer for all camlp4 to remain separate from aaa?
<thelema> maybe.
<hcarty> I understand if that's the case. It looks like you have a very nice start here.
<thelema> If batteries never resurrects, there's room in aaa for *very optional* camlp4
<thelema> but I hope someone takes batteries and carries its torch.
<thelema> Just not me.
Pimm has quit [Read error: 110 (Connection timed out)]
<thelema> one note: threads are required for aaa
Mr_Awesome has joined #ocaml
zhijie has quit [Remote closed the connection]
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
Pimm has joined #ocaml
ua has quit [Read error: 113 (No route to host)]
<mfp> thelema: I'm going to look into the syntax extensions. I think that buildind and installing them as separate packages (aaa.estring.syntax, etc.) shouldn't be too hard.
<mfp> I actually had that running in my original build sys for Batteries (full)
<mfp> gildor: is the RSA fingerprint of git.ocamlcore.org d8:87:7f:b3:0c:fc:ef:ea:79:e5:23:64:b9:db:02:00 ? (got a man-in-the-middle warning)
ttamttam has joined #ocaml
BigJ has quit [Read error: 110 (Connection timed out)]
Modius has quit ["I'm big in Japan"]
_JusSx_ has joined #ocaml
_JusSx_ has quit [Client Quit]
_andre has left #ocaml []
_andre has joined #ocaml
BigJ has joined #ocaml
_andre has quit ["leaving"]
Modius has joined #ocaml
ttamttam1 has joined #ocaml
ua has joined #ocaml
ttamttam has quit [Read error: 110 (Connection timed out)]
Snark has quit ["Ex-Chat"]
gdmfsob has quit [Read error: 110 (Connection timed out)]
Submarine has quit ["Leaving"]
slash_ has joined #ocaml
BigJ2 has joined #ocaml
jcaose has quit [Read error: 110 (Connection timed out)]
<gildor> mfp: 2048 d8:87:7f:b3:0c:fc:ef:ea:79:e5:23:64:b9:db:02:00 /etc/ssh/ssh_host_rsa_key.pub (RSA)
_JusSx_ has joined #ocaml
maskd has quit [Read error: 110 (Connection timed out)]
Narrenschiff has joined #ocaml
Honeyman has joined #ocaml
ttamttam1 has quit ["Leaving."]
<Honeyman> Hello. I am trying to compile a native code .so library from .ml source, but this .ml source uses a different OCaml library. I tried to add that different.cmxa to the list of arguments to ocamlopt, but still failed to build the .so library. Am I right assuming that it is impossible?
<thelema> it should be possible to compile code that uses libraries into a .so
<thelema> I just don't know how. I don't need to build shared objects much
<Honeyman> I found the page http://alturl.com/83ov where someone says "In byte-code libraries can contains libraries, but not in native code"...
<Honeyman> My general task is even more complex - to make a Python binary module from OCaml code, using Pycaml. So my ocaml module uses "open Pycaml" and has to be compiled with Pycaml.cmxa to the native code, and has to become the .so file to be usable from Python... and here the problems start.
ulfdoz has quit [Read error: 110 (Connection timed out)]
<thelema> ok, maybe you can't.
<Honeyman> I guess I am on my own with the particular Python stuff, but suppose that someone should definitely be more knowledgeable in compiling OCaml to the native code, provided that I have about 3 days of experience in ocaml.
ygrek has quit [Remote closed the connection]
albacker has quit ["Leaving"]
yziquel has joined #ocaml
<yziquel> type t;; module A = struct type t = t end;; Error: The type abbreviation t is cyclic. What workaround is there for that specific issue?
<mrvn> yziquel: type t; type a_t = t; module A = struct type t = a_t end;;?
<yziquel> ugly. ok. thanks.
<thelema> yes, it's a bit troublesome.
<mrvn> In C++ you would use ::t but I don't think ocaml has that
<mrvn> type t = .t
<thelema> .t?
<yziquel> type t = .t would be great...
<mrvn> the t from outside the current module
<mrvn> yziquel: if the file is called foo.ml does type t = Foo.t work?
<yziquel> module A = struct type t module B = struct type t = A.t end end
<yziquel> gives Error: Unbound type constructor A.t
<thelema> A.t only has meaning outside A. just rename the type.
<mrvn> module A = struct type t end include A module B = struct type t = A.t end
<thelema> it's only a bit ugly, and generally rare
<mrvn> I guess one should always write type foo = .... type t = foo
<mrvn> i.e. give it a propper name and only abreviate it for outside use.
<yziquel> not that rare: suppose you have an ugly with lots of things you want to hide. But you also want a Debug submodule at the end of your module recapitulating what you might want as useful debugging tools in a toploop.
<yziquel> an ugly -> an ugly module
<mrvn> yziquel: then you write type ugly = .... type t = ugly module B = struct type t = ugly end
<yziquel> mrvn: i'd rather go with module A = struct type t module Debug = struct type debug_t = t type t = debug_t end end
<yziquel> at least you keep the nastiness where it belongs, and it becomes idiomatic.
<mrvn> works too
munga_ has joined #ocaml
Pimm has quit ["Ik ga weg"]
_JusSx_ has quit ["leaving"]
munga_ has quit [Read error: 148 (No route to host)]
Narrenschiff has quit []
BigJ2 has quit [Read error: 110 (Connection timed out)]
Honeyman has quit ["õÈÏÖÕ Ñ ÏÔ ×ÁÓ (xchat 2.4.5 ÉÌÉ ÓÔÁÒÛÅ)"]
Pimm has joined #ocaml
slash_ has quit [Client Quit]
_unK has quit [Read error: 104 (Connection reset by peer)]
olegfink has joined #ocaml