gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
oriba_ has joined #ocaml
oriba__ has joined #ocaml
oriba_ has quit [Read error: Operation timed out]
NihilistDandy has joined #ocaml
NihilistDandy has quit [Client Quit]
oriba__ has quit [Ping timeout: 244 seconds]
didi has joined #ocaml
didi has left #ocaml []
oriba__ has joined #ocaml
cdidd has quit [Remote host closed the connection]
oriba_ has joined #ocaml
oriba__ has quit [Ping timeout: 260 seconds]
oriba_ has quit [Ping timeout: 246 seconds]
oriba_ has joined #ocaml
oriba_ has quit [Read error: Connection reset by peer]
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 260 seconds]
ulfdoz_ is now known as ulfdoz
lihaitao has joined #ocaml
iago has quit [Quit: Leaving]
<thelema_> Lor: use the 2.0 beta of batteries - no camomile dependency
<Lor> Nah, I'm not going to risk further incompatibilities at this stage.
<_habnabit> 'futher incompatibilitie's ?
<_habnabit> assume I typed that correctly
<Lor> There's always a risk of incompatibilities showing up when you upgrade a library.
fantasticsid has joined #ocaml
lihaitao has quit [Remote host closed the connection]
lihaitao has joined #ocaml
Tobu has quit [Ping timeout: 260 seconds]
Tobu has joined #ocaml
datkin has quit [Ping timeout: 260 seconds]
jimmyrcom has quit [Ping timeout: 260 seconds]
Tobu has quit [Ping timeout: 260 seconds]
mfp has quit [Ping timeout: 246 seconds]
Tobu has joined #ocaml
mfp has joined #ocaml
mfp has quit [Ping timeout: 246 seconds]
mfp has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
pango is now known as pangoafk
<pippijn> I have many (most) functions that need a certain mutable state, should I make it global or should I pass it around to every function?
<pippijn> actually most functions don't need it directly
<pippijn> but in the end, they will call a couple of functions (3 or so) that do need it
<Drakken> pippijn that's a judgement call. It's up to you.
<_habnabit> pippijn, avoid global mutable state whenever possible
<Drakken> where "possible" means "at all convenient" :)
wagle has quit [*.net *.split]
mehitabel has quit [*.net *.split]
wagle has joined #ocaml
<_habnabit> global mutable state is a blight on your code
<flux> global mutable state is ok in my books in situations that warrant it. say, you want to provide unique ids (for the lifetime of the program).
* Drakken bans flux from the FP community!
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
<_habnabit> it's a blight on any code
<_habnabit> even in non-functional languages
ankit9 has joined #ocaml
ankit9 has quit [Read error: Connection reset by peer]
Cyanure has joined #ocaml
Tobu has quit [Ping timeout: 272 seconds]
ftrvxmtrx has joined #ocaml
Submarine has quit [Ping timeout: 252 seconds]
fantasticsid has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
ftrvxmtrx has quit [Client Quit]
ftrvxmtrx has joined #ocaml
cago has joined #ocaml
Tobu has joined #ocaml
silver has joined #ocaml
jamii has joined #ocaml
albacker has joined #ocaml
albacker has quit [Changing host]
albacker has joined #ocaml
<flux> I bet you run your code in custom-made IO monad to avoid dealing with global file descriptors?-)
djcoin has joined #ocaml
thomasga has joined #ocaml
hto has quit [Ping timeout: 248 seconds]
hto has joined #ocaml
Cyanure has quit [Remote host closed the connection]
hto has quit [Ping timeout: 248 seconds]
hto has joined #ocaml
hto has quit [Read error: Operation timed out]
jamii has quit [Ping timeout: 245 seconds]
mehitabel has joined #ocaml
ftrvxmtrx has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
Cyanure has joined #ocaml
<adrien> I'm very annoyed because in most of my programs, I have to suffer the consequences of a big fat and ugly mutable object: the user ='(
emmanuelux has joined #ocaml
<Ptival> you should write iP... apps
<Ptival> you might get non-fat non-ugly users :p
Kakadu has joined #ocaml
<adrien> my biggest complaint is that when I put a value through user(), I often don't get the same answer; I wouldn't care if it was fat and ugly if it were at least a pure function ='(
<Ptival> and he's not even a good random generator...
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
hto has joined #ocaml
<pippijn> can I add something to Pervasives?
<pippijn> or can I make every module open a module by default?
<Ptival> I don't think so
<Kakadu> pippijn: you can extend module by anything but than You should open this module manually
<Lor> I usually write a "prelude" module that opens everything I use in many places, and then open that in all my modules.
<mfp> batteries used to do it long ago with a syntax extension
<Lor> s/opens/includes
<pippijn> Lor: ok
<pippijn> sounds reasonable
<djcoin> Sorry, newbie question but what is the other way to import a module in ocaml except by using Open that kinda "pollutes" global namespace. Despite open .. in .. for local open
<djcoin> s/despite/except/
<rixed> djcoin: there is no import. open merely dispense you to prefix names with the module name. For instance, Printf.printf "hello" is equivalent to open Printf then printf "hello".
<rixed> djcoin: There are also local opens : Printf.(print "hello" ; print "world")
<rixed> djcoin: The equivalent of, say "from Printf import printf" would be merely to write: "let printf = Printf.printf".
<djcoin> Arg, all modules are directly accessible given compilation was successfull
<djcoin> rixed: thanks a lot :)
<rixed> djcoin: exactly. there is no "search for that module" in runtime.
<djcoin> No wonder I could not find info on that. :x Sorry
<rixed> djcoin: you should have ; OCaml lacks good tutorials.
<djcoin> I know I already, of course, used this. But I forgot, seeing too much "open" on file's header made me forget you will have modules accessible even without mentionning it
<companion_cube> what you can do is rename modules so that they are shorter, like Module M = Map(some module here)
<companion_cube> so that names are still qualified, but just with a short name
<djcoin> Yeah, I find it disturbing/not so pretty, to import all in global namespaecs
jamii has joined #ocaml
avsm has quit [Quit: Leaving.]
<mfp> if I have a module type S = sig type t1 type t2 ... end how can I create a functor that operates of modules S that have t1 = t2 ?
<mfp> module F(C1 : S with type t1 = t2) fails (unknown type constructor t2)
<mfp> maybe a detour via 1st class modules
<mrvn> Don't you have to define a module sig S2?
<mfp> module type S2 = sig type t1 type t2 = t1 end or so?
* mfp tries
<mrvn> something like module type S2 = sig type t include S with type t1=t type t2=t end
<mrvn> so you don't have to duplicate all of S
<mfp> right, I had tried include S with type t2 = t1 (without the extra type t) and it didn't work, but yours does
<mfp> thanks
<mrvn> should work with t1 too if you declare if before the include
<mfp> ah, include S with type t1 := t1
<mfp> great
<mfp> the solution using 1st-class modules was very verbose without 3.13/4.00's simplified (un)packing
thomasga has quit [Quit: Leaving.]
emias has quit [Quit: Reboot.]
datkin has joined #ocaml
<pippijn>
cdidd has joined #ocaml
<mrvn> ??
avsm has joined #ocaml
datkin has quit [Remote host closed the connection]
datkin has joined #ocaml
Oejet has joined #ocaml
testcocoon has quit [Quit: Coyote finally caught me]
testcocoon has joined #ocaml
skchrko has joined #ocaml
err404 has joined #ocaml
* adrien hates Qt
<adrien> I was really wondering if it were not C++ that I hated; but I find Qt, and its style (which is because of C++), horrible
* adrien has been trying to display a transparent png for hours if not days over the course of the past year
<mrvn> do the qt bindings map things to objects?
<mrvn> I had similar problems with gtk. all the gui toolkits seem to be horrible for beginners.
<adrien> probably unless beginners copy-paste =/ =/
<adrien> as for the qt bindings, lablqt does iirc, and the other one, I guess it does too
<adrien> currently, I'm interested in the EFL (englightenment foundation libraries) which do _not_ use inheritance
<adrien> (that's one reason; among the others: I'm not under the impression they're trying to do as much crap as possible, and they're fast and light)
thomasga has joined #ocaml
<adrien> ah, finally, I found out how to get the image transparent in Qt! using the image-related functions was foolish, I had to use a QLabel, which was meant for text at first!
<Ptival> huh finally rounded down that nasty bug
<adrien> of course, that's obvious: functions for images are hihgly overrated when you can make spaghettio
<adrien> s/o$//
<Ptival> that was a Heisenbug for me :3
<adrien> Ptival: yes, gdb disables ASLR
<mrvn> let off' = max_int + 1 in
<mrvn> should be undefined
<adrien> and overflows =/
<adrien> it's probably what I always fear in my code
<Ptival> mrvn: well, replace that with a negative value, whatever
<Ptival> the problem is that the function is not safe with regards to negative values
<mrvn> try it with off = -1
<mrvn> or min_int
<Ptival> and it's not "take that exception" not safe, but rather "might segfault, might fail silently" not safe, which I think is worse
<mrvn> max_int + 1 ends up being min_int but I don't think ocaml garanties that that is so.
<Ptival> I'd expect it to raise an Invalid_argument
<Ptival> mrvn: sure
<adrien> well, we'd need safe operators for that
<adrien> Big_int actually
<mrvn> anyway, what is missing in the code is if (off' < 0)
<mrvn> and for overflows (off' < off' + len) but nobody checks that
<Ptival> it should probably be checked since we're going to call C code after that...
<Ptival> an Argument_invalid exception with a stack trace is _way_ more friendly than SIGSEGV
<mrvn> ocamls String library uses: if ofs < 0 || len < 0 || ofs > length s - len
<mrvn> then invalid_arg "String.sub"
<mrvn> Since length s and ken are both positive that won't undeflow but may be negative.
<mrvn> if off' < 0 || len' < 0 || off' > len - len' then invalid_arg "subbitstring";
<mrvn> would be the equivalent for bitstrings, right?
<Ptival> yes
<mrvn> And we know off + len does not overflow so off + off' can't overflow after this test.
<mrvn> Should cover all the cases.
<mrvn> Ptival: you should report that with a patch to bitstring.
<Ptival> mrvn: the link I sent is a ticket on bitstring's bugtracker
<mrvn> Ptival: bitstring uses google as BTS?
<Ptival> yes
Tobu has quit [Ping timeout: 272 seconds]
jamii has quit [Ping timeout: 240 seconds]
<mrvn> Ptival: they don't allow anonymous comments so you have to add the fix
<Ptival> huh
jimmyrcom has joined #ocaml
thomasga has quit [Ping timeout: 246 seconds]
Tobu has joined #ocaml
<mrvn> wow, 4.0 is 13% faster on the n-body problem benchmark (lots of float computations). What was improved there?
oriba has joined #ocaml
Tobu has quit [Ping timeout: 272 seconds]
skchrko has quit [Quit: ChatZilla 0.9.88.1 [Firefox 11.0/20120314111819]]
albacker has quit [Ping timeout: 248 seconds]
<Ptival> how to test that a range of bytes of a string are null?
<flux> with a recursive loop I'm afraid
<mrvn> let test_zero s off len = (String.sub s off len) = (String.make len '\000')
<adrien> or for + exception
<adrien> or while
<Ptival> mrvn: seems reasonable
<Ptival> (for small values of len :p)
<adrien> as for the recursive loop, if you make it tail-rec, it will be fast
Tobu has joined #ocaml
<Ptival> I don't care about speed
<Ptival> I want to test 7 bytes
<adrien> unroll :-)
<Ptival> yeah that's what I have...
<adrien> it should fit on one line
<Ptival> (Char.code str.[byte + 0] = 0x00) && (Char.code str.[byte + 1] = 0x00) && (Char.code str.[byte + 2] = 0x00) && ...
<mrvn> exception Not_null try for i = off to off + len - 1 do if s.[i] <> '\000' then raise Not_null; done; true with Not_null -> false
<adrien> let f i = s.[byte+i] = '\000' in
<adrien> f 0 && f 1 && f 2 && ...
<Ptival> List.for_all f [0; 1; 2; 3; 4; 5; 6; 7] ? :)
<mrvn> (Char.code str.[byte + 0]) + (Char.code str.[byte + 1]) + ... + (Char.code str.[byte + 6]) = 0
<adrien> too
<adrien> mrvn's is nice too; I'd use 3.12 ability to put Char.() around the whole block
<mrvn> adrien: huh?
<Ptival> actually I'm testing 8 bytes
<Ptival> so this might overflow :D
<adrien> Char.(code str.[byte+0] + code str.[byte+1] + ... )
<Ptival> oh no it can't
<Ptival> oh it can
<mrvn> Ptival: extUnix.EndianHost.get_int64 str off = Int64.zero
<Ptival> :3
<mrvn> adrien: That would overflow the char on the addition
<Ptival> crazy boys
skchrko has joined #ocaml
<adrien> Ptival: you can also get the code and put everything in an int64 using shifts and check the int64 is still = 0
<adrien> mrvn: that's the code you wrote
<adrien> but with the specifier for the Char module put outside
<mrvn> adrien: no. I convert each char to int first and then add
<Ptival> oh I can just Int64.of_string (String.substring ...) = 0l
<kaustuv> Int64.zero? Is 0L too few keystrokes?
<adrien> Ptival: it parses the string
<mrvn> Ptival: does that convert "0" -> Int64.zero?
<mrvn> kaustuv: hehe.
<adrien> mrvn: all I meant was that instead of writing (M.f x + M.f y + ...), I'd write M.(f x + f y + ...)
<mrvn> adrien: oh, sorry, misread that.
<mrvn> String needs a not_contains_from_len : string off len char -> bool
<adrien> np :-)
<Ptival> # Int64.of_string (String.make 8 '\000');;
<Ptival> Exception: Failure "int_of_string".
<adrien> Ptival: int_of_string reads "12345"
<mrvn> # Int64.of_string "123";;
<mrvn> - : int64 = 123L
<adrien> not "123ber"
<Ptival> oh...
<adrien> it _parses_
<Ptival> right :D
<Ptival> it's been too long since I've used these chars as ASCII :D
<Ptival> I'm all into bits
<mrvn> There is no Int64.as_string
<Ptival> k
<adrien> Ptival: where is your string from?
<Ptival> a binary fiel
<adrien> because depending on the alignment, a bigarray might work
<mrvn> Ptival: I would just compare the substring against "\000\000\000\000\000\000\000\000" or use the upcoming extUnix.EndianHost.get_int64
<Ptival> substring it'll be
<mrvn> adrien: you can't convert a string to bigarray
<adrien> mrvn: I meant that Ptival could use a bigarray from the beginning
<mrvn> or bitstring
<Ptival> I use a bitstring
<Ptival> I'm just looking inside :p
<mrvn> well, doesn't bitstring already have a function to pull an int64 from the bitstring?
* mrvn misses Int31, UInt31, Uint, Uint32, Uint64 modules.
<mrvn> UNativeInt too
<Ptival> yeah but at that time I don't want to package up the bitstring, anyway
<Ptival> yes, I could _really_ have used UInt32 and UInt64 =___=
<Ptival> I have a bunch of safe_ unsafe_ convertion functions
<mrvn> (untested)
<kaustuv> I think you mean Nat31, Nat32, Nat64, etc.
Submarine has quit [Quit: Leaving]
<mrvn> kaustuv: is natint unsigned?
<kaustuv> I'm just objecting to the C-like terminology "unsigned integer"
<mrvn> well, int is signed and "nat" is to easy to confuse with native
<kaustuv> Yeah, well, "native" was a mistake too.
<mrvn> My int31 bug+patch for bigarray is still not closed. :(
lihaitao has quit [Ping timeout: 245 seconds]
smondet has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
emmanuelux has joined #ocaml
emias has joined #ocaml
lihaitao has joined #ocaml
datkin has quit [Ping timeout: 240 seconds]
Kakadu has quit [Quit: Page closed]
Cyanure has quit [Remote host closed the connection]
thomasga has joined #ocaml
lihaitao has quit [Quit: Ex-Chat]
lht_ has joined #ocaml
lht_ has quit [Client Quit]
mort___ has joined #ocaml
<Ptival> so there's no List.empty predicate? :D
<Ptival> guess that'll be a match then...
<mrvn> Ptival: [] is a literal
<mrvn> if x = [] then ...
<Ptival> right
albacker has joined #ocaml
Kakadu has joined #ocaml
<adrien> Ptival: (=) []
<adrien> # (=) [];;
<adrien> - : '_a list -> bool = <fun>
<companion_cube> adrien: it's not polymorphic, is it?
<adrien> it's polymorphic
<companion_cube> fun x -> x = [] may be
<adrien> once :P
<companion_cube> yeah, so not really polymorphic
<adrien> if you have 'a list list
<adrien> and then you List.filter ((=) []) your_list
<adrien> then it's definitely enough
<adrien> (and that's all my needs)
<companion_cube> ah, sure
<mrvn> it isn't polymorphic because of the value restriction. The lifted version (fun x -> x = []) is.
<mrvn> iirc
<companion_cube> that's what I was thinking
<mrvn> Ran: 31 tests in: 0.02 seconds.
<mrvn> OK.Segmentation fault
<mrvn> :((
thomasga has quit [Quit: Leaving.]
<hcarty> mrvn: valgrind/gdb? And/or lots of printf calls.
<companion_cube> assert ftw
cago has quit [Quit: Leaving.]
<mrvn> ==4235== by 0x44B1C1: sweep_slice (in /home/mrvn/src/debian/extunix/extunix/_build/test/testba.native)
<mrvn> ==4235== by 0x44B63C: caml_finish_major_cycle (in /home/mrvn/src/debian/extunix/extunix/_build/test/testba.native)
<mrvn> The GC segfaults. So I guess I'm corrupting the memory somewhere
<companion_cube> must be cosmic rays otherwise
err404 has quit [Remote host closed the connection]
mort___ has quit [Quit: Leaving.]
mort___ has joined #ocaml
mort___ has quit [Ping timeout: 244 seconds]
<mrvn> args, I used the C stub for string instead of the one for bigarray in one of the extern functions.
zorun has quit [Read error: Connection reset by peer]
zorun has joined #ocaml
Tobu has quit [Remote host closed the connection]
Tobu has joined #ocaml
Oejet has left #ocaml []
avsm has quit [Quit: Leaving.]
djcoin has quit [Quit: WeeChat 0.3.2]
hnrgrgr has quit [Ping timeout: 244 seconds]
oriba has quit [Quit: oriba]
ftrvxmtrx has quit [Quit: Leaving]
oriba has joined #ocaml
<mrvn> I wonder if I shuld add ExtUnix.read that will invoke read multiple times until the requested amount has been read.
albacker has quit [Ping timeout: 272 seconds]
<Drakken> Is there a way to tell ocamlbuild to build an archive? And if not, what's the easiest/best/"right" way to do it?
<Drakken> Right now I have ocamlbuilde making .cmo files and then ocamlc -a makes the archive.
<Drakken> But then ocambuild keeps complaining about all the links to the .cmo files in the project directory.
<Drakken> (so I have to keep running the sanitize script)
<adrien> ocamlbuild foo.cma
<adrien> then in _build
<hcarty> gildor: Do you have a rough idea of when oasis-db's package upload will support the 0.3 _oasis format?
<hcarty> I tried uploading cmdliner 0.9.1 but oasis-db complains that the _oasis format isn't supported
snearch has joined #ocaml
err404 has joined #ocaml
<mrvn> In the extunix git why are generate files like _tags included but *.clib not?
<mrvn> gildor: ^^^
Xizor has joined #ocaml
<d3z> _tags is only sort-of generated. Parts outside of the oasis block are preserved.
ftrvxmtrx has joined #ocaml
<mrvn> ahh, I missed that there is a custom block at the end.
Juzor has joined #ocaml
<d3z> Whether it's a good idea to do that is a different issue. I personally think the extra _tags (and extra myocamlbuild.ml stuff) should come from elsewhere.
<d3z> Files should be either source or generated, not a mixture of both.
Juzor has quit [Ping timeout: 264 seconds]
albacker has joined #ocaml
<Drakken> oh, you use a .mllib file. Thank you, Google. too bad I couldn't figure that out from an obscure appendix entry at the end of the manual.
err404 has quit [Remote host closed the connection]
agarwal1975 has joined #ocaml
pangoafk is now known as pango
<mrvn> Yeah, there should be _tags_oasis and _tags_custom or something.
<mrvn> hmm, already 2100 and I haven't even started writing the ntp client I wanted to write today.
Juzor has joined #ocaml
albacker has quit [Read error: No route to host]
lorill has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
albacker has joined #ocaml
albacker has quit [Changing host]
albacker has joined #ocaml
Zedrikov has joined #ocaml
zorun has quit [Read error: Connection reset by peer]
zorun has joined #ocaml
<mrvn> If a read/write reads/writes x bytes and then gets an error should it: a) return the error ignoring the partial read/write or b) return the number of bytes read/written ignoring the error?
Tobu has quit [Remote host closed the connection]
Tobu has joined #ocaml
ocaml_man has joined #ocaml
thonz has joined #ocaml
thonz has quit [Client Quit]
<ocaml_man> Bonsoir
<Zedrikov> bonsoir
<smondet> Hi, has anyone ever parsed SSL CRL files in OCaml? (Certificate Revocation Lists)
<smondet> or managed to verify client certificates in some way?
<adrien> there's maybe something in Mirage
<adrien> (also, I'll be interested in what you find)
_andre has left #ocaml []
fraggle_ has quit [Read error: Connection reset by peer]
<lorill> is this possible to create a map module with keys and values restricted to a certain type ?
<mrvn> sure, just do
<lorill> I mean, I know module Mine = Map.Make(String) to restrict the key, but how to restrict the value too ?
fraggle_ has joined #ocaml
<mrvn> lorill: by specifying a signature that specifies the value
<Zedrikov> For instance you replace the "type 'a t" of the Map signature with "type t", "get : 'a t -> string -> 'a" with "get : t -> string -> <your type>" and so on
<mrvn> get : <your type> t -> string -> <your type>
<mrvn> or you need to type t = <your type> t
<lorill> so i would need to rewrite the while signature ?
<mrvn> yes
<lorill> i can't simply constraint 'a to a type then. That's probably why i didn't found how to do it :)
<mrvn> something along the lines of include MyMap with type 'a = int?
<lorill> that's what i'd like to do, yes
Submarine has quit [Quit: Leaving]
ocaml_man has quit [Ping timeout: 245 seconds]
Kakadu has quit [Quit: Konversation terminated!]
err404 has joined #ocaml
<lorill> but this syntax doesn't seem to exist. Am I missing something ?
<mrvn> Can't find anything better than: http://paste.debian.net/161499/
<lorill> yeah, so still writing the whole signature. Thanks.
<mrvn> I tried this: module type M = sig include Map.S with type 'a t = int Map.Make(String).t end;;
<mrvn> module M = (Map.Make(String) : M);;
<mrvn> Scratch that: module Mine : sig include Map.S with type key = String.t val empty : int t end = struct include Map.Make(String) end
<mrvn> # Mine.add "foo" "bar" Mine.empty;;
<mrvn> Error: This expression has type int Mine.t but an expression was expected of type string Mine.t
<mrvn> # Mine.add "foo" 1 Mine.empty;;
<mrvn> - : int Mine.t = <abstr>
<mrvn> You can only create Maps by starting with empty so it is enough to limit empty.
albacker has quit [Quit: Leaving]
<mrvn> and the map functions.
<mrvn> # Mine.map float_of_int (Mine.add "foo" 1 Mine.empty);;
<mrvn> - : float Mine.t = <abstr>
<lorill> nice
<mrvn> much shorter.
<lorill> i still need to declare it as a "int Mine.t" instead of only "Mine.t"
<mrvn> The downside is that you get not so good error messages.
<mrvn> By the way: What does thet + in type +'a t mean?
skchrko has quit [Quit: ChatZilla 0.9.88.1 [Firefox 11.0/20120314111819]]
err404 has quit [Ping timeout: 260 seconds]
<thizanne> basically, it means that a function which accepts an 'a t will accept a int t
<thizanne> if you had written -'a t, a function which accepts a int t would accept a 'a t
<mrvn> thizanne: In this case it rather says that empty remains polymorphic.
snearch has quit [Quit: Verlassend]
<lorill> I have to leave, but thanks again for the help!
lorill has quit [Quit: Ex-Chat]
maufred has quit [Ping timeout: 245 seconds]
maufred has joined #ocaml
datkin has joined #ocaml
datkin has quit [Remote host closed the connection]
Tobu has quit [Ping timeout: 272 seconds]
datkin has joined #ocaml
Tobu has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
NaCl has quit [Remote host closed the connection]
NaCl has joined #ocaml
NaCl has quit [Changing host]
NaCl has joined #ocaml
NaCl has quit [Remote host closed the connection]
NaCl has joined #ocaml
NaCl has quit [Changing host]
NaCl has joined #ocaml
NaCl has quit [Client Quit]
NaCl has joined #ocaml
smondet has quit [Remote host closed the connection]
rmmh has joined #ocaml
<rmmh> why would "open Foo" work, while "include Foo" complains about a reference to an undefined global?
Juzor has quit [Remote host closed the connection]
Juzor has joined #ocaml
Tobu has quit [Ping timeout: 260 seconds]
<Zedrikov> open Foo does not add anything to a module
<Zedrikov> it just makes the methods of a module visible without having to use the dot notation
<Zedrikov> include does a copy paste to your current module
<Zedrikov> so the contents of the include must be defined
<Zedrikov> For instance, you can rightfully open a module type (sig) inside of a module implementation (struct)
<Zedrikov> but you cannot include it, as it won't define anything.
<Zedrikov> So if you have a functor for instance, it is a module A which depends on a module B, you can write "open B" inside of A to avoid typing "B.stuff" everywhere
<Zedrikov> But you cannot "include B" inside of A, as B is unknown at compile time.
emmanuelux has quit [Remote host closed the connection]
Zedrikov has quit [Quit: Bye all, see you next time!]
lorilan has quit [Quit: Quitte]