gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
olle has quit [Ping timeout: 246 seconds]
sepp2k1 has quit [Read error: Connection reset by peer]
cdidd has quit [Ping timeout: 272 seconds]
cdidd has joined #ocaml
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 260 seconds]
ulfdoz_ is now known as ulfdoz
madroach has quit [Ping timeout: 265 seconds]
madroach has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
leoncamel has joined #ocaml
BiDOrD has joined #ocaml
BiDOrD_ has quit [Ping timeout: 264 seconds]
leoncamel has quit [Remote host closed the connection]
ankit9 has joined #ocaml
Fnar has joined #ocaml
cdidd has quit [Ping timeout: 245 seconds]
cdidd has joined #ocaml
thomasga has joined #ocaml
zorun has quit [Ping timeout: 268 seconds]
ftrvxmtrx has quit [Quit: Leaving]
djcoin has joined #ocaml
olle has joined #ocaml
olle has quit [Client Quit]
f[x] has quit [Ping timeout: 245 seconds]
ftrvxmtrx has joined #ocaml
cago has joined #ocaml
mika1 has joined #ocaml
ocp has joined #ocaml
pango is now known as pangoafk
targetron has quit [Ping timeout: 248 seconds]
targetron has joined #ocaml
chambart has joined #ocaml
ontologiae has joined #ocaml
Ptival has quit [Quit: Lost terminal]
cago has quit [Read error: Connection reset by peer]
cago has joined #ocaml
f[x] has joined #ocaml
osa1 has joined #ocaml
lusory has joined #ocaml
braibant has quit [Remote host closed the connection]
cicero321 has joined #ocaml
<cicero321> hi
Ptival has joined #ocaml
<cicero321> a question on putting together ocaml and c via camlidl
<cicero321> is it ok if mli file contains to declarations for a function with the same name?
<cicero321> for example, I'm struggling with z3 library, and it's somehow alarming that z3.mli contains both
<cicero321> external mk_context : config -> context
<cicero321> = "camlidl_z3V3_Z3_mk_context"
<cicero321> and external mk_context: (string * string) list -> context = "caml_z3_mk_context"
<cicero321> thoughts? thank you!
<f[x]> aren't they in different (nested) modules?
<f[x]> if not - last definition wins
<cicero321> both are in the same module. thanks for the last wins bit!
osa1 has quit [Quit: Konversation terminated!]
Progster has joined #ocaml
ontologiae has quit [Ping timeout: 252 seconds]
Progster has quit [Ping timeout: 244 seconds]
cicero321 has quit [Quit: cicero321]
eni has joined #ocaml
n00b6502 has quit [Ping timeout: 276 seconds]
ChristopheT has joined #ocaml
leoncamel has joined #ocaml
eni has quit [Ping timeout: 246 seconds]
_key_ has joined #ocaml
<_key_> hi
<_key_> i am wondering if something like this is possible in ocaml:
<_key_> class a = object(self) val mutable lst ([] : b list) end;;
<_key_> class b = object(self) val mutable lst ([] : a list) end;;
Sablier has joined #ocaml
err404 has joined #ocaml
<adrien> class a = object(self) val mutable lst : b list = [] end and b = object(self) val mutable lst : a list = [] end
<adrien> damn you irssi
n00b6502 has joined #ocaml
barronax` has quit [Remote host closed the connection]
<_key_> ah, ok, so no typing
<_key_> thanks
sepp2k has joined #ocaml
emmanuelux has joined #ocaml
Yoric has joined #ocaml
Yoric has quit [Remote host closed the connection]
Yoric has joined #ocaml
eni has joined #ocaml
targetron has quit [Ping timeout: 252 seconds]
Yoric has quit [Ping timeout: 250 seconds]
Yoric has joined #ocaml
eni has quit [Ping timeout: 260 seconds]
err404 has quit [Remote host closed the connection]
emmanuelux has quit [Remote host closed the connection]
eni has joined #ocaml
cago has quit [Ping timeout: 272 seconds]
chambart has quit [Ping timeout: 264 seconds]
Yoric has quit [Ping timeout: 246 seconds]
Yoric has joined #ocaml
Yoric has quit [Ping timeout: 245 seconds]
bddn has quit [Ping timeout: 255 seconds]
milosn has joined #ocaml
bddn has joined #ocaml
ontologiae has joined #ocaml
eni has quit [Ping timeout: 246 seconds]
thelema has quit [Remote host closed the connection]
thelema has joined #ocaml
milosn has quit [Ping timeout: 240 seconds]
thelema has quit [Remote host closed the connection]
cabbagebot has joined #ocaml
cabbagebot has quit [Client Quit]
cabbagebot has joined #ocaml
Yoric has joined #ocaml
cabbagebot has quit [Ping timeout: 255 seconds]
osa1 has joined #ocaml
osa1 has quit [Quit: Konversation terminated!]
osa1 has joined #ocaml
mika1 has quit [Quit: Leaving.]
ocp has quit [Ping timeout: 252 seconds]
Yoric has quit [Ping timeout: 260 seconds]
ftrvxmtrx has quit [Quit: Leaving]
cabbagebot has joined #ocaml
paolooo has joined #ocaml
err404 has joined #ocaml
cabbagebot has quit [Ping timeout: 240 seconds]
thelema has joined #ocaml
bzzbzz has joined #ocaml
ftrvxmtrx has joined #ocaml
djcoin has quit [Ping timeout: 240 seconds]
leoncamel has quit [Ping timeout: 246 seconds]
leoncamel has joined #ocaml
osa1 has quit [Ping timeout: 240 seconds]
sepp2k1 has joined #ocaml
cago has joined #ocaml
sepp2k has quit [Ping timeout: 276 seconds]
<thelema> " It is now possible to defer type errors until runtime using the -fdefer-type-errors flag: Section 7.13, “Deferring type errors to runtime”. " -- ?? have the haskell developers gone crazy?
cago has quit [Quit: Leaving.]
cago has joined #ocaml
<companion_cube> maybe it's for when type inference is indecidable?
<companion_cube> undecidable*
<thelema> you still get a warning, so it's still running the type checker
mika1 has joined #ocaml
<ousado> heh
mika1 has quit [Client Quit]
Snark has joined #ocaml
Drakken has left #ocaml []
xaimus has quit [Ping timeout: 252 seconds]
xaimus has joined #ocaml
cago has quit [Quit: Leaving.]
cago has joined #ocaml
ontologiae has quit [Ping timeout: 246 seconds]
targetron has joined #ocaml
<Ptival> companion_cube thelema: I think it's more advocated for "will do later" stuff
<Ptival> so that you can test relevant changes before you have to make the whole thing typecheck again
<thelema> Ptival: I use (assert false) as a value that typechecks anywhere for that purpose
pangoafk is now known as pango
err404 has quit [Remote host closed the connection]
sivoais has quit [Quit: Lost terminal]
sivoais has joined #ocaml
cago has quit [Quit: Leaving.]
cabbagebot has joined #ocaml
cago has joined #ocaml
Snark has quit [Quit: Quitte]
ChristopheT has quit [Ping timeout: 246 seconds]
osa1 has joined #ocaml
_key_ has quit [Quit: _key_]
Yoric has joined #ocaml
milosn has joined #ocaml
Yoric has quit [Remote host closed the connection]
Yoric has joined #ocaml
targetron has quit [Ping timeout: 248 seconds]
hiredman has joined #ocaml
<hiredman> how do you do open ended polmorphism in ocaml? If I have a type X with functions a b c, is there someway to "extend" that type to type Y by implementing a b c for Y?
<hiredman> I am looking for something sort of like haskell's type classes I think (not very familiar with haskell either)
<Yoric> Generally, you do this with functors.
<Yoric> I have to go, though.
<thelema> hiredman: I can answer any further questions you have about functors
<hiredman> I will continue googling then
<hiredman> thanks, I will have to read up on functors first
<thelema> given <X,a,b,c>, you want another type Y with the same functions?
<thelema> do you just want function overloading (based on the type of the arguments)?
<thelema> Do you want to be able to say (a x) and also (a y) for x and y different types?
<thelema> and have different `a` functions get called?
<hiredman> yes
<thelema> this is function overloading, quite different from functors
<thelema> ocaml doesn't support it, as it's incompatible with its type inference
<thelema> thus you must have different names for `string_of_int` and `string_of_float`
cabbagebot has quit [Ping timeout: 248 seconds]
<thelema> Jun furuse has been working hard on ways to get around this; here's his latest method in blog post format: http://camlspotter.blogspot.com/2012/09/a-safe-but-strange-way-of-modifying.html
<hiredman> what I want, is something like a typeclass where I can say here is a type calss TC it has functions x y z, and then write functions that take an "instance" of TC as an argument, and have someway to define operations x y z for a given type to make it an "instance" of TC
<thelema> yup, that's what Jun has been making possible.
<thelema> There's a way to simulate this using functors, but it's not as nice.
<thelema> and of course, ocaml's object system is able to do this perfectly well.
<thelema> but the object system is... frequently avoided.
<hiredman> maybe that is what I should do, I'll noodle and do some reading
<hiredman> thanks
thomasga has quit [Quit: Leaving.]
cago has quit [Quit: Leaving.]
<adrien> well, the object system is frequently avoided because the other ocaml features often already solve issues for which OO is typically used :-)
<julm> oh yeah
paolooo has quit [Quit: Page closed]
<mfp> hiredman: you can simulate type classes easily with first-class modules used as dictionaries; the diff with Haskell's is that you must pass them explicitly
rwmjones_hols has quit [Read error: Operation timed out]
<hiredman> mfp: do you have an example of that vailable?
<hiredman> I guess this https://ocaml.janestreet.com/?q=node/37 ?
<mfp> I don't have a 4.00 toplevel handy, but I can write one using 3.12.1's syntax (4.00 allows to write things more succintly), give me a minute
<adrien> mfp: btw, what's up with your website? (I'll probably be asleep by the time you read this so no hurry :P )
<mfp> hiredman: the blogpost you linked to is similar in spirit, but uses structs (which cannot define/carry types of their own)
<thelema> mfp: ?? structs = module = can carry types; are you thinking records?
<mfp> yes my bad
<mfp> hiredman: module type TC is the type-class, X1 is one instance of it, and val f : (module TC with type t = 'a) -> 'a -> 'a is a function taking an explicit dictionary that operates on instances of TC
<mfp> adrien: last time I logged into it (ages ago) I found some issue I couldn't fix right away, and I haven't bothered since, as I didn't feel like writing anything :P
<adrien> mfp: ok, archive.org probably serves most of your website anyway
<thelema> mfp: for benchmarking, I want to have a list of functions to benchmark, and since I don't care about their return types, I want to let this be (unit -> 'a)
<mfp> so I'll look into that, someday
<adrien> heh :-)
<hiredman> mfp: interesting, thanks
<thelema> mfp: (type a) doesn't look like the way to do this; I'll have to have a `'a. unit -> 'a` record field, right?
<mfp> hiredman: note that 4.00 introduces some syntactical/type inferrence changes that simplify this
<mfp> thelema: hmm you can pack the functions using 1st-class modules
<thelema> mfp: oh yeah, "this" is being able to have functions with different return types (that I'll just ignore)
rwmjones_hols has joined #ocaml
<thelema> mfp: can that 1st class module be typed properly?
<mfp> essentially encoding existential types
<mfp> I think so, you'd just have to have a collection of (module TY)
<mfp> without any ... with type t = .... constraint
<mfp> like module type FUNC = struct type a val f : unit -> a end
<mfp> then you pack any struct into a (module FUNC) type, thus losing the info about their respective types
<mfp> let me try...
<mfp> argh module type FUNC = ***sig***
<thelema> :) I didn't even notice the incompatibility.
<mfp> here you go: let module M1 = struct type a = int let f () = 12 end in let module M2 = struct type a = float let f () = 3.14 end in [ (module M1 : FUNC); (module M2 : FUNC) ];;
<mfp> - : (module FUNC) list = [<module>; <module>]
<thelema> nice. unfortunate about the syntactic heaviness.
<mfp> most of it goes away in 4.00 though
<thelema> is the `type a` really needed?
<mfp> nope
<mfp> in practice, you'd probably more operations with intermediate results (and types)
<mfp> which is where type a and friends enter the picture
<thelema> but you need something for the return type in the signature of f... thus we have it.
<thelema> not worried about intermediate types at all.
<mfp> oh, misread my own example :P
<thelema> as I said, I want to have a list of functions that I execute simply for their side effect, all unit -> 'a
<mfp> then let run x = List.iter (fun m -> let module M = (val m : FUNC) in ignore (M.f ())) x;; val run : (module FUNC) list -> unit = <fun>
<mfp> you can also use GADTs for the existential types I think
<thelema> is that lighter?
<thelema> in declaring the list, that is.
<mfp> probably
<mfp> IIRC you could just have "unbound" types in the GADT constructor so just CONSTR f could work?
<mfp> haven't played with 4.00/GADTs yet so unsure
<thelema> that'd be nice.
<thelema> I'm not a type system expert
<thelema> so thanks for your help
<mfp> thelema: is the above for bench?
<thelema> mfp: yes
<pr> so, what's the go-to book for learning ocaml (for someone with a background in programming, even some functional languages)?
<mfp> are 4.00 features OK then?
<thelema> it's simple enough to have (fun x -> ignore(foo x)), but if I can do better...
<thelema> mfp: why not? I'm fine moving it forward. All my code is migrating.
<thelema> mfp: do you think I should keep maintaining a 3.12 compatible version of bench?
targetron has joined #ocaml
<mfp> thelema: I personally just use the latest OCaml version available on Debian ;-)
<thelema> ah. I hope 4.00 makes it to debian quickly.
<thelema> I've switched to using ocamlbrew to install my ocaml, so I have 3.12.1 and 4.00.0 both available with independent packages
<mfp> if 4.00's new stuff makes life easier for you(r code), don't let that stop you :)
<mfp> svn update finished at last... here's what Changes says: "It is now possible to omit type annotations when packing and unpacking first-class modules. The type-checker attempts to infer it from the context."
<thelema> (easier than svn)
<mfp> indeed /me clones
targetron has quit [Ping timeout: 244 seconds]
<thelema> not official, but automatically updated (only trunk branch, not any release branch) every 5 minutes
<mfp> nice
Yoric has quit [Ping timeout: 246 seconds]
<mfp> pr: probably Jason Hickey's book (draft at www.cs.caltech.edu/courses/cs134/cs134b/book.pdf) and O'Reilly's Developing Applications with Objective Caml http://caml.inria.fr/pub/docs/oreilly-book/
<mfp> waiting for http://realworldocaml.org/
<pr> yeah, kinda waiting for realworldocaml, haha
BiDOrD_ has joined #ocaml
BiDOrD has quit [Ping timeout: 268 seconds]
ankit9 is now known as ankit9|zzz
jave has quit [Read error: Connection reset by peer]
jave_ has joined #ocaml
ontologiae has joined #ocaml
ankit9|zzz has quit [Ping timeout: 255 seconds]
Ptival has quit [Read error: Connection reset by peer]
ankit9|zzz has joined #ocaml
osa1 has quit [Quit: Konversation terminated!]
emmanuelux has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
ontologiae has quit [Ping timeout: 248 seconds]
Progster has joined #ocaml
Progster has quit [Ping timeout: 245 seconds]
emmanuelux has joined #ocaml