dylan changed the topic of #ocaml to: OCaml 3.09.1 available! Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
<holo> while bla do done ?
<ketty> yes :)
<holo> let x = -1;;
<holo> let inc = fun x -> x+1;;
<holo> let rec funcao str x =
<holo> match (nth_char( str (inc(x)) ) ) with
<holo> `.` -> ""
<holo> |_ -> string_of_char(x)^(funcao str x );;
<holo> :D
<holo> it looks a bit not caml, but its just a little
<ketty> you have a lot of un-needed parenteces...
<holo> have i sinned?
<holo> ketty, i am with a lot of non-patience too
<holo> :D
<ketty> and you do c-style parentecing...
<ketty> like string_of_char(x)...
<holo> yeah
<ketty> if you want to go paranoid and parentece it you should do: (string_of_char x)
<holo> lolol
<ketty> hmm.. does your function work as expected?
<holo> oh
<holo> i don't know
<holo> it must
<ketty> you should do the increacement in the function call...
<ketty> funcao str (x+1)
<holo> lol
<holo> yeah
cricket has quit [Read error: 104 (Connection reset by peer)]
<ketty> and: nth_char( str (inc(x)) )
<ketty> probably dont work as expected...
<holo> er
<ketty> unless string is a function :)
<ketty> i mean str is a function
<holo> str is a string
<ketty> then this wont work :)
<holo> why?
<holo> nth_char is for strings
<holo> it takes a char from it
<holo> a nth char
<ketty> you probably meant: nth_char str (inc x)
<holo> oh
<holo> yes
<holo> that
<holo> but not inc anymore
<ketty> no
<holo> just nth_char str x
<ketty> yes
<ketty> all those parenteces goes away! :)
<holo> you have a caml thoght
<holo> the match ( ) with must stay no?
<ketty> no
<ketty> match nth_char str x with
<ketty> allthou the ( ) wont change the meaning of the code in this case
<ketty> so you could use them if you think it makes it more readble...
<holo> let x = -1;;
<holo> let rec funcao str (x+1) =
<holo> match nth_char str x with
<holo> `.` -> ""
<holo> |_ -> string_of_char x^funcao str x ;;
<ketty> hmm...
<ketty> almost :)
<ketty> you chose the wrong funcao to make the increasment in thou :)
<ketty> making it in the definition probably is a syntax error...
Submarine has joined #ocaml
<holo> yeah and x+1 is not x
<ketty> and you dont need to define x either...
<ketty> x is "defined" when you call the function...
<holo> yeah, but i want it zero
<ketty> then you want to call the function with a zero value :)
<holo> yep but i can't put it there becouse its rec
<ketty> hmm?
<holo> let rec funcao str 0
<ketty> let rec funcao str x = match nth_char str x with
<ketty> (02:26:31) holo: `.` -> ""
<ketty> (02:26:31) holo: |_ -> string_of_char x^funcao str x ;;
<ketty> ehhh... sorry
<ketty> :)
<holo> ha
<ketty> i messed up :)
<ketty> but what i wanted to say is...
<ketty> after you define your recursive function you call it with the desired arguments :)
<ketty> so if you want x to be zero
<ketty> you call it with the x argument as zero
<ketty> simple, no?
<holo> er
<holo> i yeah
<holo> you're right
<holo> geez
<holo> let inc = fun x -> x+1;;
<holo> let rec funcao str x =
<holo> match nth_char str (inc x) with
<holo> `.` -> ""
<holo> |_ -> string_of_char x^funcao str x ;;
<holo> hmm no
<ketty> what to do if you want to get rid of inc?
<holo> aha
<holo> i know
<holo> wait
<holo> let rec funcao str x =
<holo> match nth_char str x with
<holo> `.` -> ""
<holo> |_ -> string_of_char x^funcao str (x+1) ;;
<ketty> yes, great! :)
<holo> :)
<holo> geez i got rid of much code
<holo> thanks ketty, you enlighted me
<holo> at least for some minutes :s
<ketty> you could do a wrapper function that calls funcao
<holo> ketty, i was thinking about that too
<holo> and would have 0 argument
<ketty> let f str = funcao str 0
<holo> but that's just a detail
dark_light has joined #ocaml
<holo> ketty you ment:
<holo> let funcao2 str 0 =
<holo> let rec funcao str x =
<holo> match nth_char str x with
<holo> `.` -> ""
<holo> |_ -> string_of_char x^funcao str (x+1) ;;
<holo> sorry for pasting the whole function
<ketty> almost :)
<holo> ha!
<holo> i understood yours
<ketty> this wont do anything interesting thou :)
<holo> yeah
<holo> but that's nice
<ketty> your version currently does exactly nothing :)
<ketty> but you are right in wraping the function inside of the other...
<ketty> that way you don't pollute the namespace...
<ketty> you understand whats wrong with your last example?
<holo> hmm
<holo> x is not bound to 0
<ketty> you have to remember that even thou a recursive function is used as a replacement for loops it is not a loop
<ketty> it is still just a function
<ketty> it just happens to call itself sometimes...
<holo> hmm
<ketty> so when you define a function or a recursive function nothing is returned...
<ketty> you just make a definition
<ketty> to actually "use" your function you have to call it...
<holo> lol
<holo> dude of course
<holo> :D
<holo> i was twisting my function to know what was stil wrong
<holo> funcao2 str 0
<holo> funcao str x
<holo> x is bound to 0?
<ketty> no :)
<holo> so it seems
<holo> so, if didn't want to pollute the namespace, how would i do?
<ketty> funcao2 str = <body of funcao (+ "in")> funcao str 0
<ketty> :)
<holo> haa
<holo> wait
<ketty> you understand what "in" means?
<holo> yeah
<holo> i used it much times
<ketty> hmm.. i probably reverse the names of the functions...
<ketty> so funcao is the outer function..
<ketty> but then again i have no clue what the name funcao is about :)
<holo> ketty, its just name function in portuguese
<holo> i was without imagination
slipstream-- has quit [Remote closed the connection]
shawn has quit ["This computer has gone to sleep"]
<ketty> holo: ok, :) when i am without imagination i usually name them "f"
<ketty> or "stupid function"
<ketty> ehh stupid_function :)
slipstream has joined #ocaml
<ketty> or weird_variable
<holo> |_ -> string_of_char x^funcao str (x+1)
<holo> This expression has type char,
<holo> but is used with type int.
<holo> on x
<holo> of funcao str (x+1)
<ketty> ohh :)
<holo> hmm it smell like {}
<holo> ()
<ketty> | c -> string_of_char c ^ funcao str (x+1)
<ketty> maybe? :)
<ketty> since the variable x was used as argument to the function string_of_char
<ketty> the compiler assumed that x was a char
<ketty> and then when x was used in (x + 1) it gave you the error because
<ketty> you cant add a 1 to a char...
<holo> lol
<holo> and it is
<holo> but i forgot nth_char
<ketty> or the real reason is that (x) is a function that takes two ints...
<holo> lol
<ketty> i mean (+) is a function that takes two ints, sorry :)
<ketty> *damn similar symbols ^^*
<holo> suppose i have:
<holo> let rec funcao str x =
<holo> bla bla
<holo> in funcao str 0;;
<holo> it's not like this what you said
<ketty> that looks like what i had in mind...
<ketty> and this all should be inside the other function... :)
<holo> hmm
<holo> ok ok
<holo> but that doesn't make the x always 0 in every iteration?
<ketty> no, not as long as you increase it in the recursive function calls...
<ketty> but i am a bit worried about your "stop case"
<ketty> if the nth_char was '.' you stopped right?
<ketty> are you sure that your function allways will terminate
<ketty> or maybe it will recurse forever?
<holo> it wont, becouse the string *has* "."
<holo> `.`
<holo> that is a given fact
<holo> i just don't know where
<ketty> ahh so your function returns the part of the string before the '.'?
<holo> ketty, yeah :D
<holo> this as some type error
<ketty> does it work?
<holo> its a function to return the object and then i make other function to return the attribute
<holo> no
<holo> ketty, you have a cammlight compiler right?
<holo> :o
<ketty> no :)
<holo> interpreter
<holo> i mean
<ketty> i only have ocaml :)
<holo> argh
<holo> nth_char x
<holo> This expression has type int -> char,
<holo> but is used with type char.
<holo> omfg
<holo> sorry dude
<holo> i'm almost dead as in sleepy mode
<ketty> :)
<holo> now it runs
<ketty> and works?
<holo> ketty, yeah!
<ketty> great! :)
<holo> now to return the attribute i just need to follow the same logic
<holo> and make other similar function
<holo> ketty, you're the man
<holo> thank you very much
khaladan has quit [" HydraIRC -> http://www.hydrairc.com <- IRC has never been so good"]
<holo> i have to go sleep
<holo> :(
<ketty> nice dreams ^^
<holo> yeah thanks
<holo> and i learned some things
<holo> hey ketty if you are a girl sorry for calling you dude
<holo> :s
<ketty> no offence taken :)
altDanly has joined #ocaml
danly has quit [Read error: 110 (Connection timed out)]
holo has quit ["This computer has gone to sleep"]
Submarine has quit ["Leaving"]
shawn has joined #ocaml
_shawn has quit [Read error: 110 (Connection timed out)]
_shawn has joined #ocaml
revision17__ has quit ["Ex-Chat"]
bohanlon has quit [Client Quit]
bohanlon has joined #ocaml
love-pingoo has joined #ocaml
AI_coder has quit ["QuIRC for *nix - http://quirc.org/"]
Tachyon76 has joined #ocaml
Smerdyakov has quit ["Leaving"]
vinceviper has joined #ocaml
vinceviper has quit [Remote closed the connection]
pango is now known as pangoafk
altDanly is now known as danly
Revision17 has joined #ocaml
dark_light has quit [Read error: 110 (Connection timed out)]
dark_light has joined #ocaml
mrsolo__ has quit [Read error: 110 (Connection timed out)]
theArthur has joined #ocaml
ppsmimou has quit ["Leaving"]
ppsmimou has joined #ocaml
revision17__ has joined #ocaml
Revision17 has quit [Read error: 110 (Connection timed out)]
ppsmimou has quit ["Leaving"]
ppsmimou has joined #ocaml
shawn has left #ocaml []
<ulfdoz> Is there a strategy for are complete ordering of pairs?
<ulfdoz> The order itself is unimportant, I just want to use the Set module.
<ulfdoz> s/are/a/1
shawn has joined #ocaml
<ulfdoz> Ehm, forget the question, it is enough for me to order over the first element of the pair.
<ppsmimou> ulfdoz: you can just use the < of caml
<ppsmimou> it works on pairs too
<ulfdoz> Oh, good to know, that makes it easier.
vin100 has joined #ocaml
Skal has joined #ocaml
Snark has joined #ocaml
Skal has quit [Remote closed the connection]
pauldia has joined #ocaml
pangoafk is now known as pango
<ulfdoz> module type AttrSet = Set.S;;
<ulfdoz> module FunDep = functor (Body : AttrSet) ->
<ulfdoz> functor (Head : AttrSet with type t = Body.t) ->
<ulfdoz> struct
<ulfdoz> type t = Body.t
<ulfdoz> let equal = Body.equal Body Head and
<ulfdoz> is_trivial = Body.subset head body or equal
<ulfdoz> end;;
<ulfdoz> I do not understand, why this doesn't work.
<ulfdoz> as I understand, the functors give me an implementation of an Implementation of module type AttrSet, but how to access the AttrSets?
mikeX has joined #ocaml
<mikeX> are the modules Lexer and Parser renamed to Lexing and Parsing in 3.09.1?
<mikeX> hmm, no that's not it, the manual is too confusing :(
<pango> ulfdoz: From what I understand, functors are like functions in modules space... so FunDep is a "module of two arguments" (two module of type AttSet, with a constraint between the two)
<ulfdoz> So I seem to have messed up modules and types.
<pango> I don't understand what you're trying to achieve, so I can't tell ;)
shrimpx has joined #ocaml
shrimpx_ has quit [Read error: 110 (Connection timed out)]
ulfdoz has quit [zelazny.freenode.net irc.freenode.net]
ulfdoz has joined #ocaml
vin100 has quit ["Kopete 0.11 : http://kopete.kde.org"]
Tachyon76 has quit ["Leaving"]
ptolomy has joined #ocaml
ptolomy has quit ["Chatzilla 0.9.72 [Firefox 1.5.0.1/2006011112]"]
cricket has joined #ocaml
<cricket> any SML'ers?
<love-pingoo> I once translated some SML into Caml, so I know a tiny little bit, but I doubt it can be useful
Oejet has joined #ocaml
<cricket> damn
<love-pingoo> you should ask on #sml
Smerdyakov has joined #ocaml
Banana has quit ["leaving"]
Banana has joined #ocaml
<cricket> that chan is dead
cricket has quit ["BitchX-1.1-final -- just do it."]
<ketty> woot! #sml is dead and we are almost not dead! =)
descender has joined #ocaml
pauldia has quit [Read error: 110 (Connection timed out)]
pango is now known as pangoafk
<Quinthius> hmm
<ulfdoz> Is there any "nice to have"-Book about OCaml and functional programming in general? Haven't found anything from the last 10 years in the library.
<Oejet> ulfdoz: SICP would be such a book. It seems the one mentioned in the subject is nice also, but online.
pangoafk is now known as pango
<ulfdoz> Hey, cool. And I prepared to spend money.
<Oejet> There are other nice online OCaml books. You can probably find them from ocaml.org.
<ulfdoz> I know the "developing Applications with OCaml". But there are no theoretical aspects in it, which would help to understand the background and why it is done this way.
<Oejet> How about this, I just stumbled upon: http://www.cl.cam.ac.uk/users/lcp/papers/Notes/Founds-FP.pdf
<ulfdoz> will read it, seems to be not that much. :)
<Oejet> Let me know, if it's any good, then I'll read it too. ;-)
Bigb[a]ng is now known as Bigbang
_JusSx_ has joined #ocaml
<_JusSx_> HI OCAML PPL
<ketty> hello _JusSx_
<_JusSx_> any news??
ski has joined #ocaml
LimeKMag has joined #ocaml
Oatmeat|umn has quit [Read error: 104 (Connection reset by peer)]
revision17__ has quit ["Ex-Chat"]
mecolin has joined #ocaml
<mecolin> hello
<mecolin> does somebody use a tuareg mode with emacs? It overrides my default highlighting and I have no clue how to get ride of that...
Oatmeat|umn has joined #ocaml
Snark has quit ["Leaving"]
<ulfdoz> just stumbled across this, at least it looks interesting: http://people.csail.mit.edu/dnj/teaching/6898/projects/vicente-wagner.pdf
<pango> yes, crap ;)
holo has joined #ocaml
<holo> hi
<ketty> hello ^^
<holo> i'm having a problem defining a type of non-terminal symbols
slipstream-- has joined #ocaml
<holo> ketty, hello!
<ketty> im not sure if it matters if they are "terminal"...
<holo> i can't do type token = INT of int | IDENT of string | DOT of string | Expr ( INT * DOT * IDENT);;
<holo> ketty, if they are not defined looks like it matters
slipstream has quit [Read error: 104 (Connection reset by peer)]
<ketty> should be Expr of ...
<holo> becouse he doesn't know what is INT yet
<holo> becouse it wasn't evaluated
<holo> oh oh
<holo> yeah
<holo> i typed that now
<holo> so that error is normal
<holo> but not the problem
<ketty> hmm...
<ketty> it could be solved by defining INT etc before...
<holo> i can't do that becouse that will conflit with other tokens in branches of a match with
<holo> they will have different types
<holo> like token1 and token2
<holo> in theory
<ketty> you could do Expr of int * string * string
<holo> ketty, yes but that won't do the job becouse i want INT to be the same name as the "int" of Expr
<holo> when it is read by the sintax analyser
<holo> houston houston we've got a problem
<ketty> Expr of token list ?
<ski> what does 'INT' mean, here ?
<holo> i tried Expr of (INT of int) * (DOT of string) * (IDENT of string) but gave syntax error, it musted be awaiting a type only syntax
<holo> ski, means int
<holo> INT of int
<holo> its there the meaning
<ski> hrm
<holo> ski, yes i must do that becouse i want to do INT number in functions
<ski> you can't use the constructor names 'INT','DOT','IDENT' as if they were types
<flux__> type token = Expr of int_expr * dot * ident and int_expr = Int of int and dot = Dot of string and ident = Ident of string
<ski> are you sure you want 'INT','IDENT','DOT','Expr' as constructors in the same type ?
<holo> ski, as a consequence of my problem, no.
<holo> ski yes i'm sure
<ski> holo : i.e. would what flux__ suggested work =
<ski> s/=/?/
<holo> ok
<holo> hmm nice
<holo> it works
<holo> flux__, very nice!
<flux__> happy to be of help
<holo> Type token defined.
<holo> Type int_expr defined.
<holo> Type dot defined.
<holo> Type ident defined.
<holo> so it is as if i defined int_expr , dot and ident before token
<ketty> or rather at the same time :)
<flux__> yes, well, or simultaneously, but that doesn't matter here
<ketty> they could mutaly depend on eachother...
_JusSx_ has quit ["leaving"]
<holo> :)
<ski> you could have defined 'token' last, and the other three in some order (possibly at same time) before that ..
<holo> yeah
<holo> let rec ident2_of_dot_field str x =
<holo> match nth_char str x with
<holo> `a`..`z` -> string_of_char(nth_char str x) ^ ident2_of_dot_field str (x+1)
<holo> | `` -> "";;
<holo> `` is bad formed
<ketty> there is no such thing as an empty char...
<holo> i wanted to mean that if there is not another caracter to be read
<holo> ketty, i noticed :s
<ketty> what happens when you call nth_char with a to big x?
<ketty> you will get an error right?
<holo> ketty, this doesn't even evaluate
<ketty> before the match you could compare x to the length of the string...
<ketty> would that solve things?
<flux__> `a` is not ocaml either
<flux__> you mean 'a'
<holo> flux__, t #let x = `c`;;
<holo> x : char = `c`
<ketty> weird :/
<holo> flux__, i don't know about ocaml, but this works in camllight
<ketty> doesn't work in ocaml...
<holo> well, incompatible implementations
<flux__> `Foo itself is valid ocaml, btw
<flux__> I'm usually assuming people are talking about ocaml in, well, #ocaml.. ;)
<holo> flux__, #camllight doesn't exist :s
<holo> and caml if exists has one or two ppl
<holo> *#caml
mrsolo__ has joined #ocaml
jcreigh has joined #ocaml
jcreigh has quit ["leaving"]
smimou has joined #ocaml
holo has quit ["This computer has gone to sleep"]
Skal has joined #ocaml
Bigbang is now known as Bigb[a]ng
rillig has joined #ocaml
perspectivet has joined #ocaml
smimou has quit ["bli"]
Skal has quit [Remote closed the connection]
neax has joined #ocaml
love-pingoo has quit [Read error: 110 (Connection timed out)]
ulfdoz has quit [zelazny.freenode.net irc.freenode.net]
shawn has quit [zelazny.freenode.net irc.freenode.net]
dark_light has quit [zelazny.freenode.net irc.freenode.net]
Oejet has quit [zelazny.freenode.net irc.freenode.net]
bohanlon has quit [zelazny.freenode.net irc.freenode.net]
danly has quit [zelazny.freenode.net irc.freenode.net]
Demitar has quit [zelazny.freenode.net irc.freenode.net]
ketty has quit [zelazny.freenode.net irc.freenode.net]
neax has quit [zelazny.freenode.net irc.freenode.net]
perspectivet has quit [zelazny.freenode.net irc.freenode.net]
rillig has quit [zelazny.freenode.net irc.freenode.net]
Oatmeat|umn has quit [zelazny.freenode.net irc.freenode.net]
ski has quit [zelazny.freenode.net irc.freenode.net]
LimeKMag has quit [zelazny.freenode.net irc.freenode.net]
ppsmimou has quit [zelazny.freenode.net irc.freenode.net]
TaXules has quit [zelazny.freenode.net irc.freenode.net]
Hadaka has quit [zelazny.freenode.net irc.freenode.net]
dvekravy has quit [zelazny.freenode.net irc.freenode.net]
julbouln has quit [zelazny.freenode.net irc.freenode.net]
flux__ has quit [zelazny.freenode.net irc.freenode.net]
mecolin has quit [zelazny.freenode.net irc.freenode.net]
_shawn has quit [zelazny.freenode.net irc.freenode.net]
zmdkrbou has quit [zelazny.freenode.net irc.freenode.net]
theArthur has quit [zelazny.freenode.net irc.freenode.net]
Bigb[a]ng has quit [zelazny.freenode.net irc.freenode.net]
pango has quit [zelazny.freenode.net irc.freenode.net]
det has quit [zelazny.freenode.net irc.freenode.net]
pattern has quit [zelazny.freenode.net irc.freenode.net]
neax has joined #ocaml
perspectivet has joined #ocaml
rillig has joined #ocaml
Oatmeat|umn has joined #ocaml
mecolin has joined #ocaml
LimeKMag has joined #ocaml
ski has joined #ocaml
Oejet has joined #ocaml
ulfdoz has joined #ocaml
shawn has joined #ocaml
ppsmimou has joined #ocaml
theArthur has joined #ocaml
dark_light has joined #ocaml
bohanlon has joined #ocaml
_shawn has joined #ocaml
danly has joined #ocaml
ketty has joined #ocaml
zmdkrbou has joined #ocaml
Demitar has joined #ocaml
TaXules has joined #ocaml
Hadaka has joined #ocaml
Bigb[a]ng has joined #ocaml
julbouln has joined #ocaml
dvekravy has joined #ocaml
flux__ has joined #ocaml
det has joined #ocaml
pango has joined #ocaml
pattern has joined #ocaml
altDanly has joined #ocaml
ulfdoz has quit [zelazny.freenode.net irc.freenode.net]
ketty has quit [zelazny.freenode.net irc.freenode.net]
Oejet has quit [zelazny.freenode.net irc.freenode.net]
dark_light has quit [zelazny.freenode.net irc.freenode.net]
shawn has quit [zelazny.freenode.net irc.freenode.net]
danly has quit [zelazny.freenode.net irc.freenode.net]
Demitar has quit [zelazny.freenode.net irc.freenode.net]
bohanlon has quit [zelazny.freenode.net irc.freenode.net]
dvekravy has quit [zelazny.freenode.net irc.freenode.net]
flux__ has quit [zelazny.freenode.net irc.freenode.net]
LimeKMag has quit [zelazny.freenode.net irc.freenode.net]
Hadaka has quit [zelazny.freenode.net irc.freenode.net]
TaXules has quit [zelazny.freenode.net irc.freenode.net]
julbouln has quit [zelazny.freenode.net irc.freenode.net]
mecolin has quit [zelazny.freenode.net irc.freenode.net]
neax has quit [zelazny.freenode.net irc.freenode.net]
perspectivet has quit [zelazny.freenode.net irc.freenode.net]
rillig has quit [zelazny.freenode.net irc.freenode.net]
ppsmimou has quit [zelazny.freenode.net irc.freenode.net]
ski has quit [zelazny.freenode.net irc.freenode.net]
Oatmeat|umn has quit [zelazny.freenode.net irc.freenode.net]
pango has quit [zelazny.freenode.net irc.freenode.net]
Bigb[a]ng has quit [zelazny.freenode.net irc.freenode.net]
det has quit [zelazny.freenode.net irc.freenode.net]
_shawn has quit [zelazny.freenode.net irc.freenode.net]
theArthur has quit [zelazny.freenode.net irc.freenode.net]
zmdkrbou has quit [zelazny.freenode.net irc.freenode.net]
pattern has quit [zelazny.freenode.net irc.freenode.net]
slipstream-- has quit [Remote closed the connection]
slipstream has joined #ocaml
mrsolo__ has quit [Killed by ballard.freenode.net (Nick collision)]
mrsolo__ has joined #ocaml
neax has joined #ocaml
perspectivet has joined #ocaml
rillig has joined #ocaml
Oatmeat|umn has joined #ocaml
mecolin has joined #ocaml
LimeKMag has joined #ocaml
ski has joined #ocaml
Oejet has joined #ocaml
ulfdoz has joined #ocaml
shawn has joined #ocaml
ppsmimou has joined #ocaml
theArthur has joined #ocaml
dark_light has joined #ocaml
bohanlon has joined #ocaml
_shawn has joined #ocaml
danly has joined #ocaml
ketty has joined #ocaml
zmdkrbou has joined #ocaml
Demitar has joined #ocaml
TaXules has joined #ocaml
Hadaka has joined #ocaml
Bigb[a]ng has joined #ocaml
julbouln has joined #ocaml
dvekravy has joined #ocaml
flux__ has joined #ocaml
det has joined #ocaml
pango has joined #ocaml
pattern has joined #ocaml
CLxyz has quit [SendQ exceeded]
ulfdoz has quit [zelazny.freenode.net irc.freenode.net]
ketty has quit [zelazny.freenode.net irc.freenode.net]
Oejet has quit [zelazny.freenode.net irc.freenode.net]
dark_light has quit [zelazny.freenode.net irc.freenode.net]
shawn has quit [zelazny.freenode.net irc.freenode.net]
danly has quit [zelazny.freenode.net irc.freenode.net]
Demitar has quit [zelazny.freenode.net irc.freenode.net]
bohanlon has quit [zelazny.freenode.net irc.freenode.net]
dvekravy has quit [zelazny.freenode.net irc.freenode.net]
mrsolo__ has quit [zelazny.freenode.net irc.freenode.net]
flux__ has quit [zelazny.freenode.net irc.freenode.net]
LimeKMag has quit [zelazny.freenode.net irc.freenode.net]
Hadaka has quit [zelazny.freenode.net irc.freenode.net]
TaXules has quit [zelazny.freenode.net irc.freenode.net]
julbouln has quit [zelazny.freenode.net irc.freenode.net]
mecolin has quit [zelazny.freenode.net irc.freenode.net]
neax has quit [zelazny.freenode.net irc.freenode.net]
perspectivet has quit [zelazny.freenode.net irc.freenode.net]
rillig has quit [zelazny.freenode.net irc.freenode.net]
ppsmimou has quit [zelazny.freenode.net irc.freenode.net]
ski has quit [zelazny.freenode.net irc.freenode.net]
Oatmeat|umn has quit [zelazny.freenode.net irc.freenode.net]
pango has quit [zelazny.freenode.net irc.freenode.net]
Bigb[a]ng has quit [zelazny.freenode.net irc.freenode.net]
det has quit [zelazny.freenode.net irc.freenode.net]
_shawn has quit [zelazny.freenode.net irc.freenode.net]
theArthur has quit [zelazny.freenode.net irc.freenode.net]
zmdkrbou has quit [zelazny.freenode.net irc.freenode.net]
pattern has quit [zelazny.freenode.net irc.freenode.net]
mrsolo__ has joined #ocaml
neax has joined #ocaml
perspectivet has joined #ocaml
rillig has joined #ocaml
Oatmeat|umn has joined #ocaml
mecolin has joined #ocaml
ski has joined #ocaml
Oejet has joined #ocaml
ulfdoz has joined #ocaml
shawn has joined #ocaml
ppsmimou has joined #ocaml
theArthur has joined #ocaml
dark_light has joined #ocaml
bohanlon has joined #ocaml
_shawn has joined #ocaml
ketty has joined #ocaml
zmdkrbou has joined #ocaml
Demitar has joined #ocaml
TaXules has joined #ocaml
Hadaka has joined #ocaml
Bigb[a]ng has joined #ocaml
julbouln has joined #ocaml
dvekravy has joined #ocaml
flux__ has joined #ocaml
det has joined #ocaml
pango has joined #ocaml
pattern has joined #ocaml
slipstream has quit [Remote closed the connection]
slipstream has joined #ocaml
joshcryer has quit [Client Quit]
joshcryer has joined #ocaml
Narrenschiff has quit ["Leaving"]
sym0r_ has joined #ocaml
neax has quit [Read error: 110 (Connection timed out)]
sym0r_ has quit [Read error: 104 (Connection reset by peer)]
sym0r__ has joined #ocaml