foxster has quit [Read error: 104 (Connection reset by peer)]
foxster has joined #ocaml
jdrake has quit [Remote closed the connection]
lus|wazze has quit ["Quidquid latine dictum sit, altum sonatur."]
jdrake has joined #ocaml
asqui has quit [Read error: 54 (Connection reset by peer)]
asquii has joined #ocaml
asquii is now known as asqui
visnu has joined #ocaml
<Riastradh>
Hi.
<visnu>
hello
visnu has left #ocaml []
<Smerdyakov>
Now you did it, Riastradh.
<Riastradh>
No, it was your silent presence, Smerdyakov.
<Riastradh>
Don't frame others for your faults.
foxster has quit [Read error: 104 (Connection reset by peer)]
lament has joined #ocaml
Smerdyakov has quit ["sleep"]
foxster has joined #ocaml
jdrake has left #ocaml []
mattam has joined #ocaml
det has joined #ocaml
<det>
If you create a list of `#drawable' (which supports only 1 method: draw) how is the method dispatched on when you call draw on a item in the list ?
foxster has quit [Connection reset by peer]
<det>
WOuld it maybe be better to have a list of closures ?
foxster has joined #ocaml
d-bug has joined #ocaml
d-bug has left #ocaml []
det has quit ["ircII EPIC4-1.1.2 -- Are we there yet?"]
<mrvn>
det: type drawable = { draw : unit -> unit };; drawable.draw ()
<mrvn>
basically.
<mrvn>
using classes just hides making those closures yourself.
<mrvn>
What would be better would be using a module.
<mrvn>
unless you have inheritance.
<mrvn>
damn, don#t tell me. det just left the minute before I startedtyping.
gene9 has joined #ocaml
<mrvn>
Anyone left alive?
* emu
keels over
lament has quit ["I AM NOT THE NEW DALAI LAMA"]
<mrvn>
I'm working on some asynchronous IO functions. I'm trying to do write a function that will returns a value into which something will be read later when the input becomes available.
<mrvn>
Something similar to the Lazy module.
<mrvn>
I'm not sure what would be the best way to go about it though.
<mrvn>
The user interface should look somewhat like this: let i = read_int input in let j = read_int input in let foo = { i = i; j = j; } in wait_for_input input (fun () -> store_foo foo)
<mrvn>
read_int would just prepare to read an int but wouldn't block and wait_for_input would call the 2nd argument (a closure) when all the input has arived.
<mrvn>
Noone any idea?
docelic has joined #ocaml
gene9 has quit [Read error: 104 (Connection reset by peer)]
<mrvn>
docelic: awake?
<docelic>
sure
<mrvn>
I'm working on some asynchronous IO functions. I'm trying to do write a function that will returns a value into which something will be read later when the input becomes available. Something similar to the Lazy module.
<mrvn>
I'm not sure what would be the best way to go about it though. The user interface should look somewhat like this: let i = read_int input in let j = read_int input in let foo = { i = i; j = j; } in wait_for_input input (fun () -> store_foo foo)
<mrvn>
read_int would just prepare to read an int but wouldn't block and wait_for_input would call the 2nd argument (a closure) when all the input has arived.
<docelic>
I know 0 ocaml.. Im here because I plan to learn it one day ;-)
<mrvn>
too bad.
lam has left #ocaml []
lam has joined #ocaml
systems has joined #ocaml
__DL__ has quit [Read error: 54 (Connection reset by peer)]
systems has quit [Read error: 110 (Connection timed out)]
det has joined #ocaml
<mrvn>
09:29 < mrvn> det: type drawable = { draw : unit -> unit };; drawable.draw ()
<mrvn>
09:29 < mrvn> basically.
<mrvn>
09:30 < mrvn> using classes just hides making those closures yourself.
<mrvn>
09:30 < mrvn> What would be better would be using a module.
<mrvn>
09:31 < mrvn> unless you have inheritance.
__DL__ has joined #ocaml
gl has quit [asimov.freenode.net irc.freenode.net]
gl has joined #ocaml
d-bug has joined #ocaml
<det>
ahh
<det>
thanks!
<det>
I found a mailing list message that outlined the dispatch of methods in ocaml
<det>
it seems that it doesnt make any closures at all
<det>
but instead dispatched like ObjC
<mrvn>
Which is?
det has quit ["ircII EPIC4-1.1.2 -- Are we there yet?"]
<det>
after reading this I came to the conclusion that I will hjust have a structure like you did called drawable with closures for all the functions that a drawable must implement
<det>
it also must check things like the right number of arguments at run-time apparently :/
<mrvn>
Do you have inhertitance?
<det>
as in they all inherit from an abstract class (all support the same interface), yes
<det>
I need to have a hetergeneous list
<det>
so the closure thing or objects appear to be the only solution
<mrvn>
but no drawable2 that inherits drawable but also some more functions?
<det>
correct?
<det>
no
<mrvn>
You can make a list of objects or a list of closures.
<det>
yeah :)
<mrvn>
I don#t think you can make a heterogene list with modules otherwise.
<det>
you cant :/
<mrvn>
You might be able to make a functor though.
d-bug has left #ocaml []
<det>
but then the list would still be homo
<mrvn>
But you would end up with a list of closures.
<det>
oh, really
<det>
sounds interesting
<det>
it would be nice if you could do something like
<det>
module type Sequence =
<det>
sig
<det>
type 'a sequence
<det>
exception EmptyList
<det>
val empty: 'a sequence
<det>
val prepend: 'a sequence -> 'a -> 'a sequence
<det>
val car: 'a sequence -> 'a
<det>
val cdr: 'a sequence -> 'a sequence
<det>
end
<det>
;;
<det>
and then have a list of `Sequences'
<mrvn>
Thats what List is.
<det>
well
<det>
I mean be able to use Sequence in type declarations
<det>
so it could be a List, or anything else that supported that interface
<mrvn>
Thats what functors do.
<det>
so, I can make a function that will create my closures for me
<mrvn>
No, the functor takes the interface as argument.
<det>
functor I mean
<det>
but I still cant have a hetergenous list ?
<mrvn>
No. but it would be homogene if all the signatures are equal.
<det>
I'm sorry, could you give a simple example as possible ?
<mrvn>
type drawable = { draw : unit -> unit; };;
<mrvn>
let button = { draw = fun () -> print_string "draw button\n"; };;
<mrvn>
let icon = { draw = fun () -> print_string "draw icon\n"; };;
<mrvn>
let l = [button; icon];;
<mrvn>
List.iter (fun x -> x.draw ()) l;;
<mrvn>
draw button
<mrvn>
draw icon
<mrvn>
- : unit = ()
<det>
oh, I thought you were saying I could do it with fucntors :)
<mrvn>
If a drawable itself has some data and some functions itself then a functor is better.
<det>
that's what I dont understand, how to do it with functors
<det>
Is using a functor a different approach than closures, or is it just helpful way to produce them ?
<det>
I hope I didnt scare you away
<mrvn>
This example gets long
<det>
ok :)
<det>
thanks very very much :)
<det>
I will wait patiently like a good boy now
<mrvn>
type base_drawable = { draw : unit -> unit; };;
<mrvn>
let button = { draw = fun () -> print_string "draw button\n"; };;
<mrvn>
let icon = { draw = fun () -> print_string "draw icon\n"; };;
<mrvn>
let l = [button; icon];;
<mrvn>
List.iter (fun x -> x.draw ()) l;;
<mrvn>
module type DRAWABLE_TYPE = sig val draw: unit -> unit end;;
<mrvn>
type drawable = { draw : unit -> unit; barf : unit -> unit; };;
<det>
I assume this example starts with "module type .." ?
<mrvn>
yes
<det>
aww
<det>
I understand now
<det>
now objects are completely useless to me
<det>
you are awsome mrvn
<mrvn>
class virtual base_drawable = object
<mrvn>
method virtual draw : unit
<mrvn>
end;;
<mrvn>
class button = object
<mrvn>
inherit base_drawable
<mrvn>
method draw = print_string "Draw button\n"
<mrvn>
end;;
<docelic>
ofcourse, he's on #debian-devel ;)
<mrvn>
class icon = object
<mrvn>
inherit base_drawable
<mrvn>
method draw = print_string "Draw icon\n"
<mrvn>
end;;
<mrvn>
let l = [((new button) :> base_drawable); ((new icon) :> base_drawable)];;
<mrvn>
List.iter (fun x -> x#draw) l;;
<mrvn>
I somewhat find that much easier.
<det>
I agree
<det>
but
<det>
that URL I posted
<det>
I cant that dispatch nastiness distubs me greatly
<det>
s/I cant//
<det>
the class example should just create the closures for you, or use a simple VFT
<mrvn>
The dispatching just looks up the function in a virtual table.
<det>
yeah, but, doesnt take advantage of the fact that you know exactly what functions all objects int he list supports
<det>
the table shouldnt be sparse
<det>
and it shouldnt have to do run-time type-checking
<mrvn>
I don't understand that part myself.
<mrvn>
The number of arguments is static at compile time. Nothing further to check there.
docelic has left #ocaml []
<det>
maybe Ill look at the assembly for the example you just gave with objects
<mrvn>
And the sparseness of the table is caused by multiple inheritance and the like.
<mrvn>
With functors you have the problem that you have to bind "that" to each function or pass it as argument all the time.
<det>
the sparseness of the table is because it is a hash table
<mrvn>
Anything that uses "object(self)" is probably better as object.
<mrvn>
Its a lot less code than rebuilding the inheritance with functors manually.
<mrvn>
Can one write a function that takes two functions f and g and creates a new function that applies as many arguments as f takes to f and the result of that to g?
<det>
that doesnt seem type-safe
<mrvn>
foo : ('a->'b) -> ('b->'c) -> 'a -> 'c
<det>
oh, right
<mrvn>
The type should be fine but how do I write code for that?
<mrvn>
let f x y = x + y;;
<mrvn>
let g x = print_int x;;
<mrvn>
let combine f g = fun ... -> g (f ...);;
<mrvn>
But the ... depends on f
<det>
can teh function also take the number of arguments that f taks ?
<mrvn>
If that helps.
<cDlm>
i think you have to define combine1 ...combineN for f with N args
<mrvn>
cDlm: Thats what I fear.
<det>
yeah
<mrvn>
Maybe with polymorphic variants.
<cDlm>
i tried to write a generic currify function once
<det>
is there no way to syntactily combine the two steps of createing the button module and then passing it to Drawable to get Drawable_Button, kind of like "This inherits Drawable" ?
<mrvn>
det: You can make a button module that internally makes the Drawable_Button and other stuff.
<mrvn>
Then you just call Button.make ()
<det>
aww
<det>
nice
<mrvn>
I still say its much easier with objects
<det>
Button.drawable.make() ?
<det>
could thacould that be done ?
<det>
I hate IRC over modem :(
<mrvn>
Only if you create a Button.drawable first.
<mrvn>
Button.Drawable.make should be possible though.
<mrvn>
i think
<det>
that way I could have all the different interfaces it supports right there
Smerdyakov has joined #ocaml
<det>
I will experiment
<det>
I kind of like that fact that virtual functions are distinctly different than regular ones
<mrvn>
all functions in a class are virtual
<mrvn>
r rather all methods are virtual
<mrvn>
+o
olrion has joined #ocaml
<olrion>
yip yip :)
<mrvn>
let f1 = function `A x -> x = 1 | `B -> true | `C -> false
<mrvn>
let f2 = function `A x -> x = "a" | `B -> true
<mrvn>
let f x = f1 x && f2 x;;
<mrvn>
val f1 : [< `A of int | `B | `C] -> bool = <fun>
<mrvn>
val f2 : [< `A of string | `B] -> bool = <fun>
<mrvn>
val f : [< `A of string & int | `B] -> bool = <fun>
<mrvn>
Can I do something similar to get
<mrvn>
val f : [< `A of string || int | `B] -> bool = <fun>
Smerdyakov has quit ["brb"]
Smerdyakov has joined #ocaml
olrion has quit ["I like core dumps"]
<det>
If I need to partially apply "draw" then the type has to be "val draw: blah -> unit -> unit" ?
<Smerdyakov>
What do you mean exactly?
<Smerdyakov>
Why would you "need" to partially apply a function?
<det>
I need a closure I can put in a list
<det>
that takes no arguments
<Smerdyakov>
You could always make a new anonymous function for that purpose.
<det>
true
<emu>
why would any function be anonymous but to mask its true identity
<det>
which would be faster ?
<emu>
perhaps it is going to commit some crime
<det>
I imagine partial application is faster
<Smerdyakov>
det, there's probably no significant difference, but I think it's nicer to give draw its obvious type.
<det>
good point
<Smerdyakov>
And remember that partial application requires allocating a new closure, too.
<Smerdyakov>
So there should be next to no difference.
<det>
I mean, not the cost of creating
<det>
the cost of calling
<Smerdyakov>
Why would it be different?
<Smerdyakov>
(in an obvious, large way)
<det>
you're right
<det>
it wouldnt be
<det>
When i make my own language, all function types will end in something like -> unit, just like how all lists and with Nil
<det>
s/and/end/
<Smerdyakov>
Why?
<det>
to represent nothing
<det>
without attempting to represent nothing as "unit"
<det>
or otehr such hacks
<mrvn>
unit is no hack.
<mrvn>
unit is a simple enumeration type with only 1 Constructor.
<emu>
where's void
<det>
well, think of the List type
<emu>
0 constructors
<mrvn>
List has 2 Contructors.
<mrvn>
type 'a list = Nil | Cons of 'a * 'a
<det>
void cant exist without a function that takes 0 arguments
<mrvn>
emu: every function returns a value. There is no void in ocaml.
<det>
mrvn, yes, Nil is a constructor that takes 0 arguments
<emu>
let foo () = raise FooException;;
<mrvn>
Also every function must take an argument, otherwise there is no point not evaulating it when its declared.
Brothert has joined #ocaml
<det>
there is a point
<mrvn>
Without "let foo ()" you couldn't see whats a value and what is a function.
d-bug has joined #ocaml
<det>
I am very tired and hungry however
<emu>
plenty of languages offer functions without arguments
<det>
I I will elaborate on my crazy language ideas tomorrow
<det>
I am sure I can convince you!
<mrvn>
emu: not syntactically.
<emu>
void foo () { }
<emu>
(defun foo () (values))
<det>
will you be here ?
<det>
mrvn
<mrvn>
det: most of the time
<mrvn>
emu: void foo() {} is a function that take any number of arguments :)
<emu>
void foo (void) { }
<mrvn>
void foo(void) {} would be 0 arguments.
<det>
void shouldnt be a type at all, rather there needs to be two types of functions, a ConsFun and a NilFUn
<emu>
silly me, forgot my C
<emu>
Lisp has the type NIL
<emu>
of which, nothing is of it
<mrvn>
In C you have a void argument to say it has no arguments, just like in ocaml.
<emu>
in Ocaml, every function takes an argument
<det>
yes, that is wrong!
<mrvn>
Only difference is that in ocaml the () argument is passed along I think.
<emu>
you simulate no argument by using unit
<emu>
() is the only value of unit type
<det>
emu, you simulate no arguments in C by using void
<mrvn>
methods have no arguments.
<mrvn>
But thats probably done via unit internally.
<mrvn>
The difference between ocaml and C is that C doesn't create a void object/variable. Saves one register.
<emu>
i'm sure ocaml is smart enough there
* det
fades into the background, continuations, ConsFun and NilFun, yuou will understand tomorrow, muahahaha
<mrvn>
Could be that its optimized out in ocaml.
<det>
mrvn, I am sure it is
<det>
:)
<mrvn>
det: write me a callCC
<det>
all functions should be continuations, screw callCC, long live Cintinuation Passing Style
<mrvn>
Is there a mechanism to lazify a function?
<emu>
the result type of ERROR (which raises an error condition) is NIL
<det>
I am away sleeping and eating now
<emu>
no result
<mrvn>
det: Thats too much to type.
<det>
mrvn, that's where macros comee in!
<det>
really
<det>
must sleep
<det>
eat first
<det>
then sleep
<det>
yes
<det>
cant eat in my sleep ..
<det>
yet
<mrvn>
emu: raise : exn -> 'a = <fun>
* det
is away: sleeping and eating
<mrvn>
emu: _every_ function returns a value.
<mrvn>
# exit;;
<mrvn>
- : int -> 'a = <fun>
<mrvn>
Even if it doesn't return :)
<emu>
so you se
<emu>
it doesn't make sense
<emu>
haha
<emu>
what is 'a?
<Smerdyakov>
"Every function has a unique most general return type" is a better way of saying it.
<emu>
why can't the type system understand that there is no return?
<mrvn>
If it werent for the input_value anything that is "-> 'a" where 'a doesn't apear on the left side would be a no return.
<mrvn>
emu: I wondered exactly that a few days ago.
<Smerdyakov>
Actually, for any function call, there is exactly one type the value of the application can have, if any.
<Smerdyakov>
There, that's the definitive statement. :-)
<mrvn>
emu: How would you type a function that never returns a value but raises an exception sometimes?
<emu>
what does it do otherwise?
<emu>
loop?
<mrvn>
emu: For a no return function one would like to clean up all local bindings. But if it throws an exception those bindings are maybe still reachable.
<mrvn>
emu: loop or exit or whatever
<emu>
how so? exception handlers are executed once the frame is exited in ocaml, no?
<emu>
or does it do it in the current frame?
<Smerdyakov>
Huh?
<mrvn>
let rec loop = function
<mrvn>
0 -> exit 0
<mrvn>
| x -> try loop (x-1) with _ -> ();;
<mrvn>
Is that tail recursive?
<emu>
someone clever might notice that the union of some type 'a and the empty type is 'a =)
<Smerdyakov>
There are no expressions with type 'a in ML, I think. :P
<emu>
raise
<Smerdyakov>
Oops
<Smerdyakov>
Hehe
<d-bug>
mrvn: nope, the try makes it not tail-recursive
<Smerdyakov>
Yes and no...
<mrvn>
But it could be cause its a no-return no-raise function.
<Smerdyakov>
You assign it 'a to start out, maybe, but type inference always restricts it.
<Smerdyakov>
So I think, in actual code, you won't find an expression that you can say has type 'a, or "any type."
<mrvn>
Smerdyakov: any no-return function will be 'a
<Smerdyakov>
I guess that's the one way it could be.
<Smerdyakov>
But... eh...
<Smerdyakov>
It depends how you look at it.
<mrvn>
Smerdyakov: and read_value, marshaling and Obj.magic stuff.
<Smerdyakov>
'a is really bound to a specific monotype inside the body of a non-terminating function.
<Smerdyakov>
It just doesn't matter what that monotype is.
<Smerdyakov>
So, looking at things this way and excluding funky libraries that play tricks using code written in other languages, I think what I've said holds.
<mrvn>
I would like exceptions to be part of the type. But that would probably let the type explode and be unreadable.
<mrvn>
If I have a type foo = { mutable x : int; mutable y : int; } can I pass the x to a function so that changes to it will refelct in the foo record?
<mrvn>
type foo = { x : int ref; mutable y : int; };;
<mrvn>
let foo = { x = ref 0; y = 0; };;
<mrvn>
incr foo.x;;
<mrvn>
foo.x;;
<mrvn>
Like that but I prefer mutable instead of ref.
<mrvn>
ref uses an indirection and mutable not, right?
d-bug has left #ocaml []
wax has quit [Remote closed the connection]
wax has joined #ocaml
<mrvn>
Can I declare a polymorphic variant to be [> ] but not `X?
lus|wazze has joined #ocaml
<mrvn>
let read `Int = ()
<mrvn>
let read = function
<mrvn>
`Float -> ()
<mrvn>
| x -> read x;;
<mrvn>
| x -> read x;;
<mrvn>
This expression has type [> `Float] but is here used with type [ `Int]
<mrvn>
(The last x is underlined)
<mrvn>
Can I fix that somehow or do I need to "| `Int -> read `Int"?
Smerdyakov has quit ["away"]
<lus|wazze>
hm i seem to remember having the same problem once
<lus|wazze>
those polymorphic variant types sometimes behave kinda .. strange imho
<mrvn>
read should be [ `Float; `Int ] and the x should be [> `Int ] because the `Float is already matched.
<lus|wazze>
actually the x i think should bne [`Float ; `Int ] , i.e. the same type as it is matched againstz
<lus|wazze>
oh, now I see the problem
<lus|wazze>
its not a recursive definition
<lus|wazze>
well of course that doesnt work
<lus|wazze>
because x is of type [ `Float; `Int ]
<mrvn>
But `Float is already handled.
<lus|wazze>
the type checking on variant types doesnt work this way
<mrvn>
Shouldn#t it see that its save to call the first read?
<lus|wazze>
well i dont know if one COULD possibly write a type-checker that powerful (i.e. if it would be computable), but in any case, ocaml's is not
<mrvn>
There should be a way to specify a polimorfic variant with exclusions.
<mrvn>
exception Unbound
<mrvn>
let read = function
<mrvn>
`Int -> ()
<mrvn>
| _ -> raise Unbound
<mrvn>
let read = function
<mrvn>
`Float -> ()
<mrvn>
| x -> read x;;
<mrvn>
val read : [> `Float | `Int] -> unit = <fun>
<mrvn>
Can I limit that to [`Float | `Int] again without typing the full list?
<lus|wazze>
whyd you want to? [> Float | `Int ] is a superset of [ `Float | `Int ]
<mrvn>
To prevent some maniac to call "read `Bkfjhgkjhd"
<lus|wazze>
:>
<mrvn>
let (read : [`Float | `Int]) = read;;
<lus|wazze>
well you could define a name for the type
<mrvn>
This expression has type [> `Float | `Int] -> unit but is here used with type
<mrvn>
[ `Float | `Int]
<lus|wazze>
you need to specify the complete type of read, n ot just the type of its return value
<mrvn>
let (read : [`Float | `Int]->unit) = read;;
<mrvn>
But I want to have a read for a rather large bunch of types and I would hate to type the full list there. Ugly if you extend it and forget one type.
<lus|wazze>
<--- afk
<lus|wazze>
simply define a name for your type ie
<lus|wazze>
type foobar = [ `Float | `Int ]
<lus|wazze>
<--- now REALLY afk
<mrvn>
cu
Smerdyakov has joined #ocaml
det has quit [Remote closed the connection]
<mrvn>
Smerdyakov: If I have a type foo = { mutable x : int; mutable y : int; } can I pass the x to a function so that changes to it will refelct in the foo record?
foxster has quit [Connection timed out]
<Smerdyakov>
I don't know.
<lus|wazze>
no
<lus|wazze>
simply pass the whole record
<lus|wazze>
or do a foo.x <- some_function foo.x
<Smerdyakov>
You can always pass it as functions to set and get it, also.
foxster has joined #ocaml
olrion has joined #ocaml
<olrion>
re
mattam_ has joined #ocaml
mattam has quit [Read error: 110 (Connection timed out)]
cDlm_ has joined #ocaml
cDlm has quit [Read error: 104 (Connection reset by peer)]
mrvn_ has joined #ocaml
olrion has quit [Read error: 113 (No route to host)]
mrvn has quit [Read error: 60 (Operation timed out)]
cDlm_ is now known as cDlm
olrion has joined #ocaml
olrion has quit [Read error: 104 (Connection reset by peer)]
olrion has joined #ocaml
<olrion>
re
<Riastradh>
Hi.
<olrion>
there is something i don't understant i execut the ocaml prompt and :
<olrion>
let succ x = x + 1 ;;
<olrion>
^^
<olrion>
Parse error: 'and' or 'in' expected (in [expr])
<olrion>
for exemple
<olrion>
he tell that there is an error in ;; ??
* Riastradh
doesn't understand that either.
<olrion>
and he didn't do that before
<vegai>
you typed some invisible characters there, perhaps?
<olrion>
i don't think so but :
<lus|wazze>
you probably didnt properly terminate the preceding statement?
<olrion>
Objective Caml version 3.06
<olrion>
Camlp4 Parsing version 3.06
<Riastradh>
Heheh, olrion, I think you mean 'and it didn't do that before' -- in English, we don't put genders on things that don't actually have genders.
<vegai>
I've seen backspace do weird stuff on the interpreter sometimes
<olrion>
this what i have when i start ocaml
<olrion>
Riastradh: possible: english is not my native language
<Riastradh>
olrion, as I guessed.
<olrion>
vegai it is the copy/past
<olrion>
you write :)
<vegai>
d'accord...
<olrion>
no
<olrion>
you are right
<olrion>
voila c mieux
<olrion>
:)
<vegai>
ah, native frenchman -- nobody writes french worse ;-D
<olrion>
hehe
<olrion>
i think that ocaml is very close to mathematic language
<olrion>
than C for exemple
<Riastradh>
If you like that, try Haskell.
<olrion>
ha i didn't try this one
<olrion>
i found ocaml not very (in the way that i try to do everything in fonctionnal)
<olrion>
easy
<olrion>
but very intresting
<olrion>
how to start ocaml without Camlp4
<olrion>
?
* Riastradh
just runs 'ocaml' from the shell.
<olrion>
this should be easy but doesn't work
lus|wazze has quit ["Quidquid latine dictum sit, altum sonatur."]
lus|wazze has joined #ocaml
whee has joined #ocaml
Smerdyakov has quit []
systems has joined #ocaml
whee has quit ["Leaving"]
Smerdyakov has joined #ocaml
systems has quit [Read error: 110 (Connection timed out)]
TachYon has joined #ocaml
TachYon has quit [Remote closed the connection]
Kinners has joined #ocaml
Smerdyakov has quit ["eat"]
cDlm_ has joined #ocaml
cDlm has quit [Killed (NickServ (Ghost: cDlm_!cdlm@lns-th2-11-82-64-173-168.adsl.proxad.net))]
cDlm_ is now known as cDlm
olrion has quit [Remote closed the connection]
mattam_ is now known as mattam
Smerdyakov has joined #ocaml
mattam has quit [Read error: 113 (No route to host)]
Kinners has quit [Read error: 54 (Connection reset by peer)]