kaustuv 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
julm has joined #ocaml
sporkmonger has joined #ocaml
ched__ has joined #ocaml
ched_ has quit [Read error: 110 (Connection timed out)]
pizza_ has joined #ocaml
<pizza_> are forward declarations to types ok where types may be mutually recursive?
<Smerdyakov> There are no forward declarations of any kind in OCaml. There are only forms for mutually-recursive definitions.
<pizza_> ok, let me read up
mfp_ has joined #ocaml
mfp has quit [Read error: 110 (Connection timed out)]
sporkmonger has quit [Read error: 104 (Connection reset by peer)]
sporkmonger has joined #ocaml
Alpounet has quit [Remote closed the connection]
julm has quit [Read error: 60 (Operation timed out)]
julm has joined #ocaml
johnnowak has joined #ocaml
johnnowak has quit []
<pizza_> Smerdyakov: thanks, i seem to have it figured out
komar_ has quit [Read error: 60 (Operation timed out)]
komar_ has joined #ocaml
spez has quit []
sciendan has joined #ocaml
Associat0r has quit []
Associat0r has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
ikaros has joined #ocaml
mgodshall has quit [Read error: 60 (Operation timed out)]
ikaros has quit ["Leave the magic to Houdini"]
Camarade_Tux has joined #ocaml
ulfdoz has joined #ocaml
ulfdoz has quit [Read error: 110 (Connection timed out)]
sgnb` has quit [Read error: 54 (Connection reset by peer)]
sgnb` has joined #ocaml
hkBst has joined #ocaml
_zack has joined #ocaml
sgnb` has quit [Read error: 104 (Connection reset by peer)]
sgnb` has joined #ocaml
jeanbon has joined #ocaml
_zack has quit ["Leaving."]
munga_ has joined #ocaml
sgnb` is now known as sgnb
sgnb has quit [Read error: 104 (Connection reset by peer)]
sgnb has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> h
<Yoric[DT]> hi
<det> Hi
_zack has joined #ocaml
johnnowak has joined #ocaml
ulfdoz has joined #ocaml
Associat0r has quit []
munga_ has quit [Remote closed the connection]
verte has joined #ocaml
verte_ has joined #ocaml
verte has quit [Nick collision from services.]
verte_ is now known as verte
ched__ is now known as Ched
johnnowak has quit [Remote closed the connection]
johnnowak has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
authentic has left #ocaml []
authentic has joined #ocaml
authentic has quit [Client Quit]
authentic has joined #ocaml
Amorphous has quit [Connection timed out]
Amorphous has joined #ocaml
authentic has left #ocaml []
authentic has joined #ocaml
Snark has joined #ocaml
Yoric has joined #ocaml
Ppjet6_ has joined #ocaml
Ppjet6_ has quit [Remote closed the connection]
johnnowak has quit [Remote closed the connection]
johnnowak has joined #ocaml
_zack has quit ["Leaving."]
_zack has joined #ocaml
_andre has joined #ocaml
Yoric has quit [Remote closed the connection]
bombshelter13_ has joined #ocaml
Snark has quit ["Ex-Chat"]
johnnowak has left #ocaml []
spez has joined #ocaml
mrvn has left #ocaml []
Spiwack has joined #ocaml
oriba has joined #ocaml
verte has quit [Read error: 110 (Connection timed out)]
julm has quit [Read error: 104 (Connection reset by peer)]
julm has joined #ocaml
ulfdoz has quit [Read error: 60 (Operation timed out)]
nominolo has joined #ocaml
<nominolo> hm, how is "type foo = [ Bar | Baz ]" different from "type foo = Bar | Baz" ?
<hcarty> nominolo: I don't think the first is valid
<nominolo> well, apparently this line compiles: "type 'a monotype_ = [ mono_var | ('a monotype_, 'a) sconstr]"
<nominolo> (it's from the MLF typechecker)
<hcarty> It may be revised syntax
ulfdoz has joined #ocaml
<hcarty> Written in revised syntax, that is
<hcarty> "type foo = [ Bar | Baz ]" in revised syntax = "type foo = Bar | Baz" in standard/original syntax
<nominolo> is there an official syntax for OCaml? A quick Google search didn't show up anything interesting
<hcarty> The standard syntax is the most commonly used
<hcarty> But there are users of the revised syntax. A lot of OCaml itself seems to be in revised syntax.
<nominolo> hcarty: ah, I see. thanks
<hcarty> You're welcome - I hope it was reasonably clear :-) I haven't used the revised syntax much.
<hcarty> nominolo: In that example, it may be using polymorphic variants. The type definition is not in revised syntax.
<hcarty> nominolo: For example - http://ocaml.pastebin.com/d4ef1ce19
ikaros has joined #ocaml
sgnb has quit [hubbard.freenode.net irc.freenode.net]
<hcarty> Any suggestions to name a function which takes a gzip-ed file, extracts it to a temporary location, runs a given function, then deletes the temporary file? I'm thinking one of gunzip_in, gunzip_with or with_gunzip_in (in the spirit of Batteries.File.with_open_in).
<hcarty> s/suggestions to/suggestions for how to/
<hcarty> Something like "gunzip_with (fun () -> some_func tmp_file) ~target:tmp_file gzip_file"
mrvn has joined #ocaml
ulfdoz has quit [Read error: 60 (Operation timed out)]
<palomer> I don't see how monotype is syntactically correct
<palomer> mono_var is not a uid
<hcarty> palomer: If mono_var is defined as something like "type mono_var = [ `Foo ]" then I think it would be ok
_zack has quit ["Leaving."]
<palomer> but where's the constructor name then?
<nominolo> hcarty: ok, I see, they use polymorphic variants
<julm> palomer: see http://caml.inria.fr/pub/docs/manual-ocaml/types.html#variant-type : "tags may be either specified directly in the `tag-name […] form, or indirectly through a type expression. In this last case, the type expression must expand to an exact variant type, whose tag specifications are inserted in its place."
sgnb has joined #ocaml
willb has quit [Read error: 110 (Connection timed out)]
oriba has quit ["Verlassend"]
ulfdoz has joined #ocaml
Snark has joined #ocaml
komar_ has quit [Read error: 54 (Connection reset by peer)]
komar_ has joined #ocaml
willb has joined #ocaml
Associat0r has joined #ocaml
<palomer> julm, whoa!
<palomer> that's awesome
* palomer wish he knew
<julm> palomer: it has some limitations though: for instance type t = [`A] and s = [t | `B] does not work; see Jacques Garrigue's comment here: http://caml.inria.fr/mantis/view.php?id=4494#bugnotes
<palomer> I thought it was for "exact variant types"
<palomer> not polymorphic variants
<julm> ah
mgodshall has joined #ocaml
Spiwack has quit ["Leaving"]
itewsh has joined #ocaml
yziquel has joined #ocaml
<yziquel> anybody familiar with c++?
<yziquel> struggling on a binding...
<Smerdyakov> I once wrote a few C++ programs. :)
<Smerdyakov> There's maybe a 25% chance that I can answer a C++ arcana question.
<yziquel> ok. i'll prepare the pastie...
<yziquel> Smerdyakov: that's the error that i do not understand.
alexyk has joined #ocaml
<alexyk> greetings -- I had a working ocamlmklib line on Mac OSX, now on Linux it complains thusly: /opt/portage/usr/lib/gcc/x86_64-pc-linux-gnu/4.2.4/../../../../x86_64-pc-linux-gnu/bin/ld: /home/alexyk/s/src/srilm/current/lib/x86_64/liboolm.a(Vocab.o): relocation R_X86_64_32 against `Vocab::compare(unsigned int, unsigned int)' can not be used when making a shared object; recompile with -fPIC
<Smerdyakov> yziquel, oh, that looks simple.
<alexyk> I recompiled each file in liboolm with -fPIC and still get that.
<Smerdyakov> yziquel, you are calling a function with an argument of the wrong type.
<Smerdyakov> yziquel, the formal and actual types are included in the error message.
<Smerdyakov> yziquel, "analysis&" is a by-reference version of an "analysis."
<Smerdyakov> yziquel, the actual supported type is an iterator to values of that type, rather than just a single value.
<alexyk> can ocamlmklib take an .a or should I make it .so?
<yziquel> alexyk: i use this to make a (weird) library: http://paste.lisp.org/display/82503
<yziquel> Smerdyakov: looking into this...
Snark has quit ["Ex-Chat"]
<alexyk> yziquel: intersting, but not using ocamlmklib
break has joined #ocaml
<yziquel> alexyk: not? ocamlmklib -o freeling_stubs freeling_wrap.cxx.o
<alexyk> yziquel: I mean with other libs
<yziquel> alexyk: what are you trying to do?
<break> can anyone explain the error listed here? http://ocaml.pastebin.com/d4bf3ea4e
<alexyk> yziquel: the relocation error on Linux came from this line which worked on OSX: ocamlmklib -lstdc++ -L/home/alexyk/s/src/srilm/current/lib/x86_64 -loolm -lmisc -ldstruct -lm lmclient_stubs.o generate.o -o lmclient
<yziquel> break: a parenthesis around n-1'
<yziquel> ?
<alexyk> so I recompiled everything in those -libs and my .o files with -fPIC and I still get a relocation error for -loolm
<break> yziquel: thanks
<break> so foo n-1 evaluates to (foo n)-1 ?
<hcarty> break: Yes
<hcarty> break: And you could, if you wanted, drop the ( ) around range, "n :: range (n - 1)", and it would work properly.
<break> ok, how do i reorder: n :: range (n-1) to produce the reverse list? range(n-1) :: [n] doesn't work
<yziquel> break: won't work.
<yziquel> break: range(n-1) is a list.
<mrvn> break: @, but you rather want to List.rev at the verry end.
<yziquel> break: range(n-1)::whatever will therefore be a list of list.
<break> okey dokey, thanks guys
<mrvn> break: or change range x to range acc x and call range (n :: acc) (n - 1)
<mrvn> break: and return acc at the end. I think that gives you your order.
<yziquel> Smerdyakov: I'm troubled. this code comes from swig... wondering why it's typing things so badly...
<break> wow, :: not being able to take a list on the left side really sucks, i'm used to erlang's ++
<mrvn> break: :: can take a list on the left side. It just isn't what you mean
<hcarty> break: ++ may be equivalent to @ in OCaml?
<break> ah let me check
<mrvn> [1;2;3] @ [4;5;6]
<yziquel> wasn't there an ocaml bot ?
<break> that's the ticket
<hcarty> yziquel: A few, but I don't think any are alive at the moment.
<mrvn> break: but never use that in a recursion.
<break> mrvn: why not?
<mrvn> break: it copies the first list.
<yziquel> break: blows up the number of concatenations...
<break> hmm, a functional language where you can't use list concatenation and recursion, interesting
<mrvn> Ist @ even tail recursive?
<break> i must be missing something
<mrvn> break: lists are not mutable. To attach the [4;5;6] to the 3 it needs to create a new list cell, write in 3 and attache the list. Then go back to 2, then 1.
<yziquel> [a]@list_n takes n operations, [b]@[a]@list_n thakes n + (n+1)...
<yziquel> and n + (n+1) isn't exactly 2...
<palomer> [a]@list_n takes 1 operation me thought
<mrvn> break: @ recurses down the first list and then does x :: list on the way back
<mrvn> yziquel: ^^^
<palomer> list_n@[a] takes n operations
<yziquel> palomer: whatever your laterality...
<mrvn> [a]@list_n and a::list_n are equivalent in O()
<break> my ultimate goal here is to generate a list of combinations given an input list, can anyone recommend the canonical method of doing this in OCaml?
<mrvn> list_n @ [a] is the evil one.
<mrvn> break: like [1;2;3] gives []; [1]; [2]; [3]; [1;2] [1;3] [2;3] [1;2;3]?
<break> mrvn: that's permutations, but the right idea
<mrvn> then what do you mean by combinations?
<Smerdyakov> break, that's one of my favorite FP challenge questions. :)
<break> Smerdyakov: do you have an implementation handy in OCaml?
<palomer> let rec comb = function x :: xs -> comb xs @ (List.map (fun y -> x :: y) comb xs) or something
<Smerdyakov> break, let me first check that you mean what I think you mean: consider every way of dropping zero or more elements from the list, leaving the remaining elements in the original order. Is that it?
<break> palomer: i've heard that using @, lists and recursion was a bad thing
alexyk has quit []
<mrvn> Smerdyakov: no, that was my example.
<palomer> recursion is evil; you should never use it.
<mrvn> hehe
<break> at this point anything that works is an improvement, i can work with it
<Smerdyakov> mrvn, oh. Your example definitely wasn't permutations, so we have a terminology problem. :)
<Smerdyakov> break, I think no one here yet knows what you mean by "combinations."
<break> i'll just do it in another language, thanks guys
<mrvn> With combinations I would think [1;2] [a;b] gives[(1,a), (1,b); (2,a); (2,b)]
<yziquel> break: you should really try to do it in ocaml...
<break> yziquel: every time i try to use OCaml it seems to get in the way
<yziquel> break: it's a good way to see that you think more but program less...
<palomer> shakespearlang is probably more efficient
<yziquel> break: it gets in the way because you're not used to it yet.
<break> maybe not, but i've been able to pick up and write small but non-trivial stuff using other functional languages within a few days or so of playing with them
<mrvn> break: unless you explain what you want to do nobody can help you
<palomer> erlang's probably better for this, or fortran
<hcarty> palomer: That's an interesting pair of language recommendations :-)
<palomer> :P
alexyk has joined #ocaml
Yoric[DT] has joined #ocaml
break has quit [Read error: 54 (Connection reset by peer)]
middayc has joined #ocaml
break has joined #ocaml
<middayc> hi .. I have one question .. is there any way one could serialize a closure or function in ocaml - send it over socket for example, deserialize and run it on the other end?
alexyk has quit [Read error: 54 (Connection reset by peer)]
<Smerdyakov> Yes, I think you can do it with [Marshal], so long as the binaries on the two endpoints match exactly.
<mrvn> not type save though
<Yoric[DT]> 'evening
<Yoric[DT]> iirc, there are several type-safe libraries for doing this, well, better.
<Yoric[DT]> I don't know if they support closures, though.
alexyk_ has joined #ocaml
<mrvn> If this must work with different versions of you code or different architectures then better design a proper network protocol for it.
<middayc> you mean they have to be exactly the same program when you compile it?
itewsh has quit [Read error: 60 (Operation timed out)]
<mrvn> middayc: worst case yes
itewsh has joined #ocaml
<mrvn> and I don't think there is much of a best case
<mrvn> I think Marshal just stores the address of a function. So if the other side has something else at that addres: *BOOM*
<Yoric[DT]> middayc: not only the same program -- also the same build.
<Yoric[DT]> (I actually don't know what is hashed, though)
<middayc> maybe I better describe the use case (I don't fully get the "proper network protocol" .. I am newbie in OCaml btw) .. A server app holds a list of values .. c
<middayc> client sends over a serialized function that server uses in List.filter and returns the list of values it got..
<palomer> sexplib doesn't support closures
<palomer> in fact, sexplib doesn't even support objects in any wa
<palomer> y
<mrvn> palomer: objects have closures.
<mrvn> middayc: bytecode or binary?
<middayc> would something like this be possible .. I imagine not because then OCaml would have to be interpreter or JIT .. but I think I saw once here that someone sends closures around .. and I am not the expert anyway
<mrvn> In bytecode you can send source and let the server compile and run that.
<mrvn> But imagine if a client sends system("rm -rf /")
<middayc> mrvn: I don't care what it is .. as long as it get's executed on the other side
<middayc> mrvn: yes , this is whole another story :)
alexyk_ has quit []
<middayc> but first I want to know if it's possible at all ... are there any docs where I could look into to learn more about the bytecode serialisation option?
<mrvn> it certainly is possible. Even simple in bytecode.
<mrvn> middayc: you wouldn't serialize the function, you send a string containing the source.
<mrvn> middayc: e.g. "fun x -> even x" which would then return all even numbers from your list.
<middayc> that is not a problem .. I do the same now in some interpreted language..
* palomer wonders if you can do this with dynlink
<mrvn> palomer: take string, ocamlopt it, linky object?
<middayc> does ocaml have some sort of "eval( )" if I borow from javascript?
<mrvn> middayc: bytecode has but don't ask me how it is called
<Yoric[DT]> mrvn: I'm pretty certain it doesn't.
<middayc> ok.. I will find it .. thanks a lot for giving me the info !
<mrvn> Yoric[DT]: bytecode can run a toplevel
<Yoric[DT]> mrvn: fair enough.
<Yoric[DT]> In that case, it's in module [Toploop].
<middayc> yes, that was my blink of hope too :)
<middayc> Thanks, I will look into Toploop
mfp_ is now known as mfp
<mfp> middayc: there's a bytecode interpreter written in OCaml (a bit slower than the C one) in CDK
<mrvn> to send over java bytecode?
<mfp> mrvn: OCaml bytecode
<mfp> http://pauillac.inria.fr/cdk/newdoc/htmlman/cdk_46.html "This library provides two functionnalities: 1. It provides a [Dynlink] module, that can be used in native-code programs to load byte-code modules during execution. 2. It allows you to eval Objective-Caml expressions inside any Objective-Caml program. "
Associat0r has quit []
ccasin has joined #ocaml
alexyk has joined #ocaml
<palomer> mrvn, right
<middayc> hm.. I can't get to anything like docs for Toploop through google .. the most informative mention is this http://alan.petitepomme.net/cwn/2004.04.13.html
psnively has joined #ocaml
<middayc> I haven't heard of CDK yet .. I will look into that too .. thanks :)
psnively has left #ocaml []
Yoric[DT] has quit ["Ex-Chat"]
Associat0r has joined #ocaml
Yoric[DT] has joined #ocaml
_zack has joined #ocaml
<hcarty> Are there other programming languages which have type inference which is as pervasive as OCaml? I'm not sure if that is the right way to put this...
<hcarty> SML looks like it does.
<Smerdyakov> I don't understand thr question.
<hcarty> Smerdyakov: I'm not sure of the proper way to ask. In OCaml, type annotations seem to be rare.
<Smerdyakov> It's definitely the same in SML. In both cases, they are all over module signatures.
<hcarty> But in the Haskell examples I've seen, almost all functions have a type annotation to go along with them.
<Smerdyakov> Haskell has this weird tradition of including annotations for new identifiers, but I don't think it's at all necessary.
<hcarty> Smerdyakov: Ok, thanks. I thought it was odd. The enjoy the lack of required annotations in OCaml (beyond, as you said, module signatures when desired).
<hcarty> s/The/I/
<mrvn> hcarty: and those I always generate with ocamlc
<middayc> mfp: I was looking CDK. Does this mean that whole app has to be "compiled" with this bytecode interpreter or that a regular OCaml program can use CDK as a libraray to eval bytecode? I couldn't find anything about toploopl yet .. only some reference to ocaml_toploop_print somewhere but no .._eval .._run .. or anything similar
<hcarty> mrvn: Indeed. "ocamlc -i" was a wonderful discovery when I started learning OCaml.
<palomer> also, haskell has a strange restriction on generalizing variables...I forget what it's called
<palomer> so often you're forced to annotate your function if you want some variables to generalize
alexyk has quit []
<palomer> it's called "the monomorphism restriction"
ikaros has quit [Read error: 110 (Connection timed out)]
itewsh has quit [Read error: 110 (Connection timed out)]
itewsh has joined #ocaml
<Yoric[DT]> middayc: the CDK is dead
<palomer> just use straight dynlink
oriba has joined #ocaml
<Yoric[DT]> To use the toploop from a bytecode program, you don't need dynlink.
<Yoric[DT]> Otoh, you need to be a little creative with Lexing.
middayc_ has joined #ocaml
itewsh has quit [Read error: 110 (Connection timed out)]
itewsh has joined #ocaml
itewsh has quit [Read error: 60 (Operation timed out)]
itewsh has joined #ocaml
nominolo has quit ["leaving"]
middayc has quit [Read error: 110 (Connection timed out)]
yziquel has left #ocaml []
<hcarty> The revised error messages in 3.11.1 seem rather nice.
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
ccasin has quit ["Leaving"]
<palomer> type error messages?
<hcarty> palomer: Yes, though there may be others as well. The type error change is the main one I've noticed.
<hcarty> ocamlbuild still doesn't have .cmxs support though, which is unfortunate. I'd like to try out the native code toplevel.
slash_ has joined #ocaml
Smerdyakov has quit [Remote closed the connection]
bombshelter13_ has quit []
Smerdyakov has joined #ocaml
_andre has quit ["*puff*"]
willb has quit [Read error: 110 (Connection timed out)]
_zack has quit ["Leaving."]
hkBst has quit [Read error: 104 (Connection reset by peer)]
Lomono_ has joined #ocaml
willb has joined #ocaml
Lomono has quit [Read error: 60 (Operation timed out)]
Lomono_ has quit ["Don't even think about saying Candlejack or else you wi"]
Lomono has joined #ocaml
<palomer> julm, you around?
<julm> palomer: here
jeddhaberstro has joined #ocaml
<Yoric[DT]> hcarty: there's a vague beginning of support for .cmxs in Batteries' myocamlbuild.ml .
slash_ has quit [Client Quit]
ccasin has joined #ocaml
<Associat0r> wow have you guys seen the new http://haskellconcrete.com syntax
ulfdoz has quit [Read error: 110 (Connection timed out)]
<palomer> har har
Yoric[DT] has quit ["Ex-Chat"]
tab has quit [Read error: 60 (Operation timed out)]
tab has joined #ocaml
lutter has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]