flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
Camarade_Tux has quit ["Leaving"]
Camarade_Tux has joined #ocaml
Associat0r has quit []
jonasb has quit [Remote closed the connection]
nuncanada has joined #ocaml
Cheshire has quit [Read error: 110 (Connection timed out)]
<jganetsk> what's a private type abbreviation?
<jganetsk> i know private types
alexyk has quit []
Stefan_vK1 has quit ["Leaving."]
<thelema_> jganetsk: http://caml.inria.fr/pub/docs/manual-ocaml/manual021.html#toc76 -> 7.9.2: Private type abbreviations
thelema has quit [Nick collision from services.]
thelema_ is now known as thelema
thelema_ has joined #ocaml
alexyk has joined #ocaml
ched has quit ["Ex-Chat"]
<thelema> jganetsk: it declares a type abbreviation that has to be coerced back to the regular type, and can only be constructed within the defining module.
alexyk has quit []
jganetsk has quit [Remote closed the connection]
seafood_ has joined #ocaml
adrian_2002ca has joined #ocaml
<adrian_2002ca> hi all, how do I compute the integral to a math function(float->float) ?
<adrian_2002ca> :'( im sooo lost now
nuncanada has quit ["Leaving"]
<adrian_2002ca> help anyone
kaustuv has joined #ocaml
<adrian_2002ca> heeeeelp
seafood has quit [Connection timed out]
<hcarty> adrian_2002ca: If someone here has time and can help they will likely offer their assistance
<adrian_2002ca> hcarty: kk, thanks!
adrian_2002ca has left #ocaml []
palomer has joined #ocaml
<palomer> im reading the lablgtk source
<palomer> and I can't find a default value for xpad
<palomer> ahh, ? notation is strange
<palomer> cool!
<thelema> default values are fun.
<palomer> wait
<palomer> erm...
<palomer> this poses a problem for me
<palomer> you see...
<palomer> I'm recycling widgets
<palomer> so I need to reset them when I'm done with them
<palomer> so I need the default value of xpad and friends
<palomer> you reading me?
<palomer> I'll just take a wild guess of... 0
<thelema> the default value isn't right there?
<palomer> right where?
<palomer> im looking at gMisc.mli
<palomer> gtkPack.ml has xpadding=0
<thelema> yup, just found taht...
<palomer> but I don't see how the 2 relate
<palomer> how do those two files interact?
alexyk has joined #ocaml
<thelema> hmmm...
<kaustuv> any debian ocaml maintainers here?
<thelema> palomer: assume it's 0.
<palomer> but then there's ?spacing and ?homogeneous in vbox
Axioplase_ has quit ["Lost terminal"]
seafood has joined #ocaml
<palomer> and then xalign
<palomer> for labels
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
seafood_ has quit [Read error: 110 (Connection timed out)]
Axioplase has joined #ocaml
jeddhaberstro has joined #ocaml
<ski__> palomer : you could hide the object inside an ADT represented as a `ref', and replace the object, when revoking
<ski__> or, you could build that into a wrapper object like
<ski__> # let make_revoker o = let r = ref o in (fun () -> r := object method b = raise Revoked method c = raise Revoked end),object method b = !r#b method c = !r#c end;;
<ski__> val make_revoker : < b : 'a; c : 'b > -> (unit -> unit) * < b : 'a; c : 'b > = <fun>
<ski__> # a;;
<ski__> - : < b : int; c : int -> int > = <obj>
<ski__> # let rev_a , r_a = make_revoker a;;
<ski__> val rev_a : unit -> unit = <fun>
<ski__> val r_a : < b : int; c : int -> int >
<ski__> = <obj>
<ski__> so `r_a' is a stand-in for `a', and `rev_a ()' revokes it
<ski__> obviously though, it is a bit tedious to manually wrap all the methods in the `make_revoker'
<ski__> (and there might potentially be other problems with this approach, too .. i haven't considered it that much, yet)
* ski__ leaves
alexyk has quit []
christian_ has joined #ocaml
<christian_> Hi bots!!
<christian_> !weather NY
wks has joined #ocaml
bzzbzz has quit ["leaving"]
alexyk has joined #ocaml
wks has left #ocaml []
willb has joined #ocaml
m3ga has joined #ocaml
palomer has quit [Remote closed the connection]
alexyk has quit []
alexyk has joined #ocaml
vuln has quit ["fuiz"]
jeddhaberstro has quit []
m3ga has quit ["disappearing into the sunset"]
alexyk has quit [Read error: 110 (Connection timed out)]
alexyk has joined #ocaml
palomer has joined #ocaml
<palomer> so... class foo = let bar = ref 0 in object(self)... end
<palomer> bar is like a global variable in this case, right?
<palomer> but its scope is limited
<ski__> define "global"
<ski__> (or, rather, please don't)
<ski__> (it might be nicer to lift out the `object ..Revoked.. end' from the `fun () -> ..' .. or maybe even make sure the revoker only assign once .. but this is just optimization)
<christian_> hi...which language should i learn ( first): ocaml or haskell?
* ski__ grows unsure of whether my earlier suggestion was seen by palomer
<ski__> christian_ : depends on what you want
<ski__> do you want to learn FP ?
<christian_> well i want to write a multiagentsystem
<palomer> ah yes
<christian_> and yeah..FP of course
<palomer> ski__, thanks for the earlier suggestion
<christian_> But OO is also nice
<ski__> it can be, yes
<palomer> ski__, by global I mean that one variable is accessible by all instances
<palomer> which seems to be the case
<ski__> haskell has the advantage of (more or less) forcing you to learn FP methods, by not letting you get away with imperative patterns so easily
<christian_> i see
<christian_> So OO is overrated?
<ski__> ocaml has the advantage of possibly moving slowly from imperative to FP methods, not taking the deep plunge
<christian_> ok
<ski__> some people prefer one, some the other
<palomer> most people here probably prefer ocaml
<ski__> also, there's other differences between haskell and ocaml, of course
<palomer> most people in #haskell probably prefer haskell
<ski__> palomer : unsurprisingly :)
<palomer> :P
<christian_> so i think
<christian_> i heard haskell has a crappy module system
<ski__> it has, indeed
<christian_> or say: not so good as ocaml
<ski__> (speaking as a haskeller myself, who's sometimes visiting ocaml)
<ski__> yes, it's ok (unlike certain other languages)
<ski__> but it's not great
<christian_> i see
<ski__> (`it' being haskell's module system)
<ski__> though in the beginning, the advanced module systems isn't all that important
<christian_> is ocaml a message based language as - eg erlang?
<palomer> I don't use the ocaml module features all that much
<ski__> and not always for larger applications, either
<palomer> in fact, I don't use them at all
<ski__> christian_ : no
<christian_> Well, i want my code ready for future for the next 10 years
<christian_> i want to study informatic in germany
<ski__> palomer : instances of what ?
<christian_> and i dont want such languages as c or c++ or java
<palomer> ski__, of the class
<palomer> christian_, those languages might be around longer than both ocaml and haskell
<ski__> christian_ : yes, it'd say OO (which isn't even well-defined) is largely over-hyped
<ski__> (s/it/i/)
<christian_> i see
<palomer> OO is great!
<christian_> but there are too close to the machine
<ski__> it can be, yes
<ski__> but insisting on OO methods in all cases is not great
<palomer> like anything
<christian_> i want a language which is possibly ready for quantum computers
<ski__> (yes)
<christian_> i think c is out of date then
<ski__> then i'd say one of the best bets is keeping track of FPs
<christian_> so i thought
<christian_> :)
<ski__> many later features in many languages have originated in FPs .. and in some cases trickled down to imperative languages
<ski__> s/many languages/language theory/
<christian_> i heared that of c#
<palomer> oh my my my
<palomer> it's not a global variable
<palomer> now im REALLY confused
<ski__> (garbage collection,closures,type inference,generics)
<ski__> palomer : `it' ?
<christian_> ok at least i have a clue to stick with FP, thanx
<christian_> good n8
<palomer> what's the difference between let a = ref 5;; class foo = object(self)....end
<palomer> and class foo = let a = ref 5 in object(self) ... end
<palomer> ?
<ski__> the former defines three things, a variable `a', a class type `foo' and a class constructor `foo'
<ski__> the latter doesn't define a variable `a'
<ski__> (except locally)
<palomer> right
<palomer> so the only difference is the scope of a, right?
<palomer> those two pieces of code are otherwise identical, right?
christian_ has quit ["Verlassend"]
<ski__> in the latter, i believe there's a new local `a' constructed each time the class constructor `foo' is invoked .. but i'm not sure
* ski__ checks
<ski__> ok, i was mistaken
<ski__> a single `a' is created in the latter, which is shared by all objects created from `foo'
<palomer> you sure?
* ski__ was thinking the body of a `class foo = ...' was thunked, like bodies of methods are
<palomer> class adjusted_point x_init =
<palomer> let origin = (x_init / 10) * 10 in ...
<ski__> that's a different thing
<palomer> same syntax though
<ski__> in that case i would be sure there's be a new `origin' created each time
<ski__> (even before i check, i mean)
alexyk has quit []
mishok13 has joined #ocaml
<palomer> the only difference is that origin refers to a parameter
<ski__> compare with a non-`class' example
<palomer> and a doesn't
<ski__> let foo x = let r = ref x in ...
<ski__> creates a new `r' every time `foo' is called
<palomer> ahhhhh, righto!
<ski__> let foo = let r = ref 42 in fun x -> ...
<ski__> is the same, except only a single `r' is created
<palomer> pfffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffft
<palomer> haha
<palomer> how right you are
<ski__> probably you can do
* palomer hits self
<ski__> class foo = let blah = ... in fun x_init -> object .. end;;
<ski__> if you want a single `blah'
<ski__> or you could define `blah' before `foo', and hide it with the module system
alexyk has joined #ocaml
<ski__> (unfortunately there's no `local' construction in O'Caml, otherwise you could also do
<palomer> gotcha!
<ski__> local blah = ...
<ski__> ..more local defs..
<ski__> in class foo x_init = object .. end
<ski__> ..more non-local defs..
<ski__> end
<ski__> )
alexyk has quit [Client Quit]
<ski__> btw, what did you want a revoker for ?
<palomer> you mean a way to invalidate objects?
<ski__> (i assume this could be for doing some kind of capability-based security, yes ?)
<ski__> yes
<palomer> nope
<palomer> I'm recycling gtk widgets
<ski__> ok
<palomer> so...
<palomer> I put them in an object
<palomer> and when I need to remove them, I remove them from the container and place them in an array
<palomer> then I need to invalidate that object
<ski__> it would be nice if there was a nicer way to delegate messages to the surrogate on to the underlying object (or to the revoked stand-in)
<ski__> without having to do bioler-plate for each method
<ski__> (er ignore the last parenthesis)
<palomer> hrmph
<palomer> I think ill just relegating accessing the widget to a single method
<ski__> (the alternate i mentioned first would be to construct something like
<ski__> type 'a revokable
<ski__> fetch : 'a revokable -> 'a
<ski__> make_revokable : 'a -> (unit -> unit) * 'a revokable
<ski__> exception Revoked
<ski__> )
<palomer> hrmphrmph
<palomer> how do I set the width of a label?
<palomer> I need to offset a widget
<palomer> so im creating a hbox
<palomer> and im inserting two widgets
<palomer> one is an empty label of width 15
<palomer> and the other is the widget im offsetting
<palomer> (me thinks there must be a better way of doing this)
Demitar has quit [Read error: 60 (Operation timed out)]
Demitar has joined #ocaml
ttamttam has joined #ocaml
palomer has quit [Remote closed the connection]
rwmjones_ has joined #ocaml
Ched has joined #ocaml
s4tan has joined #ocaml
_zack has joined #ocaml
OChameau has joined #ocaml
ikaros has joined #ocaml
Alpounet has joined #ocaml
kaustuv has quit [Read error: 60 (Operation timed out)]
kaustuv has joined #ocaml
seafood_ has joined #ocaml
seafood has quit [Read error: 60 (Operation timed out)]
arquebus has joined #ocaml
arquebus has quit [Read error: 104 (Connection reset by peer)]
Yoric[DT] has joined #ocaml
seafood_ has quit []
mikeX has left #ocaml []
jah has joined #ocaml
dabd has joined #ocaml
Axioplase is now known as Axioplase_
pango has quit [Remote closed the connection]
Yoric[DT] has quit ["Ex-Chat"]
Demitar has quit [Remote closed the connection]
Demitar has joined #ocaml
ryosei has joined #ocaml
sporkmonger has quit []
paul424 has joined #ocaml
<paul424> hi8 hello how do I inherit some basic type into my class
dabd has quit [Remote closed the connection]
<paul424> ehh anyone ? please please help me ......
<flux> basic types cannot be inherited
<flux> I'm not sure I understand the question right, though
<paul424> flux: you do understand very well ;)
<paul424> I need to wrapp some of the basic types into some class .... to provide some methods / interface that is expected from other class
<paul424> damm the time is pending .....
<paul424> I need to have a class of int which would provide the method toString and parseString
<paul424> flux: what's wrong with this ? http://codepad.org/d3PML0gp
<ski__> try removing the `ref'
<paul424> method toString = int32.toString my_int
<paul424> ^^^^^
<paul424> Unbound value int32
<ski__> (you probably don't want both `mutable' and `ref' .. if you do, you'll know)
<ski__> s/int32/Int32/
<ski__> (O'Caml is case-sensitive)
<paul424> I know that... but last time I do something in ocaml was long time ago .......
<paul424> ok how do I provide the method toString ? semms the Int32 lacks it either .......
kaustuv has quit [Nick collision from services.]
kaustuv_ has joined #ocaml
<ski__> Int32.to_string
kaustuv has joined #ocaml
kaustuv has left #ocaml []
<ski__> (also, `to_string' there is not a method, just a module member)
<paul424> ski_: ok how do I convert int32 to int ?
<paul424> I mean int32 to int ?
<ski__> Int32.to_int
<ski__> (fyi `Int32' is the module, `Int32.int32' is the type)
<paul424> ah ok
sporkmonger has joined #ocaml
<paul424> ski__: how do I force the myint to be of type int32 ?
<ski__> (one can also do `module Blah = Int32;;' in the interactor, for the signature of the module)
<ski__> probably
<ski__> val mutable my_int : Int32.t = whatever
<ski__> (but i don't know whether there's integer literals of type `Int32.t')
<paul424> yeap that's what i ndeed
<paul424> the literal of type int32
<paul424> ski__: method toString = int32.toString my_int
<paul424> ^^^^^
<paul424> Unbound value int32
<paul424> epp wrong line
<paul424> and local_value = (new mcell 0)
<paul424> ^
<paul424> This expression has type int but is here used with type int32
<paul424> see ?
<ski__> as i remarked
<ski__> try `(Int32.of_int 0)' instead
<ski__> (or `(Int32.of_string "0")')
<flux> paul424, local_Value = new mcell 0l
<paul424> aha ok
<ski__> ok, there are apparently such integer literals
* ski__ couldn't find it in the manual at <http://caml.inria.fr/pub/docs/manual-ocaml/lex.html#integer-literal> .. but maybe it's elsewhere
<ski__> ah, now i see, "Chapter 7 Language extensions", <http://caml.inria.fr/pub/docs/manual-ocaml/manual021.html#toc68> "Integer literals for types int32, int64 and nativeint"
<paul424> ski_: ok big thanks from the ocaml lamer ;)
<ski__> np
ryosei2 has joined #ocaml
paul424 has quit ["ChatZilla 0.9.84 [Firefox 3.0.6/2009011913]"]
ryosei has quit [Read error: 110 (Connection timed out)]
jah has quit ["Quitte"]
ryosei2 is now known as ryosei
ryosei has left #ocaml []
ryosei has joined #ocaml
ryosei has left #ocaml []
Alpounet has quit ["Ex-Chat"]
waleee has joined #ocaml
<thelema_> paul: IIRC, there's also Int32.zero and Int32.one for those constants
kaustuv has joined #ocaml
Ariens_Hyperion has joined #ocaml
jeddhaberstro has joined #ocaml
Cheshire has joined #ocaml
Ariens_Hyperion has quit []
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
Camarade_Tux has joined #ocaml
willb has quit [Read error: 110 (Connection timed out)]
Snark has joined #ocaml
<Snark> plop
<Snark> when will the new batteries hit debian ?
willb has joined #ocaml
<thelema_> snark: as soon as the wonderful ocaml debian packagers make the package.
s4tan has quit []
<kaustuv> Snark: ask on #debian-ocaml on irc.debian.org
jonafan has quit [Read error: 110 (Connection timed out)]
Associat0r has joined #ocaml
jonafan has joined #ocaml
Yoric[DT] has joined #ocaml
<Snark> thelema, kaustuv I just managed to compile newer packages...
<Yoric[DT]> hi
<Snark> Yoric[DT], eh, I did try to use batteries
<Yoric[DT]> Any feedback?
<Snark> yes, it didn't work -- that's with the current debian unstable package
alexyk has joined #ocaml
<Snark> I'm just finishing compiling alpha3 to see if my problems went away
<Yoric[DT]> ok
<Yoric[DT]> _zack is to blame (and thank) for the current Debian package
<_zack> here I am
<_zack> batteries alpha3 packages are on their way
<_zack> they've been delayed because we were all working for the lenny release
<_zack> and now we have to take care of 3.11
<_zack> (which has been waiting for Lenny in turn)
<Yoric[DT]> \o/
waleee has quit ["http://www.mibbit.com ajax IRC Client"]
<mbishop> I'm guessing 3.11 will be in ubuntu 9.04?
* mbishop kind of wants to go back to debian, is tired of ubuntu and it's "no major version bump" policy
<Snark> back
<Snark> _zack, it's good, I finally managed to use the alpha2 .diff.gz to make alpha3 packages
<_zack> Snark: cool
<Snark> Unbound module System
<Snark> ^ not that cool :-/
<Snark> oh, but those names must have changed
xevz has quit [Read error: 54 (Connection reset by peer)]
jganetsk has joined #ocaml
xevz has joined #ocaml
<Yoric[DT]> Snark: :/
<Yoric[DT]> Yeah, a few names have changed.
<Snark> let me port my code forward
<Snark> ulines_of;;
<Snark> - : Batteries.IO.input -> Extlib.Rope.t Extlib.Enum.t = <fun>
<Snark> sigh... why do I see Extlib types there?
<Yoric[DT]> Hum.
<Yoric[DT]> Because we haven't solved that issue yet.
<Snark> file.open_in doesn't look good either
<Yoric[DT]> As in not working or as in ugly type?
<Yoric[DT]> That ugly type problem is pervasive.
<Yoric[DT]> And there doesn't seem to be much of a workaround for the moment.
ttamttam has quit ["Leaving."]
<Snark> both
<Snark> ah, no, open_in seems to work
<Snark> I have issues with ulines_of
<Snark> Extlib.Rope.t Extlib.Enum.t is annoying : I would have expected Extlib.ExtUTF8.UTF8.t Extlib.Enum.t :-/
<Yoric[DT]> Bug thelema about that :)
<Yoric[DT]> (although I might be the culprit, I'm not sure, he's the one in charge of this particular point)
<Snark> well, I'm surprised a function documented as "offer the lines of a UTF-8 encoded input as an enumeration" doesn't have any UTF8 in its type
<Yoric[DT]> Well, Rope is our default UTF-8 type.
<Yoric[DT]> (it's immutable and supports fast concatenation)
<jonafan> are you guys gunna throw my btree implementation in there
<jonafan> it has 27 downloads
<jonafan> my thrall will notice its absence
<Yoric[DT]> jonafan: don't hesitate to throw a Request for Features.
<jonafan> haha i'm just kidding
<Yoric[DT]> At the moment, we're trying to stop adding too many features until release 1.0 .
<Yoric[DT]> Once we have reached that stage, we'll resume breathing :)
<Snark> oh, UTF8 isn't what I wanted then ?
Associat0r has quit [Read error: 104 (Connection reset by peer)]
<Yoric[DT]> Snark: presumably not.
<Snark> good!
<Snark> it works type-wise!
<Snark> wonderful
<Snark> now I just have to find out how to run a batteries script
alexyk has quit []
Yoric[DT] has quit [Read error: 104 (Connection reset by peer)]
_zack has quit ["Leaving."]
det has joined #ocaml
Yoric[DT] has joined #ocaml
det_ has quit [Read error: 104 (Connection reset by peer)]
<jganetsk> is there any project to build a parallel GC for ocaml?
<jganetsk> because haskell's got one now
Ariens_Hyperion has joined #ocaml
ched_ has joined #ocaml
rwmjones_ has quit [Read error: 60 (Operation timed out)]
Ched has quit [Read error: 110 (Connection timed out)]
ched_ is now known as Ched
<thelema_> jganetsk: yes, it's starting by building pluggable GCs
<jganetsk> thelema_: this is a project that's going on?
<thelema_> not by INRIA theselves
<jganetsk> what's it called?
* thelema_ doesn't have his mailing list archives available to look that up, sorry
<jganetsk> it's on ocaml mailing list?
<kaustuv> There was a project last summer at Jane St. Capital to build a concurrent GC for ocaml.
<jganetsk> that was last summer?
ttamttam has joined #ocaml
<kaustuv> Yes. You can read about it here: http://ocaml.janestreet.com/?q=node/38
<kaustuv> From discussion with Damien Doligez, it seems it's really unlikely to be merged into mainstream any time soon.
schmx is now known as schme
<olegfink> ttamttam: added.
<ttamttam> Waouh
<ttamttam> Before I sent my email. Thanks
<olegfink> heh, yeah, given the thing doesn't send mail notifications on user registration, that was just a coincidence.
<jganetsk> does ocaml still not allow more than one physical ocaml thread to run at once?
<Yoric[DT]> jganetsk: ocaml itself, no.
<Yoric[DT]> JoCaml, BSML, OCamlp3l, etc., do.
<jganetsk> so there are no plans to extend that to ocaml?
Alpounet has joined #ocaml
<Yoric[DT]> Not that I know of.
<olegfink> ttamttam: by the way, do you happen to have a 64-bit machine?
<ttamttam> Unfortunately not.
<ttamttam> Well. The notebook of my wife is, but the OS installed is 32 bits.
<olegfink> okay, someone else will have to check if dlopen works correctly there (and with Int64.t?)
alexyk has joined #ocaml
jah has joined #ocaml
alexyk has quit [Read error: 54 (Connection reset by peer)]
alexyk has joined #ocaml
Stefan_vK has joined #ocaml
alexyk has quit [Client Quit]
Anarchos has joined #ocaml
thelema has quit [Read error: 110 (Connection timed out)]
alexyk has joined #ocaml
<thelema_> oleg: if you write the code, I'll try it on my 64-bit PC when I get home in ~4 hours.
<olegfink> thanks, will try to write something meaningful and ping you then.
<thelema_> Merci.
jah has quit ["Quitte"]
<ttamttam> olegfink: what is the dynload_next.c file for?
<olegfink> seems to be a glue code providing a similar function to dlopen (but with a weird name) which isn't used anywhere.
marmottine has joined #ocaml
<ttamttam> Thanks
<olegfink> it probably is of no interest if noone has a macos box.
<olegfink> (i can't even tell the difference between dyld and rld and which one is used in modern macoses)
arquebus has joined #ocaml
Ariens_Hyperion_ has joined #ocaml
munga` has joined #ocaml
Waleee has joined #ocaml
<alexyk> olegfink: I have a macosx box and everything about ocaml on mac is of supreme and paramount interest to me! :)
Ariens_Hyperion has quit [Read error: 110 (Connection timed out)]
<Yoric[DT]> :)
Waleee has quit []
Waleee1 has joined #ocaml
Cheshire has quit [Nick collision from services.]
ofaurax has joined #ocaml
Cheshire has joined #ocaml
xevz_ has joined #ocaml
Waleee2 has joined #ocaml
Waleee2 has left #ocaml []
Waleee2 has joined #ocaml
xevz__ has joined #ocaml
xevz_ has quit [Client Quit]
xevz__ is now known as xevz_
xevz has quit [":wq"]
xevz_ is now known as xevz
Waleee2 has left #ocaml []
Waleee has joined #ocaml
Cheshire has quit [Read error: 104 (Connection reset by peer)]
Waleee1 has quit [Read error: 110 (Connection timed out)]
Cheshire has joined #ocaml
sporkmonger has quit [Operation timed out]
arquebus has left #ocaml []
alexyk has quit []
Waleee has left #ocaml []
Waleee has joined #ocaml
hkBst has joined #ocaml
pango has joined #ocaml
<ttamttam> olegfink: I did a lot of modifications, but don't know how to commit?
thelema has joined #ocaml
rwmjones_ has joined #ocaml
marmottine has quit ["mv marmotine Laurie"]
mib_kgg83r has joined #ocaml
mib_kgg83r is now known as chupish
Snark has quit ["Ex-Chat"]
alexyk has joined #ocaml
rwmjones_ has quit ["Leaving"]
Ariens_Hyperion_ has left #ocaml []
vuln has joined #ocaml
jonasb has joined #ocaml
christian has joined #ocaml
ttamttam has left #ocaml []
Waleee has left #ocaml []
ikaros has quit ["Leave the magic to Houdini"]
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
sporkmonger has joined #ocaml
Alpounet has quit ["Ex-Chat"]
alexyk has quit []
Cheshire has quit ["Leaving"]
seafood has joined #ocaml
ofaurax has quit ["Leaving"]
alexyk has joined #ocaml
Amorphous has quit [Connection timed out]
alexyk has quit [Client Quit]
willb has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
bdc334 has joined #ocaml