<det>
when compiled like ocamlc showable.ml circle.ml
karryall has joined #ocaml
<mrvn>
Because nowehre in Module Circle is there any show defined.
<det>
but it knows b is a Showable.showable
<det>
if I uncomment the last line
<mrvn>
hmm, what are you doing there anyway.....
<mrvn>
let c = b.Showable.show ();;
<det>
virtual functions via closures :)
<det>
oh
<mrvn>
You know that you don#t have to type ;; all the time, right.
<det>
no, I didnt
<det>
I get syntax errors on the next line when i dont :)
<karryall>
no, you _never_ need ;; with compiled ocaml programs
<det>
hrmm
<det>
b.Showable.show ();;
<det>
works
<det>
but I don't understand it one bit
<Smerdyakov>
Are you using free-floating expressions instead of grouping everything nicely into modules?
<mrvn>
Only the module Showable has a show defined.
<det>
oh
<mrvn>
And the unnamed struct in circle.ml but thats unnamed and thus not reachable.
<det>
yeah, I wanted it anonymous
<det>
Smerdyakov: I am just learning ocaml:)
<mrvn>
I sometimes hate it that one has to allways specify the full module patch to each value but the type system needs it most of the time.
<det>
Smerdyakov: trying to get away with using closures for virtual functions instead of objects :)
<mrvn>
s/patch/path/
<Smerdyakov>
det, not objects! Modules!
<det>
s/needs/doesn't need/ ?
<Smerdyakov>
Don't use OO, ever. :-)
<det>
Smerdyakov: to me OO = virtual functions, all the other stuff is garbage :)
<mrvn>
det: Where do you get an error? compiles fine here without ;;
<det>
mrvn. which line can I omit the ;;
<mrvn>
Smerdyakov: inheritance is much easier to type with objects. Why shouldn't one use them?
<mrvn>
det: all of them
<karryall>
det: all of them !
Smerdyakov has quit ["brb"]
<det>
nadda
<det>
$ ocamlopt.opt.exe -o s showable.ml circle.ml
<det>
File "circle.ml", line 10, characters 8-22:
<det>
This function is applied to too many arguments
<mrvn>
;; is a special token to get the interactive ocaml shell started.
<mrvn>
Not in the code you posted.
docelic has quit ["Client Exiting"]
<det>
I got rid of the let
<det>
on the last line
<mrvn>
thats wrong.
<mrvn>
can't have that in programs, only works with ;;
<det>
why is it wrong? I have no need to store the unit value in c :)
<karryall>
you can't have expressions at toplevel
<det>
erm ?
<karryall>
you need a let binding
<mrvn>
let _ = ....
<karryall>
let _ = ...
<det>
ok :)
<det>
mrvn, one should use them because ocaml objects are evil!
<mrvn>
I suggest you make a main.ml wich has one "let _ = " and then does all the work.
<det>
yeah
<mrvn>
det: ocaml objects are fine.
<det>
I am just in testing out how to implement interfaces stuff
<det>
mrvn, in my quick benchmark method dispatch was twice as slow as a function call
<det>
it should be the same
<det>
in the circumstances I had
<det>
ocaml needs the seperation of virtual methods and non-virtual, IMO
<det>
could probally be infered
<mrvn>
det: ocaml only has virtual methods. Bothers me too sometimes.
<mrvn>
and it can
<mrvn>
and it can't be infered because any later modules can overrule it
<mrvn>
.oO( backspace is too near to return)
<det>
:)
<det>
what is "it"
<mrvn>
I'm also not sure why ocaml needs a 2 level hash table and runtime numbering of the functions to dispatch them.
<mrvn>
det: deciding whats virtual and whats not.
<det>
well, ocaml always knows the type, and if it doesnt know the exact type, it should know the exact interface it supports in which case it becomes virtual
Smerdyakov has joined #ocaml
<mrvn>
But the interface of an object is somewhat fuzzy with a hashtable for dispatching functions.
<det>
well, I honestly think it could follow more of the c++ model reguarding dispatch you either have a list of a known type, or a list of an abstract base class, in which case the compiler generates a VT for *that* interface
<mrvn>
det: C++ can have a virtual tables of exponential size.
<mrvn>
I guess thats why ocaml uses a hashtable.
<det>
hrmm
<det>
I dont see why that would be
<mrvn>
det: C++ needs a virtual table for every path in a classes inheritance.
<mrvn>
With multiple inheritance that can be exponential.
<det>
true
<det>
I'd prefer it still
<mrvn>
Its highly unlikely that it gets big and that it can't be optimized down. But theoretically one could realy blow them up.
<det>
yeah, but you probally have bigger problems at that point :)
<Smerdyakov>
det, when you said you like OO for virtual functions, did you mean with dynamic dispatch based on which subclass of a class you have at any given time?
<det>
I'm not entirely sure what you mean
<det>
but I think so
<mrvn>
You have a showable class with a show method and inherit that in all other classes. Then you can make a heterogene list of showables.
<det>
I mean, implementation inheritance
<det>
yes
<det>
exactly
<det>
that's all I find useful about it
<det>
why do you ask ?
<mrvn>
det: Whats even more usefull is having objects announce themself and unannounce themself justby inheriting an announce class.
<Smerdyakov>
det, OK, good, because that + inheritance ARE all that is useful about C++ style OO, at least. :)
<Smerdyakov>
det, however, you may want to consider using datatypes instead!
<mrvn>
Smerdyakov: He is using functors atm.
<det>
inheritance other than implementation are garbage :)
<det>
s/are/is/
<Smerdyakov>
functors don't do the same thing.
<det>
Smerdyakov: datatypes ?
<mrvn>
det: Thats java style OO and realy sucks.
<Smerdyakov>
I don't know what OCaml calls them.
<Smerdyakov>
In SML, it's things like:
<Smerdyakov>
datatype 'a option = NONE | SOME of 'a
<mrvn>
Smerdyakov: How do you do inheritance with Datatypes?
<Smerdyakov>
mrvn, you don't. He said he only like dynamic dispatch, though!
<mrvn>
Smerdyakov: And how do you do that with datatypes?
<karryall>
the problem with heterogeneous list of showables is that it's pain to build because of the explicit subtyping
<Smerdyakov>
mrvn, you switch on which sum arm it is in a single function, instead of putting each implementaton in a separate class.
<det>
karryall: it's easy to build, just put in a VT and the object
<mrvn>
karryall: I think there is a way around that if one specifies the inheritance right.
<det>
karryall: or in my case the functions with the first argument partially applied :)
<karryall>
VT ?
<det>
Virtual Table
<karryall>
don't understand
<det>
just an array of pointers to all the functions showable requires
<det>
mrvn: I dont understand your announce thing
<karryall>
ah, objects as records of closures
<Smerdyakov>
mrvn, get what I'm saying?
<mrvn>
Smerdyakov: how do you make a heterogene list of things showable then?
<mrvn>
Smerdyakov: Especially if the different classes depend on each other in turnb.
<mrvn>
meaning are in their own modules.
<mrvn>
det: In your case I would have simply used a closure for Showable and not a functor.
<det>
mrvn, It will have more functions
<Smerdyakov>
mrvn, it's a list of values of the datatype.
<det>
mrvn, I was just experimenting
<Smerdyakov>
mrvn, you would have to put all the goodies in the same module in current ML's, probably.
<det>
Smerdyakov: you mean using a variant, like type a = Circle of float *float | Triangle of float * float *float | ... ?
<mrvn>
Smerdyakov: So you make a meta datatype: type showable = Circle c | Line l | Icon i | .... and a show method that dispatches to any of them?
<det>
mrvn, we think alike ;)
<Smerdyakov>
mrvn, yes
<det>
Smerdyakov: because in that case I need to be able to add new types at will
<mrvn>
Smerdyakov: most evil
<Smerdyakov>
det, oh, is that called a variant?
<det>
I thought it was called that
<Smerdyakov>
mrvn, is it called a variant? :)
<mrvn>
yep.
<Smerdyakov>
OK!
<Smerdyakov>
That is what I mean.
<det>
mrvn has spoken
<Smerdyakov>
And obviously you add new types at will by putting them in the list!
<det>
yes, variants require you to know all possible things that will be showable
<Smerdyakov>
Add them to the type a declaration.
<det>
most unmodular :)
<mrvn>
Smerdyakov: I think you would quickly end up in circular dependencies.
<det>
hey, is it possible to dynamicly load .so files in ocaml ?
<Smerdyakov>
But separate module methods require ostensibly "other people" to know the contract their implementations must follow.
<Smerdyakov>
mrvn, how?
<Smerdyakov>
mrvn, if it's all in one module...
<mrvn>
You want the variant to know all other types and every other type should have a function to convert itself to showable. Voila, circular depend.
<mrvn>
Having it all in one module is out of the question. Thats too evil.
<det>
yes
<mrvn>
You get name conflicts and all.
<det>
objects are less evil
<det>
IMO
<Smerdyakov>
mrvn, it's quite easy to do with mutual recursion.
<mrvn>
type line = { p1 : point; p2 : point; } type rect = { p1 : point; p2 : point; }
<mrvn>
And there you have a colission.
<mrvn>
Seperate Modules are a must.
<det>
yes
<det>
Smerdyakov: you are indeed evil it seems
<mrvn>
The way to go is using objects or interfaces.
<det>
interfaces meaning records of closures? :)
<Smerdyakov>
mrvn, no, you just wrap those type aliases inside single constructors.
<Smerdyakov>
Not to mention that you picked a bad example. Those types are the same, and you could just introduce two separate aliases for them to be made opaque later.
<mrvn>
det: records of closures is a way to go too.
<det>
{foo: float} is a structure ?
<mrvn>
Smerdyakov: no, lines and rects have different draw methods.
<mrvn>
det: no, thats a record.
<det>
mrvn, I'm sorry, I don't understand your structures line
<Smerdyakov>
mrvn, so?
<mrvn>
det: your functors use structs.
<det>
mrvn, oh, yes, but that can't be used to acheive hetergenous lists (unless you mean having them create the closures)
<mrvn>
Smerdyakov: Should lines and rects be both of type "thing defined by two points" just so don't get a name collision?
<mrvn>
type circle = { p1 : point; p2 : point; p3 : point; }
<mrvn>
another collision you would get
asqui has quit [Read error: 54 (Connection reset by peer)]
<mrvn>
And I know you can use type circle = point * point * point but that complicates access a lot of the time.
det has quit ["ircII EPIC4-1.1.2 -- Are we there yet?"]
det has joined #ocaml
det has quit [Killed (NickServ (Ghost: det!~chris@adsl-64-123-27-105.dsl.austtx.swbell.net))]
det has joined #ocaml
<Smerdyakov>
mrvn, there
asqui has joined #ocaml
<Smerdyakov>
's no reason not to make line and circle the same type inside the module, as you specified them, because your definiton MAKES THEM the same type.
<Smerdyakov>
mrvn, that's why I said you should wrap a constructor around them.
<mrvn>
No, lines have only 2 points.
<mrvn>
Also lines and rects are different. You can fill rects. In memory they are the same though.
det has quit [Client Quit]
<mrvn>
And wrapping a constructor around wastes 8 Byte per object.
<Smerdyakov>
I doubt it.
<Smerdyakov>
It wastes nothing in the SML compiler _I_ worked on.
<Smerdyakov>
And I'm sure OCaml does better than that!
<mrvn>
It has to store the variant type somewhere.
<Smerdyakov>
Why?
<Smerdyakov>
It has 1 constructor. It's isomorphic to the original.
<mrvn>
Because otherwise it wouldn't know whats a line and whats a rect
<Smerdyakov>
Just like it doesn't know what's an int and what's a string?
<Smerdyakov>
They're both 4 bytes in memory...
<mrvn>
It does. ints have a tag bit set for int and strings one for struct and then string.
<Smerdyakov>
They do?
<Smerdyakov>
Ew.
* Smerdyakov
drops a bomb on OCaml.
<mrvn>
ints are 8 byte (63 bit), string are 16+data i think.
<mrvn>
Smerdyakov: I'm 100%certain ml does the same.
<Smerdyakov>
Well, if every object in OCaml really has a full type tag, then that makes me not like it. :D
<karryall>
ints are one word minus 1 bit
<mrvn>
Otherwise the GC wouldn't know int from string.
<Smerdyakov>
mrvn, haha! Look at the TILT compiler. Uses fancy typed intermediate languages to avoid that.
<mrvn>
karryall: Well, yeah. I don#t have a braindead 32 bit cpu :)
<karryall>
heap-allocated objects have a one word header
<Smerdyakov>
(You can't look at it since it isn't released yet, though... or maybe it is.)
<Smerdyakov>
mrvn, but maybe I have not given the right example to show you your mistake.
<Smerdyakov>
mrvn, say you have two modules. Each one defines an abstract type that is really just an int. How does the compiler tell the difference between the two?
<mrvn>
Only thing that would prevent extra tags would be to use seperate heaps for the basic types and one for structured objects.
<mrvn>
Smerdyakov: Module1.t and Module2.t
<mrvn>
Smerdyakov: compile time only.
<mrvn>
In the binary its just an int.
<Smerdyakov>
mrvn, and how is that different from your complaint about telling the difference between line and rect, if each is wrapped in a constructor?
lus|wazze has joined #ocaml
<Smerdyakov>
<mrvn> Because otherwise it wouldn't know whats a line and whats a rect
<mrvn>
same as type foo = Zero | One | Two | Three is just an int.
<mrvn>
type foo = Zero | One of int | Two of int * int
<mrvn>
Now ocaml needs strcutures to store the arguments for the constructors.
<mrvn>
Zero is 1 word, One 2 words and Two is 3 words.
<Smerdyakov>
Right, but not for type line = LINE of {p1: point, p2: point} and type rect = RECT of {p1: point, p2: point}
<Smerdyakov>
The underlying type representations are identical.
<karryall>
you can't define anonymous records like that
<mrvn>
Smerdyakov: But 1 word more than {p1: point, p2: point}
<mrvn>
I think
<karryall>
yep
<mrvn>
karryall: Does ocaml optimize types with only one constructor with just one argument to just the argument?
<Smerdyakov>
karryall, you can't? Well, I am talking about SML. I've never used OCaml. Sorry!
<karryall>
mrvn: no
<Smerdyakov>
I think these differences are all to work with the OO stuff, yes?
<mrvn>
Smerdyakov: no
<mrvn>
Nothing to do with the OO stuff.
<Smerdyakov>
Then they must just to be to make things less efficient!
<Smerdyakov>
There is no other conceivable reason not to represent one-constructor datatypes with their contents.
<karryall>
mrvn: you meant somethg like type 'a t = Something of 'a
<karryall>
right ?
<mrvn>
karryall: yes
<Smerdyakov>
karryall, why isn't 'a t represented as 'a?
<karryall>
there's a good reason, it was discussed by Xavier on a post somewhere
<lus|wazze>
because that would be a pretty useless optimizatzion
<Smerdyakov>
lus|wazze, saves space and time... how useless?
<lus|wazze>
ehm
<lus|wazze>
no it doesnt save anything
<Smerdyakov>
karryall, OK. I know the big SML compilers do use this optimization. I'd be interested to see Xavier's reason.
<Smerdyakov>
lus|wazze, so how are sum types represented usually?
<lus|wazze>
because you will never HAVE a one-constructor type in a real application
<Smerdyakov>
lus|wazze, you will. It's for creating a truly new datatype that may have the same data as another, as using the constructor to keep yourself honest about remembering that.
<Smerdyakov>
lus|wazze, it's a common idiom, in SML code, at least. I guess not so common in OCaml because it has a runtime cost.
<lus|wazze>
so implementing an optimization for that specific case would be wasted effort
<lus|wazze>
why not just hide the type in a module's signature?
<Smerdyakov>
lus|wazze, no. It has real benefits for abstraction.
<lus|wazze>
then
<Smerdyakov>
lus|wazze, because you manipulate the type in that very module.
<lus|wazze>
simply do
<Smerdyakov>
lus|wazze, otherwise it would be useless...
<mrvn>
As long as you have different modules thats reminder enough.
<lus|wazze>
module Foo : sig type 'a t end = struct type 'a t = 'a end;;
<lus|wazze>
and then you can use 'a Foo.t
<lus|wazze>
same effect
<lus|wazze>
but more efficient because 'a t IS represented as 'a
<Smerdyakov>
lus|wazze, 1st, wrapping a constructor around it is ONLY helpful in places that actually know the definition of the soon-to-be-abstract type
<Smerdyakov>
lus|wazze, 2nd, what you said is only "more efficient" in OCaml because a simple optimization is not implemented.
<mrvn>
type tuple = { i1 : int; i2 : int; };;
<mrvn>
type p1 = tuple;;
<mrvn>
type p2 = Point of tuple;;
<lus|wazze>
module Foo : sig type 'a t end = struct type 'a t = 'a let make x = (x : 'a t) and get (x : 'a t) = (x: 'a) end;;
<mrvn>
p1 has size 2 and p2 has size 1.
<lus|wazze>
I just don't see the advantages of using a singe-constructor sum type
<lus|wazze>
personally, I would have the compiler give an error, or at least a warning, on encountering such
<mrvn>
lus|wazze: less to type.
<Smerdyakov>
Does OCaml let you use "flex record" patterns, where you match on only a few of the elements of a record?
<Smerdyakov>
I.e., in SML: case myRecord of {x, y, ...} => x + y
<mrvn>
Smerdyakov: nope.
<karryall>
yes
<Smerdyakov>
^-- literal code
<Smerdyakov>
... stands for "any other fields"
<Smerdyakov>
Whom should I believe?!
<lus|wazze>
yes
<Smerdyakov>
OK
<mrvn>
Smerdyakov: A record is allways one type, no point in matching it. Just use it.
<lus|wazze>
it does
<lus|wazze>
you dont type ...
<lus|wazze>
you just omit the fields youre not interested in
<lus|wazze>
ie
<lus|wazze>
type foo={x:int;y:int}
<mrvn>
let foo r = r.x + r.y;;
<Smerdyakov>
So, while this is allowed in SML, it must always know exactly what the full record type is.
<lus|wazze>
match bar:foo with {x=x} -> x;;
<Smerdyakov>
So wrapping in a constructor gives this information automatically.
<mrvn>
lus|wazze: aeh, whats that. never seen that before.
<Smerdyakov>
If you don't use a wrapper, you have to either specify all fields or give a full type annotation anyway.
<lus|wazze>
well in ocaml it does know the type anyway because using the same field identifier in two different record types is not allowed
<lus|wazze>
so naming a single field is sufficient already
<mrvn>
# let foo bar = match bar:foo with {x=x} -> x;;
<mrvn>
Syntax error on the :
<lus|wazze>
yeah you have to put ( ) around it
<Smerdyakov>
lus|wazze, OK. It seems different design decisions are cascading here. :-)
<Smerdyakov>
lus|wazze, but do you see how this is useful in SML/
<mrvn>
# let foo bar = match (bar:foo) with {x=x} -> x;;
<mrvn>
val foo : foo -> int = <fun>
<mrvn>
That knows the exact type. So why match at all?
<lus|wazze>
but if bar is already is alreaedy of type foo you can leave out the type annotation
<mrvn>
# let foo2 bar = bar.x;;
<mrvn>
val foo2 : foo -> int = <fun>
<lus|wazze>
let foo bar = match bar with {x=x} -> x;;
<Smerdyakov>
mrvn, because matching in the function parameter looks nicer :-)
<lus|wazze>
Smerdyakov, yeah I see how single-constructor sum type can be useful in SML
<lus|wazze>
but in OCaml i dont see any reason why one might want to use one
<Smerdyakov>
Maybe there isn't. There probably isn't if Xavier doesn't think it should be there. :-)
<mrvn>
lus|wazze: Is there any difference between foo and foo2 above I don#t see?
<mrvn>
lus|wazze: The match is just like saying let x = bar.x in, right?
<lus|wazze>
correct
<lus|wazze>
and the bar.x version is probably more efficient as well
<lus|wazze>
and more readable
<lus|wazze>
i was just explaining that it is _possible_ :)
<lus|wazze>
to match against just some of the fields of a record
<mrvn>
lus|wazze: If you match say 5 members of the record it gets a lot to type with lets.
<mrvn>
By the way, is it anywhere defined what 'type foo = {x:unit;y:unit} let foo = {x=print_string "x\n"; y=print_string "y\n"}' prints?=
<lus|wazze>
no
<lus|wazze>
i don't think anyway
<mrvn>
It seems to be allways reverse order: y x
<lus|wazze>
well i believe the order is undefined
<lus|wazze>
so it doesnt matter which order it turns out to be in practice
<mrvn>
lus|wazze: if I have 'type foo = { mutable x:int; mutable y:int; }' can pass just the x to a function in a way that changes to x are reflected in the foo?
<mrvn>
+I
<lus|wazze>
npo
<lus|wazze>
use type foo = { x: int ref; y: int ref}
<lus|wazze>
if you want to do that
<mrvn>
Thats twice the size.
<lus|wazze>
well what you want to do is bad style anyway
<lus|wazze>
you should rather write it in a more functional style
<lus|wazze>
like, a function which returns the new value of x
<lus|wazze>
like
<ad_>
are there any security programmaing problems with Ocamls ? (like format bugs, buffer overflows, etc..)
<lus|wazze>
bar.x <- somefun bar.x;;
<ad_>
(-s)
<mrvn>
ad_: nope.
<lus|wazze>
nope
<lus|wazze>
ocaml's static typechecking catches most of those things, and the rest are checked at runtime
<mrvn>
lus|wazze: somefun immediatly returns and only at a later stage sets x.
<mrvn>
lus|wazze: I'm wrieting asynchronous IO.
<lus|wazze>
hmm well if you're that dependant on side-effects i guess you will just have to live with the larger size of type foo
<lus|wazze>
but in such a case, personally, i would use classes
<mrvn>
Nah. I can have somefun return a Lazy.t or a closure that evaluates to the latewr read value when its read.
* Smerdyakov
doesn't like classes. :-)
<mrvn>
In ocaml you have allways multiple ways of doing things.
<mrvn>
Sometimes classes are easiest
<Smerdyakov>
Which is bad, if it's possible to get by with less ways!
<mrvn>
classes nicely explain and hide sideeffects away.
<Smerdyakov>
Not as nicely as monads. :-)
<mrvn>
If I call a method of a class its natural that that might affect the class.
<mrvn>
Smerdyakov: initializers are a realy nice feature too
<Smerdyakov>
These are like the funny 'variable name(constructor parameters)' in C++ constructors, before the code bodies?
<mrvn>
Smerdyakov: no. C++ doesn#t have them.
<mrvn>
They are done after the constructor.
<mrvn>
class int i = object(self)
<mrvn>
method print = Printf.printf "(Int %d)\n" i
<mrvn>
initializer print_string "new "; self#print
<mrvn>
end;;
<mrvn>
let i = new int 1;;
<mrvn>
new (Int 1)
<mrvn>
val i : int = <obj>
<Smerdyakov>
OK. I don't see how that's useful if you don't start out with an object system....
<mrvn>
Say you have a bunch of connections that need to stay connected by sending out keep-alife pings.
<lus|wazze>
you can call methods from the initializer, and the object will aready be fully constructed; thats how its useful
<mrvn>
You can make a class that registers itself in a list of connection to be kept alife so you can't forget to register it.
<mrvn>
The important word being "can't"
<Smerdyakov>
But you can do this with a module that gives you one function to construct an abstract connection value.
<mrvn>
Smerdyakov: Then you could forget to register inside the module.
<mrvn>
cause inside the module you wouldn't have to use the constructor function.
<mrvn>
ok, thats far fetched.. :)
* Smerdyakov
rolls his eyes.
<mrvn>
Smerdyakov: But say you have a module. Now you have server and client connections.
<mrvn>
So you add two mode modules that utilize the generic connection module.
<mrvn>
generic, server and client have a read and a write function but you still have to define read/write function in the client and server modules to displatch to the generic one.
<Smerdyakov>
So? You know exactly what you're doing.
<mrvn>
I'm lazy. objects are less to type sometimes.
<Smerdyakov>
If you use the same type, you can just open the "parent" structure.
<mrvn>
By the way, how do you make objects that refenrecne other objects of the same kind (or itself)?
<mrvn>
Smerdyakov: opening the parent structure would possibly open too much.
<Smerdyakov>
That's a risk I'm willing to take! :D
<mrvn>
I never needed to use open yet. I rather use let write = Generic.write
<mrvn>
Can you open Generic.write without getting all the rest of Generic?
<Smerdyakov>
*shrug*
lus|wazze has quit ["Quidquid latine dictum sit, altum sonatur."]
Smerdyakov has quit ["gone"]
Smerdyakov has joined #ocaml
wrunt has quit [asimov.freenode.net irc.freenode.net]
wrunt has joined #ocaml
asqui has quit [Read error: 104 (Connection reset by peer)]
asqui has joined #ocaml
lus has joined #ocaml
lus is now known as lus|wazze
rhil_zzz is now known as rhil_work
Smerdyakov has quit ["it is no more"]
karryall has quit ["tcho"]
cDlm_ has joined #ocaml
cDlm has quit [Killed (NickServ (Ghost: cDlm_!cdlm@lns-th2-12-82-64-180-37.adsl.proxad.net))]
cDlm_ is now known as cDlm
mrvn_ has joined #ocaml
lus|wazze has quit ["Quidquid latine dictum sit, altum sonatur."]
lus|wazze has joined #ocaml
mrvn has quit [Read error: 110 (Connection timed out)]
mrvn_ is now known as mrvn
cDlm has left #ocaml []
whee has joined #ocaml
Smerdyakov has joined #ocaml
<vegai>
trivial french help, please. "Email" in french?
<mrvn>
And you ask that here because?
* mrvn
wonders if lus|wazze speaks french.
<vegai>
mrvn: because all ocaml-coders know french
<mrvn>
I certainly don't.
<vegai>
ergo you are not an ocaml-coder ;D
<vegai>
seriously, "doesn't hurt to ask", I thought
<mrvn>
ocaml is getting popular outside france too
<vegai>
yes
<mrvn>
Well, this is the only channel I'm in where I ever see anyone talking french regulary.
<mrvn>
By now I should have picked up the odd word here and there but nothing :(
<vegai>
it's perhaps best not to learn french from french people =)
skwich has joined #ocaml
skwich has left #ocaml []
<lus|wazze>
[22:04:05] * mrvn wonders if lus|wazze speaks french. <-- why me in particular? :[
* vegai
shrugs
<vegai>
is knowledge of french something to be ashamed of? =)
<lus|wazze>
yes
<vegai>
oh?
<lus|wazze>
;)
<vegai>
I think people who understand that language are geniuses
<vegai>
not unlike physicists
<lus|wazze>
depends
<vegai>
...or just crazy -- not unlike mathematicians
<lus|wazze>
to understand written french is not that difficult actually
<vegai>
yes, that's true
<lus|wazze>
to understand spoken french , however, is impossible
<lus|wazze>
or to produce correct french, written or otherwise, too
<vegai>
it's actually much more regular than english
<lus|wazze>
i would sincerely doubt that
<lus|wazze>
let me get my bescherel (or whichever way its spelled)
<lus|wazze>
i just have to flip through that and fetch me some examples of the subjonctif, or the passé simple
<vegai>
ok, subjonctif is an ugly thing
<lus|wazze>
for an english verb, you usually only have to memorize two forms
<vegai>
also, gene forms of words
<vegai>
la/le
<vegai>
whatever they are actually called
<lus|wazze>
well thats not really difficult ... for a native german speaker like me, at least
<lus|wazze>
in german we even have THREE of those
<vegai>
semantically void
<vegai>
yeah, you got neuter
<vegai>
I don't respect language features that have no semantic value
<lus|wazze>
well it depends
<vegai>
...but I'm just beginning my linguistic studies, so...
<vegai>
...don't mind me
<vegai>
gotta go zzz now, early tomorrow
<lus|wazze>
hm
<lus|wazze>
ok
<lus|wazze>
gnight
<lus|wazze>
i actually just was going to refute your point that grammatical gender is necessarily bad :)
<lus|wazze>
but if you have to go to bed now go ahead^^
lus|wazze has quit ["Quidquid latine dictum sit, altum sonatur."]
lus|wazze has joined #ocaml
asqui has quit [Read error: 104 (Connection reset by peer)]
asqui has joined #ocaml
Smerdyakov has quit ["Willy Wonka is at the door."]
asqui has quit [Read error: 104 (Connection reset by peer)]
asqui has joined #ocaml
asqui has quit [Read error: 54 (Connection reset by peer)]
whee has quit ["BitchX-1.0c18 -- just do it."]
asqui has joined #ocaml
asqui has quit [Read error: 60 (Operation timed out)]
asqui has joined #ocaml
asquii has joined #ocaml
asqui has quit [Read error: 60 (Operation timed out)]
asquii is now known as asqui
Smerdyakov has joined #ocaml
mattam has quit [Read error: 113 (No route to host)]
Smerdyakov has quit ["go"]
asqui has quit [Read error: 104 (Connection reset by peer)]