mbishop 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!)
<palomer> if I have a class type T, is it possible to add to it? (like <T;bar:int>)
thermoplyae has joined #ocaml
psnively has joined #ocaml
<palomer> hrmph, I can't find a tutorial which explains the difference between val and method inside a class
<bluestorm_> "val" is private, "method" is public
<bluestorm_> in the sense that only the methods can caracterize an object from the outside
<palomer> bluestorm_, private meaning accessible to any instance of the class
<palomer> ?
<bluestorm_> hm
<bluestorm_> no, only to the object
<palomer> can method use mutable syntax?
<bluestorm_> iirc they can't
<bluestorm_> but you can store refs inside
<palomer> which is pretty much the same thing?
<bluestorm_> pretty much
<palomer> is there a way to shorten type node_wrapper = <get_right_sibling: unit -> <to_node_wrapper: unit -> node_wrapper > option ;get_parent: unit -> <to_node_wrapper : unit -> node_wrapper> option> ?
<palomer> it seems long and repetitive
<bluestorm_> why don't you declare a class type instead ?
<palomer> would it be equivalent?
<bluestorm_> hm
<bluestorm_> as you typed it, i think it wouldn't
<bluestorm_> but i'm not sure of the subtleties of object typing
<bluestorm_> (it's extensible, so it's complicated)
<palomer> it works
<palomer> in ocaml, I have to use functions to compute, right? like, method rightSibling = !rightSiblingVal <--this wouldn't work, right?
<palomer> I would have to type method rightSibling () = !rightSiblingVal
<bluestorm_> hm
<bluestorm_> the method call ( using the # thing ) is evaluated each time
<bluestorm_> by doing so it behave a bit like an implicit unit -> foo functions
<bluestorm_> (the idea is that you "send a message" to the object, each time)
<bluestorm_> but palomer : do you really need your tree to be mutable ?
<bluestorm_> from a fonctional p.o.v it seems that you could do with functional update only
<psnively> ==bluestorm_
<palomer> hrmph
<palomer> but there's a seek overhead
<palomer> right?
<bluestorm_> ?
<bluestorm_> wich seek overhead ?
<palomer> if I use the zipper
<bluestorm_> (and who cares about the overhead when writing code for the first time ?)
<palomer> this is the second time
<palomer> the first time was on haskell
<bluestorm_> what's the first time like ?
<palomer> works great
<palomer> also uses ref
<bluestorm_> blah
<psnively> Use zippers.
<palomer> advantages?
Morphous is now known as Amorphous
<bluestorm_> palomer: there are no ref around :]
<bluestorm_> and you have persistence for free
<bluestorm_> hm
<psnively> Advantages to zippers? Easier to reason about. Undo for free.
<psnively> Maximal sharing.
<bluestorm_> are we ocamlers really trying to explain the advantage of a purely functional data structure to a former haskeller ?
<psnively> Functional, obviously.
<psnively> I know... what's wrong with this picture?
<palomer> undo for free??
<palomer> really?
<psnively> Sure: since you still have the previous "version" of the structure...
<palomer> I actually tried to come up with my own zipper variant (before knowing about zippers)
<palomer> and failed miserably
<palomer> undo for free seems really interesting
<psnively> One of the general benefits of purely functional data structures is "undo for free."
yangsx has joined #ocaml
<palomer> oh, what the heck, I'll use zippers
<psnively> Zippers are easy to implement in terms of delimited continuations. Now we just need Oleg to do native delimited continuations for native OCaml.
<bluestorm_> psnively: in the case of a tree, wouldn't the usual current node * ancestors list do the job ?
<psnively> Oh, I'm sure you could hack something together that would work well enough in the specific case, sure.
<palomer> oleg does ocaml stuff?
<psnively> Oleg does Scheme, OCaml, and Haskell simultaneously in a lot of cases.
<bluestorm_> psnively: btw, what do you do ? :p
<palomer> since I don't care about performance for now, shouldn't I use something simpler than zippers
<bluestorm_> palomer: because zippers are not simple ?
<psnively> I write software, of course. :-D
<bluestorm_> (language-wise)
<psnively> Here's Oleg's delimited continuations for OCaml: http://okmij.org/ftp/Computation/Continuations.html#caml-shift
<psnively> The day job's in Python. OCaml is my preferred language on my own time.
<palomer> zippers are the simplest way to implement mutable (pure) datastructures?
<psnively> Probably the simplest in the presence of delimited continuations.
<bluestorm_> maybe we're not exactly talking of the same thing
<bluestorm_> bug palomer in the tree case the basic idea is only
<palomer> http://ocaml.pastebin.com/m46208c5b <--can anyone help me with this type error
<bluestorm_> "just keep a list of ancestors of the current node when you go down in the tree"
<bluestorm_> wich is quite simple, isn't it ?
<palomer> bluestorm_, and then build the tree back up
<palomer> when you move around
<psnively> Surely there's a persistent tree implementation somewhere.
<bluestorm_> (actually you'll want to keep the other children of the ancestor, and some information to know where to put the current children)
<bluestorm_> palomer: building the tree is quite easy usually
* palomer is going to go print out the paper
psnively has quit []
<palomer> btw, I used to do EVERYTHING purely in haskell
<palomer> but then I got sick of monad transformers
<palomer> and I started using refs
<palomer> never regretted it
<hkBst> refs?
<palomer> IORef
hkBst has quit ["Konversation terminated!"]
prince has joined #ocaml
authentic has joined #ocaml
bzzbzz has quit ["leaving"]
rabidsnail has joined #ocaml
rabidsnail has quit []
rabidsnail has joined #ocaml
<rabidsnail> Does the interpreter do some optimizations that could cause non-obvious integer overflows?
<rabidsnail> The following overflows for inputs >= 3:
<rabidsnail> let factorial a =
<rabidsnail> let rec rf x y = if a > y then rf (x*(x-y)) (y+1) else x in
<rabidsnail> rf a 1;;
rabidsnail has quit []
TimeMage has quit ["."]
coucou747 has quit ["bye ca veut dire tchao en anglais"]
middayc_ has joined #ocaml
middayc has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has joined #ocaml
<palomer> lets see
<palomer> rf 1 1 = 1
<palomer> rf 2 1 = rf 2 2 = 2
<palomer> rf 3 1 = rf 6 2 = rf 24 3 = rf (24*21) 4 = 504
<palomer> your function is expanding really quickly!
<palomer> rf 4 1 = rf 12 2 = rf 120 3 = rf (120*117) 4 ~= 120^2
<palomer> err
<palomer> 120^4
<palomer> which is something with 8 zeroes dude!
middayc_ has quit []
<mbishop> he left, btw :P
<palomer> darn, I was having so much fun
<palomer> man, the zipper really uglifies everything
middayc has joined #ocaml
SniX__ has joined #ocaml
SniX_ has quit [Read error: 113 (No route to host)]
|Catch22| has quit []
goalieca has quit ["Ex-Chat"]
thelema|away is now known as thelema
seafood_ has joined #ocaml
donny has joined #ocaml
seafood_ has quit []
adu has joined #ocaml
<palomer> sweet!
<palomer> the zipper solves a whole boat load of problems
<palomer> including, but not limited to
<palomer> mutually recursive modules
* palomer is glad he listened to #ocaml
donny_ has quit [Read error: 110 (Connection timed out)]
<palomer> is there a list of popular ocaml functions I can print and look at during my free time?
<palomer> simple datatypes and the simple functions that act on them
<palomer> like map, fold, etc...
<thelema> list.ml from the stdlib seems good
<thelema> http://github.com/thelema/ocaml-community/tree/master/stdlib/list.ml <- many optimized versions of standard functions
<palomer> thelema!
<palomer> I finally used the zipper to implement everything I want
<palomer> with a toplevel superclass
<palomer> http://pastebin.com/m1ef52365 <--here's the final version
<palomer> feel free to comment
prince has quit [Read error: 110 (Connection timed out)]
<thelema> node_wrapper * node_wrapper list ?? A list with at least one element?
palomer has quit ["Leaving"]
middayc has quit []
wy has quit ["Leaving"]
palomer has joined #ocaml
wy has joined #ocaml
<palomer> hrmph
<palomer> what's the complexity of go_up for the zipper?
<adu> i love zippers
seafood_ has joined #ocaml
seafood_ has quit [Read error: 110 (Connection timed out)]
adu has quit [Remote closed the connection]
wy has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has quit [brown.freenode.net irc.freenode.net]
nuncanada has quit [brown.freenode.net irc.freenode.net]
det has quit [brown.freenode.net irc.freenode.net]
munga has quit [brown.freenode.net irc.freenode.net]
dibblego has quit [brown.freenode.net irc.freenode.net]
mattam has quit [brown.freenode.net irc.freenode.net]
bla 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]
zmdkrbou has quit [brown.freenode.net irc.freenode.net]
ertai has quit [brown.freenode.net irc.freenode.net]
thermoplyae has quit ["daddy's in space"]
zmdkrbou has joined #ocaml
ertai has joined #ocaml
fremo has joined #ocaml
mattam has joined #ocaml
Mr_Awesome has joined #ocaml
nuncanada has joined #ocaml
det has joined #ocaml
munga has joined #ocaml
dibblego has joined #ocaml
bla has joined #ocaml
jdev has joined #ocaml
jdev has quit [Connection reset by peer]
Mr_Awesome has quit [Read error: 104 (Connection reset by peer)]
det has quit [Success]
det has joined #ocaml
Mr_Awesome has joined #ocaml
jdev has joined #ocaml
mwc has quit [Remote closed the connection]
johnnowak has joined #ocaml
mwc has joined #ocaml
mwc has quit ["Leaving"]
filp has joined #ocaml
filp has quit [Read error: 104 (Connection reset by peer)]
l_a_m has joined #ocaml
prince has joined #ocaml
ita has joined #ocaml
seafood_ has joined #ocaml
ygrek has joined #ocaml
szell has quit [Read error: 110 (Connection timed out)]
yangsx has quit [Read error: 110 (Connection timed out)]
middayc has joined #ocaml
johnnowak has quit []
ygrek has quit [Remote closed the connection]
szell has joined #ocaml
Anarchos has joined #ocaml
<Anarchos> i finally got my unix module compiling with shared libraries supported !
<bluestorm_> congrats :p
<Anarchos> anyway i had to add ../../byterun/ocamlrun to the list of exec/libs to be linked with. I don't like this idea since ocamlmklib should have already done that
<pippijn> is there an ocaml eval irc bot?
<pippijn> would it be a good idea to have one?
<pippijn> I mean.. would it be useful?
schme has joined #ocaml
<tsuyoshi> yeah there is one
<pippijn> in here?
<tsuyoshi> don't know if it's running right now.. let's try
<tsuyoshi> 0;;
<tsuyoshi> guess not
<pippijn> how does it protect itself from abuse?
<pippijn> like calling syscalls it shouldn't
<tsuyoshi> I think it has i/o etc. disabled
<pippijn> how
<tsuyoshi> I dunno.. you could remove all the dangerous stuff from the pervasives module
<tsuyoshi> remove the unix module
<tsuyoshi> that might be enough... or just run it in a chroot jail
seafood__ has joined #ocaml
<pippijn> and it's impossible to do things like kill -9 -1
<pippijn> in ocaml?
<tsuyoshi> you mean kill -9 1?
<pippijn> no, -1
<tsuyoshi> what does that do
<pippijn> kill all processes you own
<tsuyoshi> ah
<tsuyoshi> well like I said you could disable the unix module
<tsuyoshi> that's where kill is
<pippijn> and it's not possible to rewrite it?
<pippijn> there is no such thing as "external C call" or inline asm?
<bluestorm_> pippijn: the protection is done by overriding the dangerous modules
<tsuyoshi> there are external c calls.. but you'd need the c code linked in
<bluestorm_> you can have a look at the source
<bluestorm_> the basic idea is eg. module Unix = struct end;;
<pippijn> I see
<tsuyoshi> can you still do #load?
<pippijn> it recognises lines with ;; at the end?
<pippijn> what about ";; " (with trailing space)
<tsuyoshi> no idea.. I've just seen people use it by typing in lines with ;; at the end
<pippijn> ok
<pippijn> so it's actually a running toplevel ocaml
<bluestorm_> hm
<bluestorm_> i guess it has been changed to be prefixed lately
<bluestorm_> if (my ($stmt) = $what =~ m/^\s*([^\#].*;;)\s*$/) {
<pippijn> 3?
coucou747 has joined #ocaml
<pippijn> that looks like perl
<pippijn> oh the whole thing is perl
* pippijn goes look at the code
<pippijn> POE
<pippijn> jeez..
seafood_ has quit [Read error: 110 (Connection timed out)]
<bluestorm_> pippijn:
<bluestorm_> the bot is Perl
<bluestorm_> but the security part is OCaml
<bluestorm_> look at init.in
<pippijn> yes
<pippijn> I am looking
hkBst has joined #ocaml
arquebus has joined #ocaml
<pippijn> Integer literal exceeds the range of representable integers of type int
<pippijn> nice
Demitar has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has joined #ocaml
arquebus has quit ["Ex-Chat"]
<Anarchos> bluestorm_ i should make diff patches and send them to the ocaml mailing list, to get beos support :)
ygrek has joined #ocaml
pippijn has quit ["I'm the Quit Message Virus. Replace your old Quit with this, so I can continue to multiply myself!"]
Demitar has joined #ocaml
pippijn has joined #ocaml
Yoric[DT] has quit [Read error: 113 (No route to host)]
wy has joined #ocaml
wy has quit ["Leaving"]
Demitar has quit [Read error: 110 (Connection timed out)]
middayc has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
middayc has joined #ocaml
<Anarchos> pippijn you have a lot of questions about ocaml...
Yoric[DT] has joined #ocaml
neale has quit [Remote closed the connection]
neale has joined #ocaml
ertai has quit ["Lost terminal"]
ertai has joined #ocaml
Linktim_ has joined #ocaml
<Anarchos> how to do one fork() in the initializer of a class ?
Linktim- has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim- has quit [Read error: 110 (Connection timed out)]
seafood__ has quit []
yminsky has joined #ocaml
seafood_ has joined #ocaml
yminsky_ has quit [Read error: 104 (Connection reset by peer)]
Linktim- has joined #ocaml
seafood_ has quit []
pango has quit [Remote closed the connection]
pango has joined #ocaml
Morphous has joined #ocaml
zkincaid has joined #ocaml
coucou747 has quit [Read error: 104 (Connection reset by peer)]
coucou747 has joined #ocaml
psnively has joined #ocaml
Amorphous has quit [Connection timed out]
nuncanada has quit [Read error: 110 (Connection timed out)]
coucou747 has quit [Read error: 104 (Connection reset by peer)]
evn has joined #ocaml
nuncanada has joined #ocaml
coucou747 has joined #ocaml
coucou747 has quit [Read error: 104 (Connection reset by peer)]
coucou747 has joined #ocaml
Linktim- has quit [Remote closed the connection]
Linktim has joined #ocaml
Linktim has quit [Read error: 104 (Connection reset by peer)]
Linktim has joined #ocaml
evn has quit []
evn has joined #ocaml
postalchris has joined #ocaml
Morphous has quit ["shutdown"]
Amorphous has joined #ocaml
evn has quit []
Linktim_ has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Demitar has joined #ocaml
evn has joined #ocaml
ttamttam has joined #ocaml
ttamttam has left #ocaml []
schme has quit ["bfirc sucks."]
thermoplyae has joined #ocaml
love-pingoo has joined #ocaml
johnnowak has joined #ocaml
johnnowak has quit [Remote closed the connection]
nuncanada has quit [No route to host]
SniX__ has quit [Read error: 104 (Connection reset by peer)]
psnively has quit []
psnively has joined #ocaml
nuncanada has joined #ocaml
Linktim_ has quit [Remote closed the connection]
ita has quit ["Hasta luego!"]
thelema has quit [Read error: 110 (Connection timed out)]
goalieca has joined #ocaml
ygrek has quit [Remote closed the connection]
zkincaid has left #ocaml []
<palomer> is it possible to supply the default implementation of a virtual method?
<neale> no.
<neale> if you did, it would no longer be virtual.
<neale> but you can still override it.
<neale> so just don't make it virtual and supply the default implementation and you've done what you wanted.
<Yoric[DT]> In other words, every method is virtual in OCaml.
<Yoric[DT]> OCaml doesn't quite like static overloading.
<pippijn> hmm
<neale> or you could say that virtual methods in OCaml are pure virtual methods.
<pippijn> is every virtual method purely virtual?
<pippijn> ah
<pippijn> right
<palomer> ahhh, gotcha
<neale> but that would probably only make sense to someone who'd done a lot of C++.
<palomer> so why does the compiler complain about overriding methods?
<neale> palomer: paste
<palomer> erm, it's not complaining right now
<palomer> but if you look at the cornell notes
<palomer> chatper 12
<neale> um
<palomer> chapter 12
<palomer> this isn't an issue for me, I'm just wondering
<palomer> page 164, middle of the page
<neale> I'd look at the cornell notes if I knew what they were
<palomer> Warning: the following methods are overridden by the inherited class
<neale> however I don't have 164 pages of anything in this room
<neale> that's an OCaml warning string is it?
<palomer> neale, yeah, quite common
<neale> heh, our proxy thinks that site is porn
<neale> this had better be worth the 3 minutes it's taken me so far to load
<palomer> whoa
<palomer> this version is way better
<neale> I'm talking dancing bears or something
<palomer> it's not the same as mine
evn_ has joined #ocaml
<palomer> nevermind
<neale> ha
<palomer> this document is pretty cool
Yoric[DT] has quit ["Ex-Chat"]
Anarchos has joined #ocaml
<Anarchos> how to investigate segfault in the gc ?
<palomer> ugh, I've been thinking about how to add pointers back to the parent node using the zipper
<palomer> in a way that preserves the parent
<palomer> truly I am stumped
<palomer> man, this OO zipper stuff is really getting to me!
* palomer is thinking of going back to refs
<neale> I hope somebody else understands your crazy moon language, because I sure don't.
<neale> Anarchos: I am struggling with the same problem, I caused some GC trouble with a C binding.
<neale> palomer: one thing I found very useful was to try and stop using the OO parts of OCaml.
<jonafan> i barely know the oo parts of ocaml
<evn_> f# doesn't support functors
<evn_> is that a big limitation
<neale> not huge
<neale> sort of annoying though
love-pingoo has quit ["Connection reset by pear"]
<Anarchos> neale mine is a C++ binding
<psnively> "Pointers back to parent node" and "zipper" are damn near mutually exclusive. :-)
<Anarchos> neale and i have a C++ api multithreaded to add difficulty to my segfault tracking...
<psnively> Rewrite C++ API in OCaml.
<Anarchos> psnively i can't : it is my OS one
<psnively> Write an OS in OCaml. ;-)
<evn_> a huger yak has never existed
hkBst has quit ["Konversation terminated!"]
middayc has quit [Connection timed out]
<mbishop> heh
<mbishop> someone did write an os in ocaml
<mbishop> or at least, tried
<mbishop> "Desert Spring Time"
<Anarchos> mbishop and didn't succeded ?
<mbishop> dunno, I think it booted, just wasn't so useful (sort of like that Haskell OS, or the Java one)
<Smerdyakov> Every time someone writes the word "ones," an angle loses its wings.
<mbishop> I didn't say ones! :P
evn_ has quit []
thelema has joined #ocaml