rwmjones changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.2 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
ygrek has quit [Remote closed the connection]
evn has joined #ocaml
evn has quit [Remote closed the connection]
middayc has quit [Read error: 110 (Connection timed out)]
ofaurax has quit ["Leaving"]
yangsx_ has joined #ocaml
palomer has joined #ocaml
<palomer> does ocaml have rank 2 types?
<palomer> actually, no need
* palomer is switching from haskell to ocaml
<palomer> how exciting!
<palomer> caml4p is similar to template haskell?
hkBst has quit ["Konversation terminated!"]
<ziph> palomer: I think all the experts are asleep. ;)
<palomer> what's the standard ocaml file extension?
<ziph> .ml for code.
<palomer> and for the rest?
<ziph> Have a look at http://caml.inria.fr/pub/docs/manual-ocaml/manual004.html, there are a few different ones (particularly after you've run the compiler)
<thelema> palomer: .mli for signatures, mll for lex, .mly for yacc (ocaml variants)
<palomer> what do you guys use for your pastebin?
<thelema> palomer: no one standard. ocaml.pastewith.us works nicely
<palomer> do virtual function signatures have to match? meaning, if the type of f is a subtype of g, f is located in class A which is a subclass of B and B contains virtual method g, what's going to happen?
<palomer> is a subtype of the type of g, that is
<thelema> yes, virtual signatures have to match. ocaml doesn't do any overloading
<thelema> and whatever casting you might want *needs* to be explicit
<palomer> that's a bummer
<thelema> we deal with it pretty well
<palomer> is there a reason for this?
<palomer> this isn't about overloading, though, it's about subtyping
<thelema> a concrete example: f : int -> int, g : 'a -> 'a, class B = object method virtual g : 'a -> 'a end
<thelema> class A = object method virtual f : int -> int end
<thelema> palomer: does this notation makae sense?
<thelema> oops, you wanted A to have a non-virtual method.
<thelema> class A = object method f x = x + 1 end
AxleLonghorn has joined #ocaml
<palomer> wait, this is what I meant
<palomer> oh, wait ,it just returns an a
seafood_ has joined #ocaml
<palomer> I meant subtype in the sense of subclass
<palomer> that's a bummer
<palomer> hrmph
* palomer is off
a13x has joined #ocaml
LordMetroid has quit ["ZzZzZz"]
a13x has quit [Read error: 113 (No route to host)]
a13x has joined #ocaml
<a13x> hi
<a13x> anybody alive?
<hcarty> Most likely
<a13x> i had a question about Unix.Sockets if you don't mind
<a13x> how can a client detect that a connection has been closed
<thelema> reading off the end of the connection?
<a13x> zero bytes read returned from Unix.read?
jonathanv has joined #ocaml
Cosmos95 has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
<thelema> > if the connection is terminated, a signal, with a value of SIGPIPE, is sent to the process that tried to perform a read on socket.
<thelema> you could also get an error code (ECONNRESET, etc)
<a13x> thanks
<jdev> IIRC, it's only when you try to write to a closed socket/pipe that the SIGPIPE is posted and (if survived) EPIPE returned.
<thelema> jdavis_: you may be right
<thelema> err, jdev
<a13x> it seems econnreset is enough
jargonjustin has joined #ocaml
<jargonjustin> Is there a good resource resource for learning how different ocaml constructs perform? I'm particularly interested in how local functions, closures that don't escape the enclosing scope, and local functions versus methods in objects perform.
det has quit [Remote closed the connection]
aminorex has left #ocaml []
<mwc> jargonjustin, don't know of any, but you could write microbenchmarks if you care.
<jargonjustin> mwc: I considered it, I think profiling my app and playing with the hotspots is probably the way to go for now
<jargonjustin> Just checking if there was any literature out there
<a13x> funny thing, my app crashes instead of trying to catch exceptions with closed sockets
<a13x> function send crashes
<a13x> every time
<a13x> when i close the client
<a13x> does anyone have any idea why it would crash?
<thelema> a13x: crashes sigfault?
<a13x> no
<a13x> just exists
<thelema> exits
<a13x> i can send you the complete source if you want to test
<thelema> the Unix.write fails?
<a13x> yes
<a13x> last few lines
<a13x> looks like it doesn't get to adsf
<thelema> SIGPIPE?
<a13x> i don't think so
<a13x> is there any way to check for sure?
<thelema> Sys.set_signal Sys.sigpipe (Sys.Signal_handle (fun _ -> print_endline "ignoring sigpipe")
jargonjustin has quit []
<a13x> nice
<a13x> this time it didn't crash
<a13x> you are right
mwc has quit ["Leaving"]
<a13x> thanks a lot for your help
a13x has quit [brown.freenode.net irc.freenode.net]
seafood_ has quit [brown.freenode.net irc.freenode.net]
petchema has quit [brown.freenode.net irc.freenode.net]
ertai has quit [brown.freenode.net irc.freenode.net]
pattern has quit [brown.freenode.net irc.freenode.net]
Cosmos95 has quit [brown.freenode.net irc.freenode.net]
cmeme has quit [brown.freenode.net irc.freenode.net]
rwmjones has quit [brown.freenode.net irc.freenode.net]
dibblego has quit [brown.freenode.net irc.freenode.net]
yminsky_ has quit [brown.freenode.net irc.freenode.net]
neale has quit [brown.freenode.net irc.freenode.net]
jdavis_ has quit [brown.freenode.net irc.freenode.net]
ziph has quit [brown.freenode.net irc.freenode.net]
ulfdoz has quit [brown.freenode.net irc.freenode.net]
|Catch22| has quit [brown.freenode.net irc.freenode.net]
goalieca has quit [brown.freenode.net irc.freenode.net]
rogo has quit [brown.freenode.net irc.freenode.net]
seafood has quit [brown.freenode.net irc.freenode.net]
Dazhbog has quit [brown.freenode.net irc.freenode.net]
qwr has quit [brown.freenode.net irc.freenode.net]
flux has quit [brown.freenode.net irc.freenode.net]
jonathanv has quit [brown.freenode.net irc.freenode.net]
Mr_Awesome has quit [brown.freenode.net irc.freenode.net]
jsk has quit [brown.freenode.net irc.freenode.net]
Illocution has quit [brown.freenode.net irc.freenode.net]
romanoffi has quit [brown.freenode.net irc.freenode.net]
svenl has quit [brown.freenode.net irc.freenode.net]
guyzmo has quit [brown.freenode.net irc.freenode.net]
dwmw2_gone has quit [brown.freenode.net irc.freenode.net]
Ugarte has quit [brown.freenode.net irc.freenode.net]
l_a_m has quit [brown.freenode.net irc.freenode.net]
Hadaka has quit [brown.freenode.net irc.freenode.net]
mbishop has quit [brown.freenode.net irc.freenode.net]
__suri has quit [brown.freenode.net irc.freenode.net]
Smerdyakov has quit [brown.freenode.net irc.freenode.net]
Oatschool has quit [brown.freenode.net irc.freenode.net]
ozzloy has quit [brown.freenode.net irc.freenode.net]
unfo- has quit [brown.freenode.net irc.freenode.net]
AxleLonghorn has quit [brown.freenode.net irc.freenode.net]
yangsx_ has quit [brown.freenode.net irc.freenode.net]
bla has quit [brown.freenode.net irc.freenode.net]
Demitar_ has quit [brown.freenode.net irc.freenode.net]
zmdkrbou has quit [brown.freenode.net irc.freenode.net]
mattam has quit [brown.freenode.net irc.freenode.net]
fremo has quit [brown.freenode.net irc.freenode.net]
jdev has quit [brown.freenode.net irc.freenode.net]
szell` has quit [brown.freenode.net irc.freenode.net]
donny_ has quit [brown.freenode.net irc.freenode.net]
shortcircuit has quit [brown.freenode.net irc.freenode.net]
Morphous_ has quit [brown.freenode.net irc.freenode.net]
prince has quit [brown.freenode.net irc.freenode.net]
ppsmimou has quit [brown.freenode.net irc.freenode.net]
gim has quit [brown.freenode.net irc.freenode.net]
gaja has quit [brown.freenode.net irc.freenode.net]
smimou has quit [brown.freenode.net irc.freenode.net]
mfp has quit [brown.freenode.net irc.freenode.net]
TaXules has quit [brown.freenode.net irc.freenode.net]
hcarty has quit [brown.freenode.net irc.freenode.net]
acatout has quit [brown.freenode.net irc.freenode.net]
bebui has quit [brown.freenode.net irc.freenode.net]
jlouis_ has quit [brown.freenode.net irc.freenode.net]
pango has quit [brown.freenode.net irc.freenode.net]
coucou747 has quit [brown.freenode.net irc.freenode.net]
Jedai has quit [brown.freenode.net irc.freenode.net]
tsuyoshi has quit [brown.freenode.net irc.freenode.net]
huh_ has quit [brown.freenode.net irc.freenode.net]
ahf has quit [SendQ exceeded]
ramkrsna has joined #ocaml
pattern has joined #ocaml
petchema has joined #ocaml
seafood_ has joined #ocaml
a13x has joined #ocaml
ahf has joined #ocaml
ertai has joined #ocaml
Cosmos95 has joined #ocaml
jonathanv has joined #ocaml
AxleLonghorn has joined #ocaml
yangsx_ has joined #ocaml
Mr_Awesome has joined #ocaml
mbishop has joined #ocaml
jlouis_ has joined #ocaml
goalieca has joined #ocaml
Morphous_ has joined #ocaml
pango has joined #ocaml
jsk has joined #ocaml
ziph has joined #ocaml
coucou747 has joined #ocaml
szell` has joined #ocaml
prince has joined #ocaml
__suri has joined #ocaml
dibblego has joined #ocaml
bla has joined #ocaml
ppsmimou has joined #ocaml
Jedai has joined #ocaml
l_a_m has joined #ocaml
Demitar_ has joined #ocaml
gim has joined #ocaml
cmeme has joined #ocaml
qwr has joined #ocaml
gaja has joined #ocaml
ulfdoz has joined #ocaml
donny_ has joined #ocaml
zmdkrbou has joined #ocaml
smimou has joined #ocaml
shortcircuit has joined #ocaml
rogo has joined #ocaml
yminsky_ has joined #ocaml
mfp has joined #ocaml
seafood has joined #ocaml
rwmjones has joined #ocaml
Illocution has joined #ocaml
Dazhbog has joined #ocaml
Ugarte has joined #ocaml
svenl has joined #ocaml
Hadaka has joined #ocaml
dwmw2_gone has joined #ocaml
romanoffi has joined #ocaml
flux has joined #ocaml
guyzmo has joined #ocaml
jdavis_ has joined #ocaml
neale has joined #ocaml
unfo- has joined #ocaml
ozzloy has joined #ocaml
Oatschool has joined #ocaml
Smerdyakov has joined #ocaml
bebui has joined #ocaml
mattam has joined #ocaml
fremo has joined #ocaml
jdev has joined #ocaml
hcarty has joined #ocaml
huh_ has joined #ocaml
acatout has joined #ocaml
TaXules has joined #ocaml
tsuyoshi has joined #ocaml
RobertFischer has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has joined #ocaml
eelte has joined #ocaml
coucou747 has quit [Read error: 110 (Connection timed out)]
<palomer> hrmph
<palomer> are there any alternatives to the value restriction?
goalieca has quit [Remote closed the connection]
dibblego has quit ["Leaving"]
AxleLonghorn has quit ["Leaving."]
seafood_ has quit []
<thelema> palomer: what are you trying to do?
<palomer> write a programming language
<palomer> I'm thinking the value restriction is the best way
seafood_ has joined #ocaml
<palomer> (especially since I'm compiling into ocaml)
<palomer> but, it makes it very tricky for me
<thelema> good luck.
<palomer> hrmph, and I have to pick a toolkit
<ziph> Why not go dynamic?
middayc has joined #ocaml
<a13x> it seems i have finished my program, anybody want to give it a try?
<a13x> thanks to everyone who helped me out in the past month
<a13x> farewell
a13x has quit ["Leaving"]
ttamttam has joined #ocaml
seafood_ has quit []
pango has quit [Remote closed the connection]
pango has joined #ocaml
seafood_ has joined #ocaml
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
<tsuyoshi> rwmjones: in ancient, what is the my_realloc for? it doesn't do anything
middayc has quit []
ramkrsna has quit [Read error: 110 (Connection timed out)]
seafood_ has quit []
<rwmjones> tsuyoshi, you need to pass a realloc & free callback to 'mark', and depending on whether you want to mark data into the C heap or a heap managed by mmalloc, you pass different callbacks
<rwmjones> tsuyoshi, so my_realloc is used when you want to mark data to the C heap
m3ga has joined #ocaml
yangsx_ has quit [Read error: 110 (Connection timed out)]
bongy has joined #ocaml
OChameau has joined #ocaml
hkBst has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
<ziph> Hiya.
digger has joined #ocaml
LordMetroid has joined #ocaml
rwmjones has quit ["Closed connection"]
m3ga has quit ["disappearing into the sunset"]
rwmjones has joined #ocaml
digger has quit []
dwmw2_gone is now known as dwmw2
rwmjones has quit ["Closed connection"]
rwmjones has joined #ocaml
<ikatz> i have a design question...
<ikatz> say i have a functorial interface to some module
lordmetroid_ has joined #ocaml
<ikatz> and the struct i'm passing into the functor would need some values computed from stdin
<ikatz> does that mean i'm going about this the wrong way?
<ikatz> my first impulse is to define the module inside my main "let _ = ..." function
<ikatz> but that syntax gets rejected
<ikatz> i hope that explanation makes sense... but let me take another shot at it anyway
<ikatz> i am writing code to do AI searches. it made sense to me to write a general-purpose module for the searching
<ikatz> so the search module is a functor that takes a "problem domain" structure
<ikatz> "problem domain" has functions like initial state, successor function, goal test, etc
<ikatz> in the problem i am working on, the initial state and the possible actions (needed for the successor function) are read from stdin
<petchema> functorized doesn't imply purely functional... I don't see the problem with using stdin...
<ikatz> right... but where do i put the code that reads from standard in?
<petchema> where you want
<ikatz> does it go inside the functor?
<ikatz> well..
<ikatz> i have something like:
<ikatz> let _ =
<ikatz> mydata = parser.main .exer.token lexbuf in
<ikatz> module MyProblem = struct
<ikatz> let .... blah blah blah = mydata
<ikatz> end
<petchema> module ... is a definition, not an expression
<ikatz> right
<petchema> so it's normal it's rejected with a let ... in ...
<petchema> s/with/within/
<ikatz> so how would i create a module that contains function definitons derived from data gathered on stdin?
bongy has quit ["Leaving"]
<ikatz> because the only alternative i can think of is making a module that contains the "read from stdin" function
<ikatz> and i just want to make sure that that's the right way to do it
LordMetroid has quit [Connection timed out]
<petchema> function parameters...
<petchema> you can pass that read-from-stdin function as parameter, for example
seafood_ has joined #ocaml
munga has joined #ocaml
<ikatz> does that mean i need to rewrite my functor?
<ikatz> how would i do the technique you're talking about?
lordmetroid__ has joined #ocaml
rwmjones has quit ["Closed connection"]
<ikatz> petchema: can you give me an example?
gaja has quit ["leaving"]
rwmjones has joined #ocaml
marmottine has joined #ocaml
lordmetroid_ has quit [Read error: 110 (Connection timed out)]
Cosmos95 has quit []
pango has quit [Remote closed the connection]
pango has joined #ocaml
Snark has joined #ocaml
lordmetroid_ has joined #ocaml
LordMetroid has joined #ocaml
lordmetroid__ has quit [Read error: 110 (Connection timed out)]
seafood_ has quit []
lordmetroid_ has quit [Connection timed out]
RobertFischer has joined #ocaml
seafood_ has joined #ocaml
ziph has quit []
Smerdyakov has quit ["Leaving"]
Smerdyakov has joined #ocaml
seafood_ has quit []
Snark has quit [Read error: 113 (No route to host)]
aminore1 has joined #ocaml
LordMetroid has quit [Read error: 110 (Connection timed out)]
LordMetroid has joined #ocaml
delamarche has joined #ocaml
LordMetroid has quit ["Leaving"]
pango has quit [Remote closed the connection]
pango has joined #ocaml
Morphous has joined #ocaml
Morphous_ has quit [Read error: 110 (Connection timed out)]
ttamttam has left #ocaml []
evn has joined #ocaml
|Catch22| has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
ygrek has joined #ocaml
bluestorm has joined #ocaml
Snark has joined #ocaml
ita has joined #ocaml
ita has left #ocaml []
jargonjustin has joined #ocaml
jargonjustin has left #ocaml []
OChameau has quit [Read error: 113 (No route to host)]
jargonjustin has joined #ocaml
Morphous has quit [Connection timed out]
Morphous has joined #ocaml
Morphous has quit ["shutdown"]
Amorphous has joined #ocaml
dwmw2 is now known as dwmw2_gone
<palomer> is there a good lablgtk tutorial around?
<palomer> actually, I think I need an ocaml tutorial beforehand
<bluestorm> palomer: as an introduction to ocaml : http://www.nuprl.org/documents/Hickey/02caltech-ocaml.html
delamarche has quit []
ttamttam has joined #ocaml
evn_ has joined #ocaml
jonathanv is now known as jonafan
<palomer> variants look kind of like records
<RobertFischer> ?
<RobertFischer> Variant types?
<palomer> yeah
<palomer> or, rather, they are the counterpart to records
<flux> wouldn't they look more like enums with records?
<bluestorm> palomer: records are products, variants are sums
<bluestorm> so yes "couterpart" is a very good point of view
<bluestorm> (actually variants can embed an product too, with type ('a, 'b) foo = Foo of 'a * 'b, but they primarily are sums)
<palomer> is there a reason why record fields are unique?
<bluestorm> because of type inference
<bluestorm> if you had no unicity
<bluestorm> let foo x = x.field
<bluestorm> you wouldn't know "x" type
<palomer> ahh, you want to infer the type of x
<palomer> gotcha
<palomer> couldn't foo have type
<palomer> {x:'a} -> 'a
<palomer> (sorry for the syntax)
<bluestorm> hm
<Smerdyakov> palomer, that's hardly a concrete suggestion, since you haven't said how to modify the type inference algorithm.
<bluestorm> you mean {field:'a} ?
<palomer> err, yeah
<bluestorm> so you would like to add subtyping and the like
<palomer> yeah
<bluestorm> that's very near to what objects provide
<palomer> Smerdyakov, I just want to gain more insight
<Smerdyakov> SML has a way of doing this, which ends up being very similar to how polymorphic variant type inference is handled in OCaml.
<bluestorm> al foo : < field : 'a; .. > -> 'a = <fun>
<palomer> sml has subtyping between records?
<bluestorm> urgh
<bluestorm> # let foo x = x#field;;
<bluestorm> val foo : < field : 'a; .. > -> 'a = <fun>
<palomer> nice
<Smerdyakov> No. SML type inference involves open record types as intermediate results.
<palomer> Smerdyakov, so record fields are still unique
<Smerdyakov> palomer, no.
<palomer> bluestorm, are there any advantages of using records over objects?
<bluestorm> records are simpler
<bluestorm> you won't need subtyping most of the time
<bluestorm> and objects can raise quite delicate typing issues (eg. rank-2 polymorphism)
<palomer> ocaml has rank-2 polymorphism?
<bluestorm> hm
<bluestorm> inside records and objects, yes :-'
<palomer> Smerdyakov, I haven't touched sml in 2 years, lemme download and fire up smlnj
<Smerdyakov> palomer, no, I forbid it.
<palomer> so records are a poor man's object?
<palomer> Smerdyakov, but I want to see what sml does!
<bluestorm> palomer: are closures poor man instances ?
<bluestorm> i'm not sure the "poor man" thing is appropriate
<bluestorm> if you want more (eg. subtyping) you can have
<bluestorm> but it's more complicated, so if you don't need that, records are better
<palomer> Smerdyakov, what's the sml syntax for the record directed foo function previously mentioned?
<palomer> bluestorm, but records can be implemented using objects in a trivial way, right?
<Smerdyakov> palomer, #field
<bluestorm> i guess so
Snark has quit ["Ex-Chat"]
bluestorm has quit ["Konversation terminated!"]
<flux> palomer, however objects cannot be pattern matched
<palomer> ahh, there's the difference!
<flux> I suppose if that were fixed, there would be no actual reason to use records.. bluestorm up for a camlp4 extension?-)
<palomer> well, sml doesn't want to type foo until it knows more about it
<flux> (I don't know how, though)
<Smerdyakov> palomer, like I said, open record types are intermediate constituents of type inference. They all need to be resolved by the end.
<palomer> gotcha
<flux> match object method a = b end with | {#a = 42} -> .. let o = object method a = b end in let a = lazy o#a .. and use lazy pattern matching by yoric afterwards?
RobertFischer has left #ocaml []
Cosmos95 has joined #ocaml
ttamttam has left #ocaml []
psnively has joined #ocaml
* palomer loves otags
<palomer> I followed the steps indicated by http://www.ocaml-tutorial.org/introduction_to_gtk
<palomer> and I'm getting the error: Unbound module GMain
* palomer begins to apt-get everything in sight
<jonafan> how are you launching ocaml?
<jonafan> you need to do something like ocaml -I "+lablgtk2" lablgtk.cma
<jonafan> it depends on your distro and crap probably
<palomer> ocamlc -g -w s -I +lablgtk lablgtk.cma gtkInit.cmo simple.ml -o simple
<palomer> ok, I'll try plus.kaist.ac.kr
<ygrek> btw looks like latest otags in debian doesn't work with ocaml 3.10, needs recompile..
<palomer> tsok, using 3.09
* pango locked otags on version 3.09.3-2
<palomer> otags is very important for me
* palomer feels like he's going to like ocaml
<psnively> OCaml is my favorite language ATM, and I look at LOTS of languages.
AndreWe has joined #ocaml
vpalle has joined #ocaml
marmottine has quit ["Quitte"]
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
psnively has quit []
AndreWe has left #ocaml []
vpalle has quit ["Leaving"]
pango has quit [Remote closed the connection]
pango has joined #ocaml
pango has quit [Client Quit]
pango has joined #ocaml
psnively has joined #ocaml
ygrek has quit [Remote closed the connection]
evn has quit []
evn has joined #ocaml
pango has quit [Remote closed the connection]
delamarche has joined #ocaml
evn has quit []
Yoric[DT] has joined #ocaml
pango has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]