rwmjones changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.1 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
ManarD- has quit [Remote closed the connection]
jlouis_ has quit ["leaving"]
jlouis has quit [Read error: 110 (Connection timed out)]
bzzbzz has joined #ocaml
<Yoric[DT]> mfp: thanks
<mfp> Yoric[DT]: so LazyMonad is faster than SimpleMonad because it doesn't have to box success values, and the use of the internal MonadicException allows to skip all the Failure f -> ... matching?
<Yoric[DT]> That's the idea.
<Yoric[DT]> I haven't actually tested performances.
<mfp> yet you said that it executes much faster than Haskell ;)
<Yoric[DT]> Then I must be tired, I meant to say that it should execute much faster than Haskell.
<Yoric[DT]> (since it's past 1am, I am probably tired indeed)
<mfp> don't know, GHC is smarter when it comes to removing closures, so maybe it can also get rid of the boxing
yminsky has joined #ocaml
<mfp> Yoric[DT]: may I quote you (<me>... so LazyMonand is .... <Yoric[DT]> ...) in a reddit comment?
<mfp> *Monad
mbishop_ has joined #ocaml
lbc has left #ocaml []
<Yoric[DT]> Sure.
* Yoric[DT] hopes he's not selling his soul.
* Yoric[DT] is too tired to be sure.
* mfp ponders whether to include "I haven't actually tested performances."
postalchris has quit [Read error: 110 (Connection timed out)]
<mfp> not doing so might increase the changes of somebody benchmarking equivalent hs for us }:-)
<mfp> *chances
<mbishop_> What are you guys talking about?
<mfp> (same timezone, 2am here too...)
<Yoric[DT]> I've just done that :)
<Yoric[DT]> mbishop_ my exception monads for OCaml.
<mfp> mbishop_: your reddit post
<mbishop_> oh, heh :)
<Yoric[DT]> I've updated the page, that is.
<Yoric[DT]> I don't even know how to work with reddit.
<mfp> by saying it's faster than haskell, you automatically get a response from dons + somebody benchmarking it for us }:-)
<Yoric[DT]> :)
mbishop has quit [Read error: 110 (Connection timed out)]
<mfp> I recently saw somebody in #haskell rallying ppl to upmod a haskell article
mbishop_ is now known as mbishop
<mfp> don't know if that's customary
<mfp> but hey, conspiracy theories are fun
seafood_ has joined #ocaml
thermoplyae has joined #ocaml
<Yoric[DT]> Well, I'm too tired to think about conspiracies.
<Yoric[DT]> So I'm going to wish you a pleasant night.
Yoric[DT] has quit ["Ex-Chat"]
bzzbzz_ has joined #ocaml
bzzbzz has quit [Read error: 110 (Connection timed out)]
thermoplyae has left #ocaml []
AxleLonghorn has joined #ocaml
adu has joined #ocaml
middayc_ has quit []
seafood_ has quit []
__suri has joined #ocaml
adu has left #ocaml []
Snrrrub__ has quit [Read error: 110 (Connection timed out)]
jderque has joined #ocaml
pango has quit [Remote closed the connection]
AxleLonghorn has left #ocaml []
pango has joined #ocaml
jderque has quit [Read error: 113 (No route to host)]
ttamttam has joined #ocaml
Yoric[DT] has joined #ocaml
olleolleolle has joined #ocaml
olleolleolle has left #ocaml []
alkoma has joined #ocaml
<alkoma> this is probably a silly question: how can I specify the type of a function without actually defining it? ie: val foo : 'a -> bool
<flux> hmm
<flux> what do you mean?
<flux> specify without specifying?
<alkoma> I mean declare the type of a function (like giving it interface), but not providing a (body) definition.
<Yoric[DT]> Where do you want to do that ?
<Yoric[DT]> If you mean prototypes as in C, so as to be able to call a function before having actually defining it, there's no such thing in OCaml (well, unless you start writing several modules).
<alkoma> I know I can do that in a module, but this is just a regular function.
<Yoric[DT]> If you mean interfaces as in Java, so as to be able to distribute specifications, you can either use modules (that's the granularity of specifications in OCaml) or let OCaml do the type inference.
<alkoma> Probably it's not necessary, since the type is inferred correctly anyway.
<alkoma> ...yes
<alkoma> the example I am writing is a dfs (depth first search) function: let dfs goal succ init = ... where goal and succ are function that takes a node and return true/false (goal) or return all the successor node.
filp has joined #ocaml
<flux> alkoma, do you mean this? let foo : int -> int = fun i -> i + 1 ?
<flux> some prefer let foo (i : int) : int = i + 1
<flux> also you can do module Foo : sig val foo : int -> int end = struct let foo i = i + 1 end
<flux> that's the way to guarantee that your function won't turn out to be more specific than what you specified
<flux> for example this is correct: let foo : 'a -> 'a = fun i -> i + 1
<flux> it will however define function foo : int -> int
<flux> but with module signatures the match must be exact
<flux> no need to privmsg me..
<alkoma> flux: I get it. define it in a sig is the way to go ...
<flux> alkoma, if you want to define functions of certain prototype but you don't have an implementation around, you can do: let foo : int -> int = fun i -> failwith "foo: not implemented"
<flux> I use that quite often
<flux> code still compiles, without putting everything in
<alkoma> I see. thanks!
Yoric[DT] has quit ["Ex-Chat"]
Tetsuo has joined #ocaml
alkoma has quit [Read error: 110 (Connection timed out)]
munga has joined #ocaml
madroach has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
Demitar has joined #ocaml
madroach has quit [Remote closed the connection]
kbidd has quit [Read error: 104 (Connection reset by peer)]
kbidd has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
olegfink has joined #ocaml
hkBst has joined #ocaml
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has joined #ocaml
jderque has joined #ocaml
ttamttam has left #ocaml []
olleolleolle has joined #ocaml
<olegfink> hi, I need some explanation of lazy evaluation in ocaml.
<olegfink> I want to know the first natural number
<olegfink> I have:
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
<olegfink> let rec gen n = n::(gen (n+1))
jlouis has joined #ocaml
<olegfink> then I have let n = lazy (gen 1)
<rwmjones> olegfink, you understand that the definition of 'gen' isn't lazy, so it's basically an infinite loop?
<olegfink> mhm, but n is lazy, isn't it?
* rwmjones wakes up xavierbot
xavierbot has joined #ocaml
<tsuyoshi> if you ever force n it will go into an infinite loop
<olegfink> so I need a lazy gen? but how?
<tsuyoshi> so as written those two lines are pretty useless
<rwmjones> hmm
<rwmjones> this sounds like a university question
<rwmjones> what's the real problem?
Mr_Awesome has joined #ocaml
<olegfink> there's no real problem here, I'm just trying to understand what ocaml has about lazy evalutation. So far I couldn't move to anything more useful than suspending 2+2.
<olegfink> *evluation
<olegfink> meh.
<rwmjones> olegfink, lazy is really just a shorthand for writing 'fun () -> (* some calculation *)'
<rwmjones> although the implementation is more efficient than that
<rwmjones> open Lazy ;;
<xavierbot> Characters 0-9:
<xavierbot> open Lazy ;;
<xavierbot> ^^^^^^^^^
<xavierbot> Unbound module Lazy
olleolleolle has left #ocaml []
xavierbot has quit [Remote closed the connection]
xavierbot has joined #ocaml
<rwmjones> open Lazy;;
<xavierbot> Characters 0-9:
<xavierbot> open Lazy;;
<xavierbot> ^^^^^^^^^
<xavierbot> Unbound module Lazy
Snark has joined #ocaml
xavierbot has quit [Remote closed the connection]
xavierbot has joined #ocaml
<flux> rwmjones, it's actually also a shorthand for keeping the result of that evaluation around in order not to evaluate it again :)
<olegfink> ocaml manual lacks any examples of using it.
<rwmjones> yeah, I was simplifying
<rwmjones> open Lazy;;
<rwmjones> let's see if I can write this cold ...
<olegfink> the problem with my understanding is that things like :: constructor and List.hd want 'a and 'a list, and all I have is 'a list lazy_t.
<rwmjones> type 'a lazy_list = Empty | Cons of 'a * 'a lazy_list ;;
<xavierbot> type 'a lazy_list = Empty | Cons of 'a * 'a lazy_list
<rwmjones> I think you want to define a new list type as above
<olegfink> ah
<rwmjones> obviously that won't work with the existing List.* functions, so you will need to define your own as necessary
<rwmjones> let rec gen n = Cons (n, lazy (gen (n+1))) ;;
<xavierbot> Characters 26-42:
<xavierbot> let rec gen n = Cons (n, lazy (gen (n+1))) ;;
<xavierbot> ^^^^^^^^^^^^^^^^
<xavierbot> This expression has type int lazy_list lazy_t but is here used with type
<xavierbot> int lazy_list
<rwmjones> let rec gen n = Cons (n, gen (n+1)) ;;
<xavierbot> val gen : int -> int lazy_list = <fun>
<rwmjones> let's see ...
<rwmjones> let xs = gen 10;;
<xavierbot> Out of memory during evaluation.
<rwmjones> hmmm, obviously that wasn't lazy then
<flux> you'r lazy_list should involve Lazy.t somehow?
<flux> s/'//
<olegfink> let hd = function Cons (t,_) -> t | Empty -> failwith "hd" ;;
<xavierbot> val hd : 'a lazy_list -> 'a = <fun>
<olegfink> (for future use)
<olegfink> for now lazy_list is exactly the same as List.t, how should it differ?
<rwmjones> sorry, diverted onto something else
<olegfink> This expression has type int lazy_list Lazy.t = int lazy_list lazy_t
<olegfink> what is '=' in type definition?
<rwmjones> OK I think my type is wrong
<rwmjones> type 'a lazy_list = Empty | Cons of 'a * 'a lazy_list Lazy.t;;
<xavierbot> type 'a lazy_list = Empty | Cons of 'a * 'a lazy_list Lazy.t
<rwmjones> let rec gen n = Cons (n, lazy (gen (n+1))) ;;
<xavierbot> val gen : int -> int lazy_list = <fun>
<rwmjones> let xs = gen 10 ;;
<xavierbot> val xs : int lazy_list = Cons (10, <lazy>)
<olegfink> yyeah!
<olegfink> hd (gen 1) ;;
<xavierbot> Characters 9-10:
<xavierbot> hd (gen 1) ;;
<xavierbot> ^
<xavierbot> This expression has type int lazy_list but is here used with type
<xavierbot> 'a lazy_list
<olegfink> hm
<rwmjones> let hd = function Empty -> failwith "hd" | Cons (t, _) -> t ;;
<xavierbot> val hd : 'a lazy_list -> 'a = <fun>
<rwmjones> hd xs ;;
<xavierbot> - : int = 10
<olegfink> that's it! cool!
<rwmjones> let tl = function Empty -> failwith "tl" | Cons (_, t) -> force t ;;
<xavierbot> val tl : 'a lazy_list -> 'a lazy_list = <fun>
<rwmjones> tl xs ;;
<xavierbot> - : int lazy_list = Cons (11, <lazy>)
<rwmjones> hd (tl xs) ;;
<xavierbot> - : int = 11
<rwmjones> and so on
<olegfink> aha, so a lazy data structure is a structure which holds data of type Lazy.t
<flux> I think this would work, but is cumbersome: (I'll ruin the types)
<flux> uh
<flux> I was in the backlog :)
<flux> time to read what has happened :)
<olegfink> wait, why tl has force?
<flux> yes, it's better than what I had in mind: (although mine is lazy on the first data too) type 'a lazy_list = Empty | Cons of ('a * 'a lazy_list) Lazy.t let rec gen n = Cons (lazy (n, gen (n + 1))) let rec output l = match l with Empty -> () | Cons x -> let (x, xs) = Lazy.force x in Printf.printf "%d\n%!" x; output xs
<olegfink> ah, understood
<rwmjones> let rec first n xs = if n > 0 then hd xs :: first (n-1) (tl xs) ;;
<xavierbot> Characters 22-64:
<xavierbot> let rec first n xs = if n > 0 then hd xs :: first (n-1) (tl xs) ;;
<xavierbot> ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
<xavierbot> This expression has type unit but is here used with type 'a list
<rwmjones> let rec first n xs = if n > 0 then hd xs :: first (n-1) (tl xs) else [] ;;
<xavierbot> val first : int -> 'a lazy_list -> 'a list = <fun>
<rwmjones> first 20 xs ;;
<xavierbot> - : int list =
<xavierbot> [10; 11; 12; 13; 14; 15; 16; 17; 18; 19; 20; 21; 22; 23; 24; 25; 26; 27; 28;
<xavierbot> 29]
<rwmjones> just like haskell ...
<olegfink> so, now I can begin writing lazy versions of all data structures in ocaml, and then add some fancy syntax with camlp4 ;)
<flux> olegfink, lazy pattern matching exists already
<flux> but Yoric isn't around to tell about it
ttamtta1 has joined #ocaml
ttamtta1 has left #ocaml []
ttamttam has joined #ocaml
<rwmjones> olegfink, why though?
<olegfink> why what?
<rwmjones> why create lazy data structures? they're not really very useful
<olegfink> I use ocaml merely for fun since I've finished a course on it. So was just wondering how to use lazy evaluation.
<rwmjones> lazy data structures also make it hard to reason about the performance of the structure ... there's a lot about that in okasaki's book
<olegfink> I'm still to read it, though.
<tsuyoshi> er whoops.. wrong channel
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has joined #ocaml
kbidd has quit [Read error: 110 (Connection timed out)]
<olegfink> mneh, I'm stuck again, now at lazy fib. Seems I need a lazy int?
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
Snark has quit ["Ex-Chat"]
jderque has quit [Read error: 113 (No route to host)]
Mr_Awesome has joined #ocaml
StoneNote has quit []
<petchema> olegfink: what is lazy is computations, not types
<petchema> (computations == expressions)
<olegfink> okay, well, I need a lazy '+'
<olegfink> first I tried let (++) a b = lazy (a+b), but that's not what I want, it's int -> int -> int lazy_t and I want int lazy_t -> int lazy_t -> int lazy_t
dramsay has joined #ocaml
ita has joined #ocaml
<olegfink> but with this lazy_list I will never know what's the last natural number. Or I just can't write a proper rev.
<olegfink> well, it's quite obvious since the first argument to Cons is not lazy
<mfp> let (!!) = Lazy.force;;
<xavierbot> val ( !! ) : 'a Lazy.t -> 'a = <fun>
<mfp> let (++) a b = lazy(!!a + !!b);;
<xavierbot> val ( ++ ) : int Lazy.t -> int Lazy.t -> int lazy_t = <fun>
<olegfink> but that force, uhm, beats the whole point, I'm afraid.
<mfp> it's lazy(force ... ), so it won't evaluated right away
<olegfink> ah
<olegfink> cool, I have a lazy fib now. Rather useless, however.
<olegfink> well, not really, as lazy should use results from earlier computations
asmanur has joined #ocaml
RobertFischer has joined #ocaml
ttamttam has left #ocaml []
pango has quit [Remote closed the connection]
pango has joined #ocaml
seafood has joined #ocaml
* qwr isn't sure about that memoizing
<petchema> yup lazy doesn't provide automatic memoizing
<rwmjones> erm, lazy does do memoizing
<petchema> it does caching, not memoizing
<rwmjones> what's the difference?
<mfp> olegfink: you have to reuse the thunks, if you create new lazy (...) each time, nothing is gained
<petchema> there's no unique identity for a given "computation" in general
<rwmjones> oh I see ... it doesn't memoize the function + argument
<petchema> (I'm not sure I'm very clear)
<petchema> in Lazy.force (lazy(1+1)) + Lazy.force (lazy(1+1)) 1+1 is computed twice, while in let a = lazy(1+1) in Lazy.force a + Lazy.force a it's computed once
_andre has joined #ocaml
<_andre> hello
<_andre> anyone familiar with nethttpd?
<ecc> _andre: I wrote a server that uses it
<olegfink> let rec fib = function 1->lazy 1 | 2->lazy 1 | n -> lazy ((Lazy.force (fib (n-1))) + (Lazy.force (fib (n-2)))) ;;
<xavierbot> val fib : int -> int Lazy.t = <fun>
<olegfink> this thing doesn't seem to cache anything
<_andre> ecc: i'm use code like "raise Standard_response(`Not_found, None, None)" to generate the server response in case of errors. do you know if it's possible to add some info to the reponse (something like "page foo.html not found")?
<_andre> the other tuple members are header and log message, so i guess it would have to be done some other way
marmottine has joined #ocaml
<jonafan> every time you create a lazy value, it must be evaluated. it doesn't look up separate calls of fib magically
<ecc> _andre: check out the http_processor_config object. you can provide your own error_response method to generate the content of the error page
<jonafan> ocaml isn't a purely functional language anyway
<olegfink> yeah, but that's why I like it.
<olegfink> Anyway, so unless I store my fibs somewhere I'll have no fun?
<jonafan> maybe if you made a map and put the lazy values in there
<jonafan> yeah
<petchema> olegfink: because there difference instances of computing 'fib n' for a given n don't share the same identity
<olegfink> that's strange, however, if there was a way to say 'see, fib is a pure function, it's okay to cache anything in it'
<olegfink> hm, okay, then I'll rather write map2 for lazy_list and do a list of fibs recursively.
<jonafan> yeah........
<jonafan> maybe some wizard can make some camlp4 magic that does that pure function thing
<petchema> olegfink: you could write a wrapper function to do memoizing
<mfp> let rec fib = memo 1 -> 1 | 2 -> 1 | n -> fib (n-1) (n-2)
<mfp> or even 0 -> 1 | 1 -> 1
<jonafan> awesome
g36130 has joined #ocaml
<olegfink> excellent, so from this time on I can use memo instead of function in case I do pure things?
<g36130> Hi! Am I right that unlike Haskell, a string and a char list are totally different in ocaml?
<rwmjones> yup
<mfp> olegfink: if you can use pa_memo AND unbounded memoization is OK, yes
<rwmjones> a string is somewhat like a byte array
<jonafan> and they're mutable
<g36130> At the moment, I use: let print_cl mylist = List.map print_char mylist
<g36130> Is it ok?
<rwmjones> for an list of char it is
<rwmjones> Extlib has functions called String.explode & String.implode
<rwmjones> which convert between strings & char lists
<g36130> Because I don't know if List.map expects something of type char -> unit ?
<g36130> I've got a warning
<rwmjones> you probably want List.iter, but most likely you should just use print_string
<g36130> I want to print a char list. How would you do?
<rwmjones> let mylist = ['a'; 'b'; 'c'; 'd'] ;;
<xavierbot> val mylist : char list = ['a'; 'b'; 'c'; 'd']
<rwmjones> List.iter print_char mylist;;
<xavierbot> abcd- : unit = ()
<g36130> Thanks
<mfp> ooh xavierbot > lambdabot, it can do IO :)
<_andre> ecc: do you have an example at hand? i'm not sure how to access that object, as i'm using Nethttpd_plex for the server
<_andre> in fact i'm still quite lost inside the ocamlnet class hierarchy...
<g36130> Is there an equivallent of String.make for List?
<mfp> let mklist n x = Array.to_list (Array.make n x);;
<xavierbot> val mklist : int -> 'a -> 'a list = <fun>
<ecc> _andre: yes, class hierarchy is complex -- I always have a browser with several tabs of ocamldoc for the different modules while I'm coding
<mfp> let rec mklist n x = let rec aux n l = if n > 0 then aux (n-1) (x::l) else l in aux n [];;
<xavierbot> val mklist : int -> 'a -> 'a list = <fun>
<ecc> _andre: here's a snippet: http://pastebin.com/m48c8bc4b
filp has quit ["Bye"]
<_andre> thanks!
<g36130> I don't really get the difference between List and Array (except that you can have 2D arrays)?
<_andre> ecc: thanks, i'll try it out :)
Morphous_ has joined #ocaml
<mfp> g36130: access to an element, or getting the length of a list is O(n); in an array, both are O(1). Arrays are mutable, lists aren't. You can prepend an element to a list in constant time.
<mfp> the maximum array length is
<mfp> Sys.max_array_length;;
<xavierbot> Characters 1-21:
<xavierbot> Sys.max_array_length;;
<xavierbot> ^^^^^^^^^^^^^^^^^^^^
<xavierbot> Unbound value Sys.max_array_length
<mfp> ouch
<mfp> - : int = 4194303
<mfp> (Sys seemingly disabled in xavierbot)
<rwmjones> g36130, lists are like linked lists in C, and arrays are like arrays in C
<olegfink> hm, by the way, how do I ask ocaml[c] to print cc-style errors, like file.ml:666: what I don't like about this line
<jonafan> yay, i compiled this crazy pa_memo thing
<jonafan> i don't understand how
<jonafan> but it works well
<rwmjones> olegfink, you can't, at least not easily. In any case ocamlc errors are line + byte, not just line
<olegfink> yeah, but that doesn't work very well with my environment
<olegfink> sed'ing ocaml output yields strange side effects
<mfp> jonafan: you can run camlp4o pa_memo.cmo pr_o.cmo yourcode.ml | less to see what "memo" is expanded to if you don't grasp the code of the extension
<jonafan> wow
<ecc> olegfink: emacs + tuareg supports easy jumping to the location of each error
ygrek has joined #ocaml
<olegfink> but that's emacs
Morphous has quit [Connection timed out]
<olegfink> well, figured out which format for errors I want
<olegfink> file.ml:linestart+#charstart,lineend+#charend
<olegfink> if only sed worked well
postalchris has joined #ocaml
<hcarty> olegfink: What editor/environment are you using?
<olegfink> acme
<olegfink> now on linux, but going to play with ocaml on plan9
<olegfink> okay, seems awk does what I want
<olegfink> ocamlc lazy.ml |[0=2] awk '/File .*line .* characters/{getline;print}'
RobertFischer has left #ocaml []
mwc has joined #ocaml
bongy has joined #ocaml
bongy has quit [Client Quit]
mwc has quit ["Leaving"]
mwc has joined #ocaml
psnively has joined #ocaml
bluestorm has joined #ocaml
_andre has quit ["leaving"]
pango has quit [Remote closed the connection]
psnively_ has joined #ocaml
bzzbzz_ has quit ["Lost terminal"]
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
<hcarty> Hello Yoric[DT]
<Yoric[DT]> How do you do ?
<hcarty> I am well thank you! And you?
<hcarty> I am enjoy the pieces of your comprehension library I have used so far
<hcarty> Thanks for putting it out
psnively_ has quit []
<Yoric[DT]> My pleasure.
bzzbzz has joined #ocaml
pango has joined #ocaml
psnively has quit [Connection timed out]
ttamttam has joined #ocaml
psnively has joined #ocaml
Morphous_ has quit ["shutdown"]
Amorphous has joined #ocaml
asmanur has quit [Remote closed the connection]
ttamttam has left #ocaml []
thermoplyae has joined #ocaml
postalchris has quit [Read error: 110 (Connection timed out)]
postalchris has joined #ocaml
kbidd has joined #ocaml
jlouis_ has joined #ocaml
middayc has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
AxleLonghorn has joined #ocaml
rwmjones has quit ["Closed connection"]
psnively has quit []
jlouis has joined #ocaml
thermoplyae has quit ["daddy's in space"]
jlouis_ has quit [Read error: 110 (Connection timed out)]
ygrek has quit [Remote closed the connection]
l_a_m has quit [Remote closed the connection]
Morphous has joined #ocaml
middayc has quit []
thermoplyae has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
jlouis_ has joined #ocaml
StoneNote_ has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
jlouis has quit [Read error: 110 (Connection timed out)]
AxleLonghorn has left #ocaml []
dramsay has quit [Read error: 110 (Connection timed out)]
pattern has quit [Remote closed the connection]
rwmjones has joined #ocaml
pattern has joined #ocaml
hkBst has quit ["Konversation terminated!"]
pattern has quit [Remote closed the connection]
marmottine has quit [Remote closed the connection]
rwmjones has quit ["Closed connection"]
ita has quit [Read error: 110 (Connection timed out)]
<Yoric[DT]> Good night everyone,
Yoric[DT] has quit ["Ex-Chat"]
Tetsuo has quit ["Leaving"]
Jedai has quit ["KVIrc 3.2.6 Anomalies http://www.kvirc.net/"]