ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | http://www.ocaml.org | OCaml 4.01.0 announce at http://bit.ly/1851A3R | Logs at http://irclog.whitequark.org/ocaml
Lycurgus has quit [Client Quit]
alexst_ has quit [Ping timeout: 260 seconds]
contempt has quit [Disconnected by services]
contempt has joined #ocaml
WraithM has quit [Ping timeout: 264 seconds]
SethTisue has joined #ocaml
ebzzry has quit [Ping timeout: 255 seconds]
jwatzman|work has quit [Quit: jwatzman|work]
q66 has quit [Quit: Leaving]
huza has joined #ocaml
huza has quit [Client Quit]
huza has joined #ocaml
SethTisue has quit [Quit: SethTisue]
SethTisue has joined #ocaml
huza has quit [Ping timeout: 264 seconds]
araujo has quit [Read error: Connection reset by peer]
shinnya has quit [Ping timeout: 264 seconds]
araujo has joined #ocaml
milosn has quit [Ping timeout: 260 seconds]
ygrek has joined #ocaml
malo has quit [Remote host closed the connection]
rand000 has quit [Quit: leaving]
xaimus_ has quit [Ping timeout: 245 seconds]
xaimus has joined #ocaml
SethTisue has quit [Quit: SethTisue]
manizzle has quit [Ping timeout: 260 seconds]
milosn has joined #ocaml
penglingbo has joined #ocaml
ebzzry has joined #ocaml
seanmcl has joined #ocaml
fold has joined #ocaml
seanmcl has quit [Client Quit]
seanmcl has joined #ocaml
seanmcl has quit [Client Quit]
ustunozgur has joined #ocaml
manizzle has joined #ocaml
philtor_ has joined #ocaml
tianon has quit [Ping timeout: 240 seconds]
lewis1711 has joined #ocaml
<lewis1711> can one make a record that takes a polymorphic variant on one of its fields?
distantunclebob has joined #ocaml
milosn has quit [Ping timeout: 240 seconds]
milosn has joined #ocaml
<ygrek> what's the problem? show the code
philtor_ has quit [Ping timeout: 255 seconds]
<lewis1711> ygrek, https://gist.github.com/LewisAndrewCampbell/f217e7894ab15d3c99ae line 16, I want the unbox field to be a void pointer, or a dynamic type. or something like a run-time-extensible union type.
tianon has joined #ocaml
<lewis1711> I'm not having much luck figuring out Univ, which i thoguth seemed like the answer
isBEKaml has joined #ocaml
rrolles has joined #ocaml
<rrolles> so... what do I need to know in order to include module types in function pointers?
<rrolles> sorry, function signatures
<ygrek> Univ should help here iiuc
<rrolles> I have three module types: Lang, CFG, and CFGBuilder, and two Make functors for producing CFGs and CFGBuilders
<rrolles> then I have two concrete instances of those modules, X86CFG implementing CFG, and X86CFGBuilder implementing CFGBuilder
<rrolles> now I have another file that exports two functions in the .mli, like so: val assemble_channel : X86CFG.X86CFGBuilder.C.G.t -> int32 -> (int32 -> unit) -> unit
<rrolles> except including the X86CFGBuilder directly in the function signature is undesirable
<rrolles> I want to be able to use different module types other than X86CFG and X86CFGBuilder, which are compatible according to the underlying parameterized types
distantunclebob has left #ocaml [#ocaml]
mcclurmc has quit [Remote host closed the connection]
<rrolles> basically, CFG and CFGBuilder are parameterized over the Lang module, and I want to have a different Lang module that has the same interface (including identical types)
<rrolles> but my existing code dies with a type error when I try to pass the alternative CFGBuilder instantiated-objects to assemble_channel
mcclurmc has joined #ocaml
<rrolles> basically, including the actual name of the instantiated module in the function signature is too concrete
<rrolles> I want to instead specify some type constraints
<rrolles> i.e. you can call assemble_channel for any instantiation of this module that has type lang = X86.x86instrpref
<rrolles> rather than, you can only call it for X86CFG.X86CFGBuilder (which has type lang = X86.x86instrpref)
<rrolles> is this making any sense?
<rrolles> to be very concrete about it, I want my assemble_channel to have a type signature that looks something like (CFG.CFGBuilder with type lang = X86.x86instrpref).C.G.t
<rrolles> thereby allowing me to use any instantiation of that module which the same ¨lang¨ type
axiles has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
mcclurmc has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
mcclurmc has joined #ocaml
isBEKaml has quit [Quit: leaving]
<ygrek> rrolles, can you name the module type separately and then use it in funciton sigs?
<ygrek> module type IntSet = Set.S with type elt = int
<ygrek> so module type CFGBuilderWithX86InstrButNotAlwaysX86CFGBuilder = CFG.CFGBuilder with type lang = X86.x86instrpref
<ygrek> but that's a module type and you cannot refer to it's contents in signature
<ygrek> can you put assemble_channel inside functor?
<rrolles> I guess I technically could
<rrolles> why not?
<ygrek> hm, that doesn't help %)
<ygrek> bad idead
<rrolles> I don't know actually
<rrolles> the assembler obviously has a bunch of X86 specific stuff in it
jao has quit [Ping timeout: 240 seconds]
<rrolles> it sounds like you understand what I'm talking about at least
<rrolles> the module system has always given me incredibly painful headaches
<rrolles> basically I try to "get it working" and then never touch it again
<rrolles> unfortunately my project is using OCamlGraph
<rrolles> are there any good articles/manual pages/etc I should read about modules?
<rrolles> none of them really seem to go to the depth of questions like these
<ygrek> I can not point at one place
<ygrek> see the manual section on moduels
<ygrek> there are alos useful answers on SO on modules
<ygrek> here is the paper http://caml.inria.fr/pub/papers/xleroy-manifest_types-popl94.pdf on which modules original design is based I believe
<ygrek> I think you cannot refer the type of the result of functor application
<ygrek> because there is no such thing as functors of signatures
<ygrek> so either you can describe your type in terms of lang
<ygrek> or you have to actually build that module and then refer to the C.G.t type
<ygrek> if this type is an alias then having X86Cfg in type path is not a problem - because aliases are equal type - path doesn't matter
<ygrek> but if it is abstract - that's a problem
<rrolles> ok
<rrolles> if I understand, I can replace may X86CFG.X86CFGBuilder type with something that looks roughly like CFGBuild(Lang with type t = X86.x86instrpref)?
<ygrek> what is CFGBuild?
<ygrek> and no, it doesn't look right to me
<ygrek> there are no functors of signature
<ygrek> only functors of modules
<rrolles> val assemble_channel : (module C(L : Lang with type t = X86.x86instrpref) : CFGBuild.S).C.G.t -> int32 -> (int32 -> unit) -> unit
<rrolles> syntax error on that
<ygrek> no
<ygrek> that won't work
<ygrek> you are trying to get the signature of functor application without applying it
rishabhjain has joined #ocaml
rishabhjain has quit [Remote host closed the connection]
mort___ has quit [Quit: Leaving.]
<rrolles> ok
<rrolles> then I guess I didn't really understand what you were saying above
<rrolles> in what I read into it, I thought you were saying that I described the type constraints on lang, and then described basically the functor application to that, then I could get something like what I wanted
<rrolles> but you might also have been saying that what I am trying to do is impossible
<rrolles> I'm willing to refactor my code, change the module type, whatever
<rrolles> for example if I could make this polymorphic somehow, so I can just pass around terms of type X86.x86instrpref CFGBuild.S.t
<rrolles> then it doesn't matter how the things are constructed, only that they satisfy that type signature
<rrolles> so having multiple functors to build that same concrete type would be totally fine
mort___ has joined #ocaml
<ygrek> rrolles, here is also a thread you might find interesting - https://groups.google.com/forum/#!topic/fa.caml/daiBWmtRHnI
<ygrek> if you can describe that type t without refering to a module - than do it
mort___ has quit [Client Quit]
mcclurmc has quit [Remote host closed the connection]
<ygrek> if it only can be produced by functor applicaiton (e.g. it is abstract) - then I believe you cannot say "give me some type in the module that gets produced when you apply functor to (other module with type lang equaling x86smth)"
<ygrek> what is that C.G.t ?
<rrolles> ok
<rrolles> so the output of the functor does match a module type
<rrolles> i.e. that's already defined
<rrolles> CFG.ml/mli are my control flow graphs; CFGBuild.ml/mli are my "control flow graph builder" modules; X86CFG.ml/i contains "control flow graphs" and a "control flow graph builder" for X86
Arsenik has joined #ocaml
<rrolles> I'm in over my head a bit
<rrolles> so let me step back and ask a different question
<rrolles> is it possible for me to write a function that operates on CFG module instances directly, outside of the CFG module definition?
<rrolles> CFG.mli again being at http://pastebin.com/3PZiPw3k
<rrolles> and, if not, can I modify CFG.mli such that I can enable this type of thing
philtor has quit [Ping timeout: 260 seconds]
philtor has joined #ocaml
tidren has joined #ocaml
siddharthv_away is now known as siddharthv
philtor has quit [Ping timeout: 240 seconds]
ontologiae has joined #ocaml
ygrek has quit [Ping timeout: 256 seconds]
rishabhjain has joined #ocaml
<def`> rrolles: cpuld you explain what you want ?
<rrolles> sorry I'm having a hard time with that
<rrolles> my framework has a module CFG that is parameterized by language; presently a functor takes a Language structure which dictates the type of the language
<rrolles> from there, I have another module CFGBuild, also parameterized by the Language structure, that lets you build CFG objects
<rrolles> I have some functions that operate upon CFGs which are created with type Language.t = X86.x86instrpref
<rrolles> except those functions have signatures that are specific to the functors in CFGBuild that was used to build the CFG object
<rrolles> so I can only use that particular functor to build types that are accepted by that function
<rrolles> when in reality, I want that code to be able to operate upon any CFG object that has the same language type
<rrolles> so what I've been playing with for the last hour or so is to turn the CFG module itself into some sort of polymorphic module
<rrolles> so I can have things like 'a CFG.t
<rrolles> and then hopefully write functions that operate upon any type of CFG
<def`> you can either make another functor or a function with fort-class module
<rrolles> so the latter is an alluring prospect, but I couldn't get the syntax correct
<def`> first*. What you want is abstracting over a cfg instance, right?
<rrolles> yes, still paramterized by the language upon the CFG
<def`> type 'a cfg = (module CFG with type Language.t = 'a)
<def`> ooups, with type language = 'a sry
<def`> And if you are in a different unit, the path will of course be CFG.CFG
<rrolles> ok
<rrolles> alluringly, that compiles
<rrolles> so now I go to make the next change, in CFGBuild.mli
<rrolles> there is this line: module C : CFG.CFG with type language = lang list
<rrolles> I try to modify that to something like " module C : lang list CFG.cfg
<rrolles> "
<rrolles> but that is apparently a syntax error
RenRenJuan has joined #ocaml
BitPuffin has quit [Ping timeout: 240 seconds]
hhugo has joined #ocaml
diethyl has quit [Ping timeout: 240 seconds]
<rrolles> how do I use that 'a CFG.cfg type I just defined in the definition of the CFGBuild module?
diethyl has joined #ocaml
angerman has joined #ocaml
<rrolles> though I have managed to get the compiler to accept this 'a cfg type, any attempts to use it are falling flat
Arsenik has quit [Remote host closed the connection]
<def`> re
<rrolles> hello
pgomes has joined #ocaml
<def`> rrolles: let f (type a) ((module CFG) : a cfg) … = …
ygrek has joined #ocaml
RenRenJuan has quit [Quit: This computer has gone to sleep]
Simn has joined #ocaml
racycle has joined #ocaml
<rrolles> okay
<rrolles> this is getting towards working
<rrolles> so let's say I want to write a function that requires that the type 'a in 'a cfg is fixed, say X86.X86instrpref
<rrolles> and now I need to get at an inner module
<rrolles> let assemble_channel (cfg : X86.x86instrpref CFGBuild.s) startea ob =
<rrolles> let module S = (val cfg : X86.x86instrpref CFGBuild.s) in
<rrolles> let startv = try S.C.find_vertex cfg startea with ...
ontologiae has quit [Ping timeout: 264 seconds]
<rrolles> this however is not working
racycle has quit [Client Quit]
<def`> why is this not working?
<rrolles> syntax error on line 3 at the position of the CFGBuild token, expected ')'
rishabhjain has quit []
<rrolles> sorry, line 2
Eyyub has quit [Ping timeout: 255 seconds]
<def`> just write (val cfg)
<def`> X86.x86instrpref CFGBuild.s is a term type, while this is in the position of a module type
<rrolles> I do not follow about term types versus positions of module types, sorry for my ignorance
<rrolles> (val cfg) also errors
<rrolles> very generic "syntax error" at the close paren
<def`> what is your version of ocaml ?!
<rrolles> 3.12
Eyyub has joined #ocaml
<def`> ouch
<rrolles> yeah, long story
<def`> is it possible for you to use 4.01?
<rrolles> I have this whole toolchain built off of OCaml 3.12
<rrolles> I embedded a REPL in some other application
<rrolles> I could technically upgrade it, but that would be even more hassle
<rrolles> I would like to do it, but I also want to accomplish stuff, you know
<def`> there is strong compatibility, there are high chances that this works out of box.
<rrolles> unfortunately not
<def`> yet, I don't think that there is proper support for what you want to achieve in 3.12
<rrolles> ok
<def`> you will have to be very explicit
<rrolles> well, your point is very reasonable
huza has joined #ocaml
<def`> so:
<def`> let module S = (val cfg : CFG with type language = X86.x86instrpref) in …
<def`> which you can always alias upfront: module type X86_CFG = CFG with type language = X86.x86instrpref
<def`> let module S = (val cfg : X86_CFG) in .
<rrolles> so that works
<rrolles> nice, thank you
<def`> basically, 3.12 doesn't try to do any inference at all on packages, so you have to annotate each (val …) and each (module …)
<rrolles> that's good motivation to upgrade
<rrolles> anything that takes the pain out of my ass a little bit
manizzle has quit [Read error: Connection reset by peer]
demonimin_ has joined #ocaml
manizzle has joined #ocaml
manizzle has quit [Read error: Connection reset by peer]
manizzle has joined #ocaml
<rrolles> ok
<rrolles> just one more of these and it'll work
<rrolles> let assemble_channel (cfg : X86.x86instrpref CFGBuild.s) startea ob =
<rrolles> let module S = (val cfg : CFGBuild.S with type lang = X86.x86instrpref) in
<rrolles> let module C = S.C in
<rrolles> let startv = try C.find_vertex cfg startea
<rrolles> error in the try clause
_0xAX has joined #ocaml
<rrolles> referring to cfg
demonimin has quit [Ping timeout: 256 seconds]
<rrolles> Error: This expression has type X86.x86instrpref CFGBuild.s = (module CFGBuild.S with type lang = X86.x86instrpref) but an expression was expected of type S.C.G.t. The type constructor S.C.G.t would escape its scope
<def`> hard to tell without more context
<rrolles> sorry
<rrolles> this is brutal
<rrolles> I've been at this for about 3.5 hours, it's 12:30AM
ustunozgur has quit [Remote host closed the connection]
ollehar has joined #ocaml
cago has joined #ocaml
<rrolles> ok
<rrolles> I'm giving up for the night
<rrolles> I thank both def and ygrek for helping me, that's very kind of you, particularly considering I was lost and confused
Kakadu has joined #ocaml
huza has quit [Quit: WeeChat 0.3.8]
thomasga has joined #ocaml
thomasga has quit [Client Quit]
huza has joined #ocaml
BitPuffin has joined #ocaml
huza has quit [Client Quit]
sagotch has joined #ocaml
AltGr has joined #ocaml
angerman has quit [Remote host closed the connection]
angerman has joined #ocaml
RenRenJuan has joined #ocaml
<companion_cube> o/
rrolles has quit [Ping timeout: 252 seconds]
angerman has quit [Quit: Bye]
alpounet has joined #ocaml
huza has joined #ocaml
huza has quit [Client Quit]
Arsenik has joined #ocaml
<Kakadu> \o
Muzer has quit [Quit: ZNC - http://znc.sourceforge.net]
lewis1711 has left #ocaml ["Leaving"]
Eyyub has quit [Ping timeout: 256 seconds]
Eyyub has joined #ocaml
ontologiae has joined #ocaml
manizzle has quit [Ping timeout: 260 seconds]
dsheets has joined #ocaml
manizzle has joined #ocaml
avsm has joined #ocaml
q66 has joined #ocaml
studybot_ has quit [Remote host closed the connection]
studybot_ has joined #ocaml
ollehar has quit [Ping timeout: 255 seconds]
_0xAX has quit [Remote host closed the connection]
samebchase has quit [Ping timeout: 255 seconds]
paddymahoney has quit [Ping timeout: 240 seconds]
sagotch has quit [Remote host closed the connection]
sagotch has joined #ocaml
samebchase has joined #ocaml
jludlam has joined #ocaml
jludlam is now known as jonludlam
WraithM has joined #ocaml
paddymahoney has joined #ocaml
ygrek has quit [Ping timeout: 252 seconds]
ygrek has joined #ocaml
ontologiae has quit [Ping timeout: 240 seconds]
Arsenik has quit [Remote host closed the connection]
avsm1 has joined #ocaml
avsm has quit [Ping timeout: 240 seconds]
waneck has quit [Ping timeout: 240 seconds]
yacks has quit [Ping timeout: 240 seconds]
WraithM has quit [Quit: leaving]
ontologiae has joined #ocaml
Arsenik has joined #ocaml
maattdd has joined #ocaml
studybot_ has quit [Ping timeout: 264 seconds]
ontologiae_ has joined #ocaml
middayc has joined #ocaml
avsm has joined #ocaml
studybot_ has joined #ocaml
hhugo has quit [Write error: Connection reset by peer]
Sim_n has joined #ocaml
hhugo has joined #ocaml
avsm1 has quit [Ping timeout: 240 seconds]
ontologiae has quit [Ping timeout: 255 seconds]
Arsenik has quit [Remote host closed the connection]
ollehar has joined #ocaml
Simn has quit [Ping timeout: 240 seconds]
Asmadeus has quit [Ping timeout: 240 seconds]
pollux has quit [Ping timeout: 240 seconds]
companion_cube has quit [Ping timeout: 240 seconds]
Valdo has quit [Ping timeout: 240 seconds]
yroeht has quit [Ping timeout: 252 seconds]
pippijn has quit [Ping timeout: 252 seconds]
patronus_ has quit [Ping timeout: 240 seconds]
acieroid` has quit [Ping timeout: 255 seconds]
kerneis has quit [Ping timeout: 240 seconds]
nispaur has quit [Ping timeout: 240 seconds]
bacam has quit [Ping timeout: 272 seconds]
Arthur_R` has quit [Read error: Connection reset by peer]
def` has quit [Ping timeout: 245 seconds]
adrien has quit [Ping timeout: 245 seconds]
The_third_man has quit [Ping timeout: 240 seconds]
vbmithr_ has quit [Ping timeout: 255 seconds]
Arthur_R` has joined #ocaml
asmanur_ has quit [Ping timeout: 252 seconds]
deavid has quit [Ping timeout: 252 seconds]
AltGr has quit [Ping timeout: 264 seconds]
vbmithr has joined #ocaml
adrien has joined #ocaml
bacam has joined #ocaml
deavid has joined #ocaml
yroeht has joined #ocaml
pollux has joined #ocaml
kerneis has joined #ocaml
The_third_man has joined #ocaml
pippijn has joined #ocaml
asmanur has joined #ocaml
Valdo has joined #ocaml
AltGr has joined #ocaml
companion_cube has joined #ocaml
nispaur has joined #ocaml
patronus has joined #ocaml
Eyyub has quit [Ping timeout: 256 seconds]
siddharthv is now known as siddharthv_away
Muzer has joined #ocaml
Asmadeus has joined #ocaml
acieroid has joined #ocaml
def` has joined #ocaml
sagotch has quit [Remote host closed the connection]
middayc has quit [Ping timeout: 260 seconds]
middayc has joined #ocaml
_0xAX has joined #ocaml
maattdd has quit [Ping timeout: 245 seconds]
<whitequark> Drup: note that for now you need ppx_tools from trunk
<whitequark> I've asked Alain to release it, but not yet
alpounet has quit [Remote host closed the connection]
alpounet has joined #ocaml
<Drup> I know
avsm has quit [Read error: Connection reset by peer]
alpounet has quit [Ping timeout: 240 seconds]
fold has quit [Ping timeout: 264 seconds]
alexst has joined #ocaml
pgomes has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
tidren has quit [Remote host closed the connection]
alexst has quit [Ping timeout: 252 seconds]
pgomes has joined #ocaml
ustunozgur has joined #ocaml
alpounet has joined #ocaml
Arsenik has joined #ocaml
rand000 has joined #ocaml
badon has joined #ocaml
brendan has quit [Ping timeout: 256 seconds]
ollehar has quit [Ping timeout: 255 seconds]
SethTisue has joined #ocaml
brendan has joined #ocaml
fold has joined #ocaml
sagotch has joined #ocaml
siddharthv_away is now known as siddharthv
_andre has joined #ocaml
simn__ has joined #ocaml
<sagotch> is there sugar to write something like [0 as x; x - 1]? (avoid the `let` definition)
ggole has joined #ocaml
Sim_n has quit [Ping timeout: 240 seconds]
<Drup> what is it suppose to mean ?
ygrek has quit [Ping timeout: 245 seconds]
SethTisue has quit [Quit: SethTisue]
<Drup> just a let with fewer characters ?
SethTisue has joined #ocaml
freling has joined #ocaml
siddharthv is now known as siddharthv_away
<sagotch> I mean defining a variable in a list definition.
typedlambda has quit [Ping timeout: 252 seconds]
<Drup> in pattern, it would work
alexst has joined #ocaml
<Drup> (but "x-1" wouldn't)
typedlambda has joined #ocaml
<sagotch> I is not even a pattern, so I guess there is no way to achieve this
eikke__ has joined #ocaml
yacks has joined #ocaml
<sagotch> I asked just in case I missed any magic trick in the language, but with no hope ;)
arj has joined #ocaml
alexst has quit [Ping timeout: 255 seconds]
arj has quit [Client Quit]
SethTisue has quit [Quit: SethTisue]
<flux> I suppose it would make sense for 'as' to introduce a 'let' bound variable, but I'm uncertain what would be its scope
<flux> also I would be afraid what code using it would look like..
Moataz-E has joined #ocaml
SethTisue has joined #ocaml
ollehar has joined #ocaml
RenRenJuan has quit [Quit: This computer has gone to sleep]
maattdd has joined #ocaml
<nox> sagotch: Why do you want to avoid a let?
<def`> the problem with your construction is indeed the notion of scope, this would against the rest of the design of the language (except for type variables :))
maattdd has quit [Ping timeout: 272 seconds]
<sagotch> I am not sure about why I would do that, the first idea was: writing LLVM ir instruction list, I would like to write [alloca as a; store 0 a; load a as r; ret r] because it is strange to write let x1 = alloca a in let x2 = load a whereas I did not write the store instruction yet
<sagotch> And yes, the scope is very undefined, even in my mind :P
<def`> I would like a lighter syntax for that kind of case… But I don't know what :)
SethTisue has quit [Quit: SethTisue]
<sagotch> (plus, the final list would be quite "ugly" [x1; store 0 x1; x2; ret x2] ...
<def`> (you can probably define a monad to build this list)
<Drup> (I was going to advise a monadic interface and though "naaah, too type-hip")
<def`> (this would replace your "let x = a in body" by ~ "a >>= fun x -> body" while building your program under the hood)
SethTisue has joined #ocaml
<nox> Or a Camlp4 DSL for LLVM IR.
<Drup> (I think ppx would be far enough for that)
<def`> … Or just stick to the language
<Drup> you're no fun :p
<ggole> Can you rewrite instructions? If so, you could do something like let a = placeholder () and b = placeholder () and ... in rewrite a (alloca ...); rewrite b (store 0 a); ...
<ggole> More verbose, but the interesting part would be in the order that you would expect.
<ggole> And SSA form programs are graph like, their variables won't usually nest nicely
<sagotch> I will think about monads...
penglingbo has quit [Ping timeout: 245 seconds]
<sagotch> but ggole, what do you mean by "rewriting instructions" ?
<ggole> Mutate in place.
<sagotch> hum, ok I see the idea
SethTisue has quit [Quit: SethTisue]
<ggole> Looking at the LLVM docs, it seems this is only possible per basic block
<sagotch> It is actually not linked to the llvm lib, so I could do whatever I want
<ggole> So you are designing your own IR?
<sagotch> it still llvm ir, but I do not rely on libllvm to manipulate it
<ggole> Sounds like you should stick to the semantics of LLVM then.
tidren has joined #ocaml
<Drup> sagotch: any reasons not to use libllvm ?
alexst has joined #ocaml
ontologiae_ has quit [Ping timeout: 264 seconds]
arj has joined #ocaml
tidren has quit [Ping timeout: 256 seconds]
alexst has quit [Ping timeout: 240 seconds]
<sagotch> Mainly having, something more easy and more pleasant to handle in ocaml than c bindings.
<Drup> the binding isn't that terrible
bjorkintosh has quit [Ping timeout: 245 seconds]
avsm has joined #ocaml
<BitPuffin> anyone know a good resource for learning type theory?
<companion_cube> Pierce: Types and Programming Languages?
ollehar has quit [Ping timeout: 255 seconds]
tidren has joined #ocaml
maattdd has joined #ocaml
<jpdeplaix> +1 for companion_cube
<companion_cube> might be Peirce btw, I always forget
<Drup> there is a nice paper where you gradually introduce new typing stuff in a lambda calculus and you end up at an ML-like language
shinnya has joined #ocaml
arj has quit [Quit: Leaving.]
<Drup> and obviously I don't find it anymore
ollehar has joined #ocaml
<ggole> It's Pierce
darkf has quit [Quit: Leaving]
tidren has quit [Ping timeout: 260 seconds]
maattdd has quit [Ping timeout: 255 seconds]
struktured has quit [Ping timeout: 252 seconds]
alexst has joined #ocaml
<BitPuffin> companion_cube: Oh I thought you were highlighting someone in here named Pierce
alexst has quit [Ping timeout: 240 seconds]
<BitPuffin> bit Pierce is a book, not a paper
<BitPuffin> well actually he's an author
claudiuc has quit [Remote host closed the connection]
claudiuc has joined #ocaml
<Drup> BitPuffin: you want simply a paper to "learn type theory" ?
<Drup> it's a bit ambitious :p
<adrien_oww> step 1: do some haskell
<BitPuffin> well you were talking about a paper Drup :P
<adrien_oww> step 2: write a blog post about type theory
<adrien_oww> step 3: start learning about type theory
<BitPuffin> lol
<Drup> step 2.5 monad as buritos
<Drup> BitPuffin: it would have been more of a small introduction
<BitPuffin> Drup: sure, but maybe a good place to start :o
<Drup> (but I don't recall the title anyway)
sagotch has quit [Ping timeout: 260 seconds]
claudiuc has quit [Ping timeout: 260 seconds]
tane has joined #ocaml
penglingbo has joined #ocaml
divyanshu has joined #ocaml
ollehar has quit [Ping timeout: 255 seconds]
sagotch has joined #ocaml
libertas has quit [Ping timeout: 240 seconds]
RenRenJuan has joined #ocaml
badon_ has joined #ocaml
badon has quit [Disconnected by services]
jonludlam has quit [Ping timeout: 240 seconds]
badon_ is now known as badon
rand000 has quit [Quit: leaving]
Khady has quit [Remote host closed the connection]
slash^ has joined #ocaml
maattdd has joined #ocaml
Khady has joined #ocaml
Khady has joined #ocaml
Khady has quit [Changing host]
huza has joined #ocaml
cago has quit [Quit: cago]
sagotch has quit [Remote host closed the connection]
alexst has joined #ocaml
srax has quit [Ping timeout: 240 seconds]
Arsenik has quit [Remote host closed the connection]
alexst has quit [Ping timeout: 240 seconds]
ygrek has joined #ocaml
mcclurmc has joined #ocaml
ollehar has joined #ocaml
ustunozgur has quit [Remote host closed the connection]
ustunozgur has joined #ocaml
srax has joined #ocaml
ustunozgur has quit [Remote host closed the connection]
ustunozgur has joined #ocaml
ustunozgur has quit [Remote host closed the connection]
olauzon has joined #ocaml
divyanshu has quit [Ping timeout: 264 seconds]
ontologiae_ has joined #ocaml
divyanshu has joined #ocaml
S11001001 has joined #ocaml
S11001001 has quit [Changing host]
S11001001 has joined #ocaml
ontologiae_ has quit [Ping timeout: 272 seconds]
RenRenJuan has quit [Quit: This computer has gone to sleep]
shinnya has quit [Ping timeout: 264 seconds]
philtor_ has joined #ocaml
Moataz-E has quit [Quit: Leaving]
alexst has joined #ocaml
tidren has joined #ocaml
_0xAX has quit [Remote host closed the connection]
huza has quit [Ping timeout: 252 seconds]
ontologiae_ has joined #ocaml
tidren has quit [Ping timeout: 272 seconds]
philtor has joined #ocaml
<BitPuffin> what do you guys think about a syntax like this https://gist.github.com/BitPuffin/a457c0a381bc8daf5d8f
leowzukw has joined #ocaml
<companion_cube> "rec" looks really ugly
<BitPuffin> well it could be recurse or self or whatever
<whitequark> why do people feel a need to invent new syntax
<BitPuffin> whitequark: I'm not looking to invent a new one, I was making an ml style syntax and began to realize that if the rule is that most things end when a value is reached then I can have a very minimal syntax
<companion_cube> this doesn't look very ML
<BitPuffin> so I kind of stumbled upon it
<BitPuffin> had let rec and everything
divyanshu has quit [Ping timeout: 256 seconds]
<companion_cube> indeed
<BitPuffin> the difference here was that I thought, what if I try to unify so that the syntax reflects that variables are just functions without parameters
<companion_cube> if you write a match construct, please add a terminator
<BitPuffin> why?
<companion_cube> because of nested matches
<BitPuffin> hmm
<BitPuffin> yeesh
<BitPuffin> you might be right
<BitPuffin> well actually no
<BitPuffin> the match must be exhaustive
<BitPuffin> so it has a clear ending
<ousado> O_O
divyanshu has joined #ocaml
avsm has quit [Ping timeout: 240 seconds]
philtor_ has quit [Ping timeout: 240 seconds]
avsm has joined #ocaml
<BitPuffin> so match something with Some x -> match x with Some -> print "woot" () None -> print "aw" () (# exhaustion reached #) None -> print "wut" ()
<BitPuffin> so it works for a compiler
<BitPuffin> and if you indent it correctly it will look fine
<companion_cube> it looks pretty dangerous
<companion_cube> if you have wildcards/variables
<companion_cube> if you get exhaustivity wrong, the compiler will stop the submatch at the wrong place
<BitPuffin> but a wildcard forces an exhaustive
<BitPuffin> if you get exhaustivity wrong the compiler won't compile it
<companion_cube> I mean, if you make a mistake the compiler won't warn you
<ousado> exhaustiveness is typer business
<companion_cube> it will just make the sub-patterm too long
<ousado> distinguishing where matches end is the parsers business
<BitPuffin> like if you forget a wildcard then it will whine
<BitPuffin> I don't see any danger really
<BitPuffin> you'd have to present me with a real example
<companion_cube> match x with Some x when x=() -> _ | None -> ...
<companion_cube> exhaustive or not?
<companion_cube> as a subpattern
<companion_cube> and at the parser phase
<BitPuffin> ousado: I'm sure you can make it work with multiple passes or something
<companion_cube> that's a really bad idea
<ia0> +1
<ousado> that's so silly it doesn't deserve further comments
<companion_cube> by reading the code you will have no clue
<BitPuffin> why would it be at the parser phase?
<companion_cube> well, what would the parser return otherwise?
<companion_cube> an ambiguous AST?
<ia0> some people do that to resolve precedence at a later phase
<BitPuffin> an intermediate thing
<ia0> I think this is the case in Agda
eikke__ has quit [Ping timeout: 240 seconds]
avsm has quit [Ping timeout: 252 seconds]
<ia0> but you definitely want a precise AST before you start typing
<ia0> some ambiguities have to be resolved before
<BitPuffin> companion_cube: I don't see why it's hard to see that it's exhaustive
agarwal1975 has quit [Quit: agarwal1975]
<companion_cube> BitPuffin: in real patterns it will be difficult to see
<ia0> match x with | K y when n_or_np () == y -> blabla
<BitPuffin> companion_cube: I'm not so convinced
<companion_cube> and if you modify a type by adding a variant, it will get even worse
<ia0> p_or_np *
<companion_cube> the compiler is supposed to help you find broken matches
<ia0> where y is of type bool
<companion_cube> with your idea it just won't
<companion_cube> ia0: :)
<companion_cube> match x,y,z with | _ when x^3 + y^3 <> z^3 -> ....
<ia0> exhaustiveness is an over-approximation
<ia0> you can not take it for granted
leowzukw has quit [Quit: leaving]
<BitPuffin> so what you are talking about is pattern guards and not sub patterns?
<companion_cube> pattern guards in sub-patterns
avsm has joined #ocaml
<companion_cube> also: match _ with ... | foo -> bar; yolo
<ousado> BitPuffins compiler: "ah we've typed the 150,000 LoC - oh wait, no, there's some match that doesn't add up, let's start over"
<BitPuffin> pattern guards already ruin exhaustion checks
<companion_cube> does "yolo" belong to the match?
<BitPuffin> companion_cube: no ; discards bar and returns yolo
<BitPuffin> and that's the end of that arm
<companion_cube> so it's foo -> (bar; yolo) ?
<BitPuffin> yes
<BitPuffin> scope is terminated when a value is reached
<companion_cube> how do you write (match _ with ... | foo -> bar); yolo ?
<BitPuffin> when the hell would you ever?
<BitPuffin> and if you want to, like you just did :P
<companion_cube> I often do
<BitPuffin> why
<companion_cube> begin match foo with | None -> () | Some _ -> () end; ...
<companion_cube> well for a conditional side effect?
<BitPuffin> hmm
<BitPuffin> well
<BitPuffin> say you could make the ending markers optional?
Moataz-E has joined #ocaml
<companion_cube> what's the point? :(
<companion_cube> don't save on 3 chars
<companion_cube> use a regular, simple and predictible syntax
<companion_cube> I wish OCaml had "end" after match
<BitPuffin> well
<BitPuffin> I thought that it was a pretty simple idea :P
<ia0> companion_cube> I wish OCaml had "end" after match <= +1
<BitPuffin> that doesn't require that much getting used to
<ggole> Yeah, end after match would be an improvement.
<BitPuffin> companion_cube: I'm thinking I'm optimizing for the common case. An optional end that you could get your semicolon behind is an adjustment for a less common case
<BitPuffin> but allowing you to not having to parenthesize
<BitPuffin> sounds like the sweet spot if you ask me
<companion_cube> it's more complicated, but anyway
<BitPuffin> and it scales to all the other ones as well
<BitPuffin> with full consistency
<BitPuffin> and also modules still have an end
<BitPuffin> otherwise you'd be limited to just one value per module ;P
<ousado> you didn't write much ocaml, did you?
<BitPuffin> so say you have if ... then bla else blu
<BitPuffin> and you want to do (if ... then bla else sidefx unit); somethingother
<BitPuffin> you could do if ... then bla else sidefx unit end (possibly ;?) somethingother
<BitPuffin> ousado: I wrote some, and I'm writing the compiler in ocaml
<BitPuffin> yeah it would have to be end;
alexst has quit [Ping timeout: 240 seconds]
<BitPuffin> otherwise when you do somemod = module ... end it would count as discard the module and return what comes after if you wanna be consistent :P
<BitPuffin> yeah I think end is a nice extension to the syntax. Thanks for being a bollplank companion_cube!
<BitPuffin> companion_cube: another option is to enforce good indentation and use that to determine scope
<BitPuffin> I don't know if I want to do that
<companion_cube> that's also a possibility
<companion_cube> since it removes ambiguities
<companion_cube> the problem imho is how to indent properly anonymous functions
<BitPuffin> The problem with end is that say you are 6 levels deep and want an end at level 2 then you have to add 4 ends or something
<BitPuffin> companion_cube: I guess you can have a mix of all three lol
<BitPuffin> that would be weird
philtor_ has joined #ocaml
<BitPuffin> like indendation determines which thing you end
RenRenJuan has joined #ocaml
<adrien_oww> NOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOOO
<adrien_oww> even Montebourg has better ideas
<BitPuffin> a french politician?
<BitPuffin> no condescension at all :P
Moataz-E has quit [Quit: Leaving]
<adrien_oww> he just pulled a "we'll give money to Comcast and Disney so they can innovate in the IT"
tidren has joined #ocaml
racycle has joined #ocaml
tidren has quit [Read error: Connection reset by peer]
tidren has joined #ocaml
maattdd has quit [Ping timeout: 252 seconds]
avsm has quit [Quit: Leaving.]
tani has joined #ocaml
tidren has quit [Ping timeout: 264 seconds]
<BitPuffin> companion_cube: https://gist.github.com/BitPuffin/5554cfde85c987b09788 that's an example of what I mean
<BitPuffin> the only thing that cares about indentation is end
tane has quit [Ping timeout: 240 seconds]
<BitPuffin> meh, not sure might even be better to parenthesize at that point
<BitPuffin> or assign that part to unit
<BitPuffin> actually assigning to unit doesn't help. Tbh I'd probably even prefer indentation sensitive ; over end :P
badon has quit [Ping timeout: 240 seconds]
philtor_ has quit [Ping timeout: 240 seconds]
<BitPuffin> actually assigning it to unit does work, you just need to add "in"
alexst has joined #ocaml
<BitPuffin> yeah that's a lot better actually
ontologiae_ has quit [Ping timeout: 240 seconds]
<BitPuffin> if you refresh the gist
Hannibal_Smith has joined #ocaml
badon has joined #ocaml
alexst has quit [Ping timeout: 245 seconds]
maattdd has joined #ocaml
tianon has quit [Quit: brb, time to upgrade kernel and Docker and kexecfuntimes]
<BitPuffin> tough crowd
eikke__ has joined #ocaml
<eikke__> is there a way in lwt to mask exceptions?
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
tianon has joined #ocaml
edom has joined #ocaml
<whitequark> mask?
<edom> how do you write this haskell "type Cont r a = (a -> r) -> r" in ocaml?
<eikke__> don't inject async exceptions for a bit
matematikaadit has joined #ocaml
<eikke__> whitequark: basically, is there a way to make "Lwt_mvar.take m >>= Lwt_mvar.put t" safe (thinking about cancelation at that bind point)
jwatzman|work has joined #ocaml
BitPuffin has quit [Ping timeout: 272 seconds]
<ygrek> eikke__, you can protect from cancelation
<smondet> edom: type ('longer_name, 'also_longer_name) full_word_that_means_something = ('longer_name -> 'also_longer_name) -> 'longer_name
<ygrek> wrap it in Lwt.protected
brendan has quit [Quit: leaving]
brendan has joined #ocaml
azynheira has joined #ocaml
philtor_ has joined #ocaml
<eikke__> ygrek: right, but then what happens when a cancel occurs while in the protected section
<whitequark> it is igored
<eikke__> will the calling thread be canceled anyway?
<whitequark> ignored*
<edom> smondet: thank you very much
<ygrek> there is also no_cancel
<ygrek> one of them will behave as canceled and the other one will ignore completely silently
<ygrek> iirc
philtor has quit [Ping timeout: 245 seconds]
<eikke__> ah
<eikke__> the docs aren't very clear
<eikke__> imho
<ygrek> maybe, try it out with print_endline in on_cancel and submit a patch to improve the wording :)
brendan has quit [Client Quit]
brendan has joined #ocaml
philtor_ has quit [Ping timeout: 240 seconds]
matematikaadit has quit [Ping timeout: 240 seconds]
manizzle has quit [Ping timeout: 260 seconds]
tani is now known as tane
alexst has joined #ocaml
emias has quit [Quit: Reboot.]
srcerer has joined #ocaml
<eikke__> looks like with 'protected', the 'cancel' is injected in the thread in which 'protected' is called, but even before the 'protected' thread finished
tidren has joined #ocaml
<eikke__> with 'no_cancel', the 'cancel' is swallowed
tidren has quit [Ping timeout: 240 seconds]
matematikaadit has joined #ocaml
edom has left #ocaml ["ERC Version 5.3 (IRC client for Emacs)"]
Eyyub has joined #ocaml
maattdd has quit [Ping timeout: 240 seconds]
Kakadu has quit [Ping timeout: 246 seconds]
axiles has quit [Ping timeout: 240 seconds]
WraithM has joined #ocaml
axiles has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
dsheets has quit [Ping timeout: 240 seconds]
emias has joined #ocaml
penglingbo has quit [Ping timeout: 264 seconds]
RenRenJuan has quit [Quit: Leaving]
Somix has quit [Read error: Connection reset by peer]
bjorkintosh has joined #ocaml
Kakadu has joined #ocaml
divyanshu has joined #ocaml
divyanshu has quit [Client Quit]
Muzer has quit [Excess Flood]
ontologiae_ has joined #ocaml
ygrek has quit [Ping timeout: 255 seconds]
Muzer has joined #ocaml
badon_ has joined #ocaml
ontologiae_ has quit [Ping timeout: 272 seconds]
badon has quit [Ping timeout: 240 seconds]
badon_ is now known as badon
keen_______ has joined #ocaml
keen_______ has left #ocaml ["ERC Version 5.3 (IRC client for Emacs)"]
matematikaadit has quit [Quit: ...]
philtor_ has joined #ocaml
araujo has quit [Read error: Connection reset by peer]
araujo has joined #ocaml
AltGr has left #ocaml [#ocaml]
manizzle has joined #ocaml
philtor_ has quit [Ping timeout: 260 seconds]
hhugo has quit [Quit: Leaving.]
<bjorkintosh> is it true? that RWO is the bestest of the bestest so far?
divyanshu has joined #ocaml
<smondet> bjorkintosh: I've heard good things about: http://ocaml-book.com/ also
<bjorkintosh> i see.
<smondet> maybe it's more total beginner oriented than RWO
eikke__ has quit [Ping timeout: 240 seconds]
azynheira has left #ocaml ["Leaving"]
manizzle has quit [Ping timeout: 240 seconds]
philtor_ has joined #ocaml
<bjorkintosh> how is it that there are 1001 introductions to java, but just a handful for ocaml?
divyanshu has quit [Ping timeout: 240 seconds]
<bjorkintosh> i wonder what they're all saying in those 1001 introductions.
divyanshu has joined #ocaml
hhugo has joined #ocaml
<ggole> Because people can actually make money writing about Java
<bjorkintosh> oh it's about the money?
<bjorkintosh> i thought they just wanted everyone to try a new neat language.
<whitequark> enthusiasm is *so* not enough to write a good book...
<bjorkintosh> the dinars help then when enthusiasm flags?
<ggole> I'd guess (without any real justification) that it is about the money for one group but not the other.
divyanshu has quit [Ping timeout: 240 seconds]
divyanshu has joined #ocaml
eikke__ has joined #ocaml
BitPuffin has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
eikke__ has quit [Ping timeout: 260 seconds]
ontologiae_ has joined #ocaml
Hannibal_Smith has quit [Quit: Sto andando via]
avsm has joined #ocaml
manizzle has joined #ocaml
badon has quit [Ping timeout: 240 seconds]
ontologiae_ has quit [Ping timeout: 264 seconds]
_JokerDoom has joined #ocaml
shallow has quit [Ping timeout: 255 seconds]
badon has joined #ocaml
JokerDoom has quit [Ping timeout: 272 seconds]
hexo_ has joined #ocaml
typedlambda has quit [Ping timeout: 252 seconds]
typedlambda_ has joined #ocaml
typedlambda_ is now known as typedlambda
ontologiae_ has joined #ocaml
jludlam has joined #ocaml
malo has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
_andre has quit [Quit: leaving]
jwatzman|work has quit [Quit: jwatzman|work]
jwatzman|work has joined #ocaml
ontologiae_ has quit [Ping timeout: 240 seconds]
philtor_ has quit [Ping timeout: 240 seconds]
philtor_ has joined #ocaml
hexo_ is now known as shallow
typedlambda has quit [Ping timeout: 252 seconds]
typedlambda has joined #ocaml
eikke__ has joined #ocaml
Submarine has quit [Quit: Leaving]
ggole has quit []
claudiuc has joined #ocaml
claudiuc_ has joined #ocaml
Thooms has joined #ocaml
axiles has quit [Remote host closed the connection]
claudiuc has quit [Ping timeout: 264 seconds]
ontologiae_ has joined #ocaml
simn__ has quit [Quit: Leaving]
olauzon has quit [Quit: olauzon]
azynheira has joined #ocaml
azynheira has quit [Quit: Leaving]
<tane> This function naming "string_of_int" and similar really has something to it, giving that the variables of the corresponding types match the side of the part in the function name as opposed to int_to_string. I like that
<def`> tane: I can't tell the original reason, but one thing that this naming bring is reading in the order of composition: let x = x_of_y (y_of_z z) in …
<tane> yeah, that's exactly it, i like and use that style
<tane> my first guess (jokingly) was of course, that it stems from the french origin
<tane> isn't NATO = OTAN in france=
<tane> etc :)
<BitPuffin> tane: it would be more ideal to be able to write something like stringvar `from` intvar
<tane> well, that's less verbose, as i guess your variables rarely contain "string" or "int" :)
<tane> a `from` b, mh
<def`> BitPuffin: might be possible, but then you are no longer parametric
<BitPuffin> def`: sure you are, why not?
<BitPuffin> or whaddaya mean boi
shinnya has joined #ocaml
<def`> how would the compiler find that the variable being bound should be a string?
Kakadu has quit [Quit: Konversation terminated!]
<Drup> BitPuffin: he want dependent type-like meta programming, he's not talking about ocaml
<Drup> you could actually do that with an open Gadt type, I think
<BitPuffin> you mean that I want dependent type like programming? Or tane
<Drup> ( def` I think this one would be quite high on the unmaintanability scale)
<Drup> BitPuffin: you do
<tane> surely not me, i've not been suggesting anything :)
<BitPuffin> yeah
<BitPuffin> for sure
<BitPuffin> that's why I was confused when he said "he" :P
<Drup> hum
<Drup> I wanted to HL def`
<def`> Ok, I got it :D
S11001001 has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<Drup> BitPuffin: you could have an open Gadt type and register conversion function on pairs of Gadt constructors
<Drup> that would be horribly fabulous
avsm has quit [Quit: Leaving.]
<Drup> BitPuffin: If you start doing dependently typed programming (or, even better, using haskell extensions) you will learn that there is price to pay for typing black magic :D
<Drup> you don't pay in blood, you pay in headaches
<BitPuffin> maybe I shall try and find a balance in my language then
<BitPuffin> :D
ollehar has quit [Ping timeout: 255 seconds]
maattdd has joined #ocaml
alexst has quit [Ping timeout: 240 seconds]
tane has quit [Quit: Verlassend]
alexst has joined #ocaml
cantstanya has joined #ocaml
typedlambda has quit [*.net *.split]
badon has quit [*.net *.split]
emias has quit [*.net *.split]
bjorkintosh has quit [*.net *.split]
q66 has quit [*.net *.split]
asmanur has quit [*.net *.split]
Valdo has quit [*.net *.split]
acieroid has quit [*.net *.split]
yroeht has quit [*.net *.split]
madroach has quit [*.net *.split]
ia0 has quit [*.net *.split]
troydm has quit [*.net *.split]
ski_ has quit [*.net *.split]
osnr has quit [*.net *.split]
jerith has quit [*.net *.split]
Armael has quit [*.net *.split]
_weykent has quit [*.net *.split]
jbrown has quit [*.net *.split]
_twx_ has quit [*.net *.split]
SHODAN has quit [*.net *.split]
johnelse has quit [*.net *.split]
iZsh has quit [*.net *.split]
mk270 has quit [*.net *.split]
vpm has quit [*.net *.split]
adrien_oww has quit [*.net *.split]
marky has quit [*.net *.split]
lusory_ has quit [*.net *.split]
cthuluh has quit [*.net *.split]
hnrgrgr has quit [*.net *.split]
icicled has quit [*.net *.split]
fx has quit [*.net *.split]
alex_nx_ has quit [*.net *.split]
Derander_ has quit [*.net *.split]
hcarty has quit [*.net *.split]
parcs has quit [*.net *.split]
cdidd has quit [*.net *.split]
reynir has quit [*.net *.split]
robink has quit [*.net *.split]
sgnb has quit [*.net *.split]
mdenes2 has quit [*.net *.split]
ssbr has quit [*.net *.split]
chris2 has quit [*.net *.split]
gasche has quit [*.net *.split]
puzza007 has quit [*.net *.split]
msch has quit [*.net *.split]
jyc has quit [*.net *.split]
olasd has quit [*.net *.split]
jzelinskie has quit [*.net *.split]
__marius____ has quit [*.net *.split]
leifw has quit [*.net *.split]
SethTisue_______ has quit [*.net *.split]
jlouis has quit [*.net *.split]
steshaw has quit [*.net *.split]
nk0 has quit [*.net *.split]
zozozo has quit [*.net *.split]
rossberg_ has quit [*.net *.split]
gereedy has quit [*.net *.split]
bitbckt has quit [*.net *.split]
mal`` has quit [*.net *.split]
def` has quit [*.net *.split]
_habnabit has quit [*.net *.split]
inr has quit [*.net *.split]
hyPiRion has quit [*.net *.split]
hbar has quit [*.net *.split]
esden has quit [*.net *.split]
cthuluh has joined #ocaml
vpm has joined #ocaml
madroach has joined #ocaml
weykent has joined #ocaml
johnelse has joined #ocaml
osnr has joined #ocaml
osnr has quit [Changing host]
osnr has joined #ocaml
yroeht has joined #ocaml
johnelse has quit [Changing host]
johnelse has joined #ocaml
marky has joined #ocaml
marky has quit [Changing host]
marky has joined #ocaml
acieroid has joined #ocaml
badon has joined #ocaml
asmanur has joined #ocaml
iZsh has joined #ocaml
Armael has joined #ocaml
mk270 has joined #ocaml
adrien_oww has joined #ocaml
hnrgrgr has joined #ocaml
ski has joined #ocaml
SHODAN has joined #ocaml
johnelse is now known as Guest78461
Thooms has quit [Ping timeout: 255 seconds]
bjorkintosh has joined #ocaml
jbrown has joined #ocaml
hnrgrgr is now known as Guest39875
_twx_ has joined #ocaml
Valdo has joined #ocaml
Derander_ has joined #ocaml
icicled has joined #ocaml
alex_nx_ has joined #ocaml
fx has joined #ocaml
parcs has joined #ocaml
hcarty has joined #ocaml
cdidd has joined #ocaml
robink has joined #ocaml
reynir has joined #ocaml
jyc has joined #ocaml
ssbr has joined #ocaml
chris2 has joined #ocaml
mdenes2 has joined #ocaml
gasche has joined #ocaml
sgnb has joined #ocaml
puzza007 has joined #ocaml
msch has joined #ocaml
olasd has joined #ocaml
jzelinskie has joined #ocaml
__marius____ has joined #ocaml
leifw has joined #ocaml
SethTisue_______ has joined #ocaml
jlouis has joined #ocaml
steshaw has joined #ocaml
nk0 has joined #ocaml
rossberg_ has joined #ocaml
zozozo has joined #ocaml
bitbckt has joined #ocaml
gereedy has joined #ocaml
mal`` has joined #ocaml
_habnabit has joined #ocaml
def` has joined #ocaml
esden has joined #ocaml
hbar has joined #ocaml
inr has joined #ocaml
hyPiRion has joined #ocaml
srcerer has quit [Ping timeout: 272 seconds]
maattdd has quit [Ping timeout: 272 seconds]
bacam_ has joined #ocaml
pollux_ has joined #ocaml
pollux has quit [Read error: Connection reset by peer]
pollux_ is now known as pollux
pippijn has quit [Remote host closed the connection]
bacam has quit [Write error: Broken pipe]
lusory has joined #ocaml
contempt has quit [Ping timeout: 245 seconds]
pippijn has joined #ocaml
hhugo has quit [Quit: Leaving.]
jerith has joined #ocaml
q66 has joined #ocaml
contempt has joined #ocaml
hhugo has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
struktured has joined #ocaml
jludlam has quit [Remote host closed the connection]
darkf has joined #ocaml
philtor has joined #ocaml
ontologiae_ has quit [Ping timeout: 256 seconds]
Guest39875 is now known as hnrgrgr
ontologiae_ has joined #ocaml
ontologiae_ has quit [Ping timeout: 240 seconds]
eikke__ has quit [Ping timeout: 255 seconds]
madroach has quit [Ping timeout: 260 seconds]
madroach has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml