flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab OCaml 3.10.2 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
ofaurax has quit ["Leaving"]
seafood has quit []
seafood has joined #ocaml
Ched- has joined #ocaml
bohanlon has quit ["leaving"]
bohanlon has joined #ocaml
Ched has quit [Read error: 110 (Connection timed out)]
seafood has quit []
seafood has joined #ocaml
seafood_ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
tvn1981a has joined #ocaml
<tvn1981a> is there a generic value like "NULL" in ocaml ? I have type my_recrd = { member_name : my_type ; } and get_new_record = {member_name = What_to_put_here? ; }
<tvn1981a> get_new_record ():my_rcrd = {member_name = What_to_put_here? ; }
<thelema> tvn1981a: the ocaml way to do that involves using an "option type".
<thelema> if you want to have "nothing" in member_name.
<thelema> the better solution constructs the record with its needed data:
<thelema> let get_new_record name = { member_name = name }
<thelema> does that make sense?
<tvn1981a> because when I call get_new_record , I don't know the value for member_name yet
<tvn1981a> ok so I just read about option in ocaml --- I would define member_name = None ?
<thelema> can you restructure your program so that you only make the record once you have the name?
<thelema> type my_record = { mutable member_name : my_type option; }
<thelema> let get_new_record () = { member_name = Null }
<thelema> let r = get_new_record () in r.member_name := Some "Bill"
<tvn1981a> by Null you mean None
<tvn1981a> ?
<thelema> yes. thinko.
<tvn1981a> thelema: I could do that but I have other members such as data etc that is not available when I create that record.
<thelema> then the [my_type option] method seems most appropriate.
<tvn1981a> yes -- that looks good - thanks
<thelema> using [mutable] makes the record field updateable - usually good with option types
<tvn1981a> yeh I have that
<tvn1981a> when I pass a record, I just pass a reference of it correct ?
seafood_ has quit []
<tvn1981a> pass a recrd to a function
<thelema> yes.
<thelema> anything that doesn't fit in the machine word size gets passed by reference
tomh_-_ has quit ["http://www.mibbit.com ajax IRC Client"]
<tvn1981a> what if my record has just a member of type Bool ? it's smaller than a word size
<thelema> the ocaml compiler does what you tell it to - if you want a record that's just a bool, it'll make one.
<thelema> (that said, even bools take up one word, just like in C)
<thelema> well, C doesn't have bool, but...
<mbishop> that's why you use short for "boolean like" variables in C :P
<thelema> :P
<tvn1981a> ok - another question, a member in my record points to another record, as in type my_record = {mutable my_friend : my_record;} --- I just did that and it runs fine
<thelema> no problems.
<tvn1981a> but does this really mean 'pointing' ?
<thelema> yes, the "reference" to the other record will get stored in that field.
<tvn1981a> I want something like a pointer points to an address of an existing record
<tvn1981a> oh ok
keram has quit [Connection timed out]
<tvn1981a> no need to use the keyword 'ref' ?
<thelema> it won't store a copy of the data of that record.
<tvn1981a> that's great
<thelema> type 'a ref = { mutable contents: 'a }
<tvn1981a> what is that /
<tvn1981a> ?
<tvn1981a> type 'a ref = { mutable contents: 'a }
<thelema> that's the definition of the type "ref"
<thelema> the function "ref" just constructs a value of that type (i.e. ref x = { contents = x } )
seafood has joined #ocaml
<tvn1981a> so what's the definition of type my_record = {mutable my_friend : my_record;} and type my_record = {mutable my_friend : my_record ref;}
<tvn1981a> what's the difference
<thelema> one extra level of indirection
<thelema> the second container points to a record that points to the friend record
<tvn1981a> so something like this is also extra level of indirection -> let b = ref 10 in let c = ref !b ?
<tvn1981a> I could just use let c = b
<thelema> these differ in one important way - the first creates a new pointer to the 10, while the second has two names for the same pointer to the 10.
<tvn1981a> right
<tvn1981a> that's interesting --- so let c = ref !b , when changing the value of b , c still equals 10
<tvn1981a> ah ok - got it
<thelema> let b = ref 10 :: b -> 10
<tvn1981a> in let c = ref !b , that's just let c = 10
<thelema> ! b :: 10
<tvn1981a> in let c = ref !b , that's just let c = ref 10
<thelema> yes
<tvn1981a> so let c = ref d where d is a record , that's extra level of indirection ?
<thelema> yes, but it's sometimes useful, if you want to be able to change what record c refers to -- without that level of indirection, c's "value" can't change.
<tvn1981a> ic --
<tvn1981a> great -- that's enough for the day -- thank so much thelema
<thelema> de nada
TypedLambda has quit [Read error: 110 (Connection timed out)]
tvn1981a has quit ["ChatZilla 0.9.83 [Firefox 3.0.1/2008070206]"]
postalchris has joined #ocaml
postalchris has left #ocaml []
ozy` has joined #ocaml
Palace_Chan has joined #ocaml
Associat0r has quit []
jeddhaberstro has quit []
bluestorm has joined #ocaml
tvn1981a has joined #ocaml
<tvn1981a> I have something like let a = ref None in a:= Some 3
<tvn1981a> now how do I access a ? like printf ("%d\n" a) won't work
<bluestorm> !a
<bluestorm> match !a with Some foo -> ....
<tvn1981a> ah have to use pattern matching
Palace_Chan has quit [Client Quit]
<bluestorm> tvn1981a: well you could create a function to encapsulate the pattern
<bluestorm> the problem is : what do you do if it is None ?
seafood has quit []
<bluestorm> you could have say
<bluestorm> let get a = match !a with Some x -> x | None -> invalid_arg "get"
<bluestorm> but you'll probably want to have a custom behavior instead of the exception (that you could still add with an try..with wrapper of course), and that would make the matching practical
electronx has joined #ocaml
Jedai has quit [Read error: 110 (Connection timed out)]
Jedai has joined #ocaml
BMoncef has joined #ocaml
seafood has joined #ocaml
ofaurax has joined #ocaml
ofaurax has quit ["Leaving"]
<tvn1981a> bluestorm: I know the type giving to variable 'a' , for example T(a) = my_type , just that in the beginning , a has no value yet, I just want to intilization it to something ...
<bluestorm> well if that makes sense you could also choose a default value of the right type
<bluestorm> (access would then be a bit easier)
<bluestorm> tvn1981a: you could also use http://ocaml-extlib.googlecode.com/svn/doc/apiref/Global.html
<tvn1981a> if it were something like string .. I can intialize it to "" -- but I don't know how to create an empty value of type my_type
<bluestorm> ok
<bluestorm> in that case 'a option is a sensible choice
<tvn1981a> oh this global thing seems good
<tvn1981a> thanks bluestorm --- I think I should use this extlib
tvn1981a has quit ["ChatZilla 0.9.83 [Firefox 3.0.1/2008070206]"]
electronx has quit []
Jedai has quit [Read error: 60 (Operation timed out)]
Jedai has joined #ocaml
bluestorm has quit [Remote closed the connection]
rwmjones_ has joined #ocaml
itewsh has joined #ocaml
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
BMoncef has quit ["Bye"]
Myoma has quit [Read error: 113 (No route to host)]
Myoma has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
Yoric[DT] has joined #ocaml
itewsh has quit ["KTHXBYE"]
longh has joined #ocaml
seafood has quit []
jlouis has quit ["Leaving"]
filp has joined #ocaml
filp has quit [Client Quit]
guillem has joined #ocaml
filp has joined #ocaml
filp has quit [Client Quit]
guillem has quit [Remote closed the connection]
hnr has quit ["Leaving"]
rog1 has quit [Read error: 110 (Connection timed out)]
mishok13 has joined #ocaml
Jedai has quit [Success]
Jedai has joined #ocaml
mishok13 has quit [Read error: 110 (Connection timed out)]
rog1 has joined #ocaml
<thelema> Yoric[DT]: ping
pango_ has joined #ocaml
hkBst has joined #ocaml
<Yoric[DT]> thelema: pong
<thelema> have you successfully linked anything outside the batteries tree with batteries?
<Yoric[DT]> Only tried the tests.
<Yoric[DT]> Which are in trunk/tests.
<Yoric[DT]> I'm not sure they're up-to-date anymore, though.
<Yoric[DT]> Note: have you read the compilation instructions?
<Yoric[DT]> Other note: I won't be able to stay long today.
<thelema> yes, I've followed those instructions, and I get problems linking
<thelema> Error: Error while linking /home/thelema/bin/ocamlcvs//lib/ocaml/site-lib/batteries/batteries.cma(Batlib_Extlib_Dllist):
<thelema> Reference to undefined global `Extlib'
Smerdyakov has quit ["BRB"]
<thelema> maybe you can answer: which copy of extlib should get installed: the one in trunk/batteriex/src/additions/extlib or trunk/extlib?
<Yoric[DT]> trunk/batteriex/src/additions/extlib
<Yoric[DT]> trunk/extlib is on its way out.
Smerdyakov has joined #ocaml
<thelema> at the moment, it seems that one gets compiled, but not installed.
<Yoric[DT]> No, it's not installed.
<Yoric[DT]> I'm not attempting to install it either.
<Yoric[DT]> It gets compiled into batteries.cma .
<thelema> should it get installed?
<thelema> really?
<thelema> then why the missing global?
<thelema> is it okay to remove the external dependency on extlib (in the META file)?
<thelema> dah! it works now...
Linktim has joined #ocaml
<Yoric[DT]> Oops.
<Yoric[DT]> Need to fix the META...
pango_ has quit [Remote closed the connection]
jeremiah has joined #ocaml
<thelema> very nice. I just wish I had a better idea what was going on with the extlib problem... maybe batteries was depending on the external extlib instead of its internal copy...
Jedai has quit [Read error: 110 (Connection timed out)]
<thelema> Thanks for the help. I'll keep forging ahead.
Jedai has joined #ocaml
pango_ has joined #ocaml
Associat0r has joined #ocaml
<Yoric[DT]> thelema: yes, that was it.
<thelema> if I wanted to extend Batlib.Data.Text.String, I'd edit batteries/src/additions/extlib/extString.* ??
Linktim has quit [Read error: 110 (Connection timed out)]
<thelema> also, there's at least one bug in your ocamldoc - in my output for Data.Text.String, the section titles divide val/description chunks. i.e. "Constructors" sits between "val make: int->char->string" and "String.make n c returns a fresh string..."
threeve has joined #ocaml
Myoma has quit [Read error: 113 (No route to host)]
threeve_ has joined #ocaml
threeve_ has quit [Remote closed the connection]
Myoma has joined #ocaml
itewsh has joined #ocaml
<thelema> grr, I'm back to the 'undefined global extlib' problem...
<Smerdyakov> File systems are crap.
<flux> the implementations or the concept?
<thelema> Smerdyakov: really? I don't mind mine too much.
<Smerdyakov> flux, the concept.
<thelema> Smerdyakov: the whole tree thing?
<flux> smerdyakov, it's the wrong idea or it's not taken far enough?
<Smerdyakov> The problem is fitting everything into the interface of nested trees ending in character arrays.
<flux> smerdyakov, so, what would be better? tag-based systems?
<Smerdyakov> Persistent heaps
<thelema> so instead of a directory of files made of characters, you'd have... a heap?
<Smerdyakov> Yeah.
<thelema> and what would you do with the heap?
<Smerdyakov> On the phone. Will return later.
<Yoric[DT]> thelema: to extend Data.Text.String, yes, modify extString.*
<Yoric[DT]> *and* batlib_Extlib_String
<Yoric[DT]> Fixing ocamldoc bug.
<Yoric[DT]> Thanks.
<thelema> hmm... mind if I repurpose String.of_list. Right now it only does char list -> string
<thelema> I'd like to do ('a -> string) -> 'a list -> string
<thelema> (or we can come up with a better name for the general one)
<kig> how about List.fold_left
<thelema> let of_list_f string_of l =
<thelema> "["^concat "; " (List.map string_of l)^"]"
<Yoric[DT]> That's more a String.unfold, or something such.
<kig> List.fold_left (fun s i -> s ^ (f i)) l
<thelema> i.e. of_list_f string_of_int [1; 2; 3] = "[1; 2; 3]"
<kig> err, "" l
<Yoric[DT]> There's a list printer in module Printf.
jeddhaberstro has joined #ocaml
<thelema> kig: very inefficient - look at all that string allocatin
<thelema> Yoric[DT]: really?
<Yoric[DT]> Well, in my version of module Printf :)
<Yoric[DT]> Printf.make_list_printer .
<Yoric[DT]> Should avoid any concatenation.
adema has quit ["Quitte"]
<thelema> ah, that's why I didn't know of it.
* thelema waits for his documentation to rebuild
<thelema> Yoric[DT]: in batteries?
<Yoric[DT]> Yes.
<thelema> where's the source?
<Yoric[DT]> SVN version, of course.
<thelema> what file?
marmotine has joined #ocaml
<Yoric[DT]> additions/extlib/IO.ml
<thelema> Yoric[DT]: I think your version involves as many allocations as kig's
tomh_-_ has joined #ocaml
<thelema> only less copying
<thelema> n/m, same amount of copying
<kig> the other way is String.concat "" (List.map f l)
<kig> which uses 2n memory
<thelema> kig: that's almost exactly what I'm doing, except I put "[" and "]" at ends.
<kig> but less work, sure
<thelema> and use "; " as separator
<kig> you want a list pretty-printer?
<thelema> 2N memory vs. 1/2 N^2 memory for the GC to collect
<kig> i thought it was more about some sort of concatMap for strings, gn
<thelema> The only way I can think to do it better than String.concat would involve a second helper function that only returns length of needed string.
<thelema> (to know how big a string to allocate), and then just blit the strings directly into place.
<thelema> but most of the time, calculating length of output string isn't much easier than just making the string, so might as well do that.
<Yoric[DT]> thelema: what my version involves depends on the underlying stream.
<kig> List.pretty_print : ('a -> string) -> 'a list -> string
<thelema> true - for making a string output, you'll end up doing lots of allocation
<Yoric[DT]> Mmmhhh....
<Yoric[DT]> Probably not, actually.
<Yoric[DT]> It's going to use a Buffer.
<Yoric[DT]> Yes, just checked, it uses a Buffer.
<thelema> my apologies - that's not as bad as kig's
<Yoric[DT]> Now, the initial buffer size is 0, which is probably dumb.
<thelema> heh. yup
* Yoric[DT] will fix that.
<kig> oh nm my stupidity, the fold with ^ uses ~2n for the last ^
itewsh has quit [Read error: 110 (Connection timed out)]
itewsh has joined #ocaml
<Yoric[DT]> thelema: any suggestion about a reasonable default value?
* Yoric[DT] would intuitively use 32, but without any good argument.
<pango_> 42
<thelema> most two-digit numbers should work. My initial answer would be 10
<thelema> the ocaml manual says "In doubt, take n = 16"
<Yoric[DT]> Fair enough.
<Yoric[DT]> Fixed a few other occurrences of Buffer.create along the way.
<thelema> can we get rid of the mli duplication?
<Yoric[DT]> I'm not sure.
<Yoric[DT]> Some of the .mli are identical, others are not.
<thelema> isn't it a remenant of the externality of extlib
<Yoric[DT]> Most definitely.
<Yoric[DT]> So for extlib (and only for extlib), we could probably get rid of them.
<thelema> ok.
<Yoric[DT]> That would mean completely making extlib + baselib the core of Batteries.
<thelema> for others, we won't have the source in our tree, so we won't be maintaining two .mli files, only one.
<Yoric[DT]> That's not shocking.
<Yoric[DT]> Exactly.
<thelema> I can deal with that.
<Yoric[DT]> Importing extlib?
<Yoric[DT]> I mean, getting rid of the duplication?
<Yoric[DT]> That would be nice.
<thelema> yes.
<thelema> I'll send you a patch.
<mbishop> if you guys are talking about Batteries Included, I want to suggest again that more datatypes be added (like unsigned int32/64)
jderque has joined #ocaml
<thelema> mbishop: they will.
Camarade_Tux_ has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
<Yoric[DT]> mbishop: that's planned.
<Yoric[DT]> However, in the current state, these types exist only as modules using additional native code, without any packaging.
<Yoric[DT]> It would really simplify our life if someone packaged these types.
<Yoric[DT]> It would really simplify our life if someone packaged this module, that is.
<kig> hey, as ocaml has a lot of collection types with nearly identical interfaces (create, [unsafe_]set, [unsafe_]get, length, rest can be implemented with those), what would be the good way to write a bunch of functions against that interface so that it can be added to all collections (functors / copypaste?)
<Yoric[DT]> Let's make it "these modules".
<Yoric[DT]> kig: working on that, too :)
<Yoric[DT]> One of the problem is that currently the interfaces are not always identical.
<Yoric[DT]> i.e. [fold] vs. [fold_left] vs. [fold_right]
<mbishop> it would be nice if you crazy hax0rs could hack it up so we can use literals for additional types
<mbishop> 123UL for uint64, etc
<kig> that's why i'm writing them identical from the ground up
<Yoric[DT]> kig: then functors.
<flux> kig, have you taken a look at the ocaml reins project?
<thelema> mbishop: write some camlp4, please
<flux> wish the defunctorizer was resurrected, that way functorizing code wouldn't feel that much like throwing speed away :)
johnnowak has joined #ocaml
Snark has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
<kig> flux: nope, it looks interesting though (read: i'll read the documentation and go NIH anyway)
<Yoric[DT]> thelema: unfortunately, it requires changing the camlp4 lexer...
Camarade_Tux_ is now known as Camarade_Tux
<kig> ah, reins is more about pointery data structures than arrays
itewsh has quit [Connection timed out]
<kig> maybe i can use it
<thelema> Yoric[DT]: you couldn't simulate 123UL by doing a (from_int64 123L)?
<thelema> yes, you'd still have to change the lexer, you're right.
johnnowak has quit []
Camarade_Tux has quit []
johnnowak has joined #ocaml
Camarade_Tux has joined #ocaml
tar_ has joined #ocaml
<thelema> Yoric[DT]: it looks like there's no real batteries code outside extlib (and maybe some minor things like ocamlbuild/findlib). Am I missing something?
guillem has joined #ocaml
<thelema> all the glue modules seem to do is include one other module. Why the indirection?
<thelema> main/ seems to have enough indirection to get the job done.
<Yoric[DT]> thelema: For the moment, everything's in extlib and misc.
<thelema> will anything get put in base?
<Yoric[DT]> What the glue code does is change the apparent structure and possibly the documentation.
<thelema> or is that just references to the ocaml stdlib?
<Yoric[DT]> Base is just the inria library.
<Yoric[DT]> Yep.
<Yoric[DT]> Since "stdlib" has gotten pretty ambiguous, it's called "base library" here.
<thelema> hmm. why have glue to the base lib? There's got to be a better way to change the documentation...
<thelema> and can you give an example of changing the apparent structure?
<Yoric[DT]> ExtArray.Array => Array
<Yoric[DT]> ExtList.List => List
<Yoric[DT]> but ExtList.( @ ) => List.( @ )
<thelema> ExtArray.Array => Batteries.Data.Containers.Mutable.Array
<thelema> and the issue with @ gets resolved easily by putting let (@) = Extlib.ExtList.(@)
<thelema> inside module Standard (which shouldn't even be a module)
<Yoric[DT]> Sure.
<Yoric[DT]> Well, there should be a way of referring to stuff which lies in Standard.
<Yoric[DT]> And of reaching the corresponding documentation.
<thelema> Batteries.foo
<Yoric[DT]> Although Standard is actually included in Batteries for convenience.
<Yoric[DT]> So [open Batteries] actually also does [open Batteries.Standard].
<flux> I suppose many of the uses of such longwinded names will be expected to be via local aliasese? or even via opening the module (which I attempt to avoid)..
<thelema> I missed the "include Standard"
<Yoric[DT]> flux: the idea is to do [open Batteries.Data.Containers.Mutable]
<flux> or, open one level, use the rest with full names?
<Yoric[DT]> Then you have your usual List.fold_left, etc.
<flux> it has a mutable List?
<Yoric[DT]> Sorry, I meant [Persistent].
<thelema> Yoric[DT]: I don't like that idea -- you seem to have taken some non-features from java in your design.
<Yoric[DT]> It has mutable [RefList], though.
<thelema> for example, deep nesting of modules
<Yoric[DT]> thelema: well, the Java aspect is that I expect 100+ modules.
<Yoric[DT]> So we need to arrange them in a coherent pattern.
<thelema> and because ocaml has a flat module namespace, making a heirarchy doesn't buy us anything.
<Yoric[DT]> Otherwise, people won't even be able to read the list or to find stuff in the documentation.
<flux> I'm not sure there are going to be so many modules that an intermediate level "Containers" is going to be useful?
<Yoric[DT]> flux: I agree that we could perhaps remove some modules.
<Yoric[DT]> I expect this to happen between 0.1 and 0.2 .
<Yoric[DT]> Although it could happen before 0.1 :)
<Yoric[DT]> thelema: what do you mean flat?
<thelema> java has a heirarchical namespace for modules, so you can have foo1.bar and foo2.bar
<flux> google doesn't know much of batteries yet, the forge-page is the nth of the results to 'ocaml batteries' :)
<thelema> ocaml won't allow that.
<thelema> you only get one bar
<thelema> or is that only for module files?
<flux> well
<Yoric[DT]> thelema: well, here, you can.
<flux> this is legal: module A = struct module B = struct end end module A2 = struct module B = struct end end, right?
<flux> I guess the trick is how to not to introduce global module 'B' also
<flux> ?
<Yoric[DT]> You can quite well have Data.Containers.Mutable.Array and Data.Containers.Persistent.Array .
<thelema> flux: that is legal, but if you try to split it into separate files (as in a large project), you die.
<Yoric[DT]> Which is one of the reasons of the indirection.
Snark has quit ["Ex-Chat"]
<Yoric[DT]> Directory [main] gives the "apparent" module names.
<Yoric[DT]> Directory [glue] gives them unreadable unique names.
<Yoric[DT]> (and documentation)
<thelema> I guess I'm thinking that there's no benefit in separate maintenance because of the collisions.
<flux> thelema, well, then there's the compile time switch for adding levels of hierarchy, so you can put everything under XXX.*
<flux> but I don't know what batteries does
<Yoric[DT]> thelema: the only collision I can think of is Camomile vs. ExtLib.
<flux> yoric[dt], so it generates identifiers?
<Yoric[DT]> flux: what do you mean?
<flux> yoric[dt], "Directory [glue] gives them unreadable unique names." ?
<Yoric[DT]> flux: no, it's hand-generated.
<thelema> Yoric[DT]: they must already have unique names to get compiled together.
<thelema> I don't see the [glue] directory helping.
<flux> yoric[dt], hm, when they refer to each other, they must use the hand-generated identifiers?
<Yoric[DT]> thelema: true, they must have originally unique names.
<Yoric[DT]> thelema: on the other hand, we can give them more coherent names in [main], even if these names are identical.
<thelema> so at the moment, the glue dir gives us... better documentation
<Yoric[DT]> Fair enough.
<Yoric[DT]> It gives more segmented documentation.
<Yoric[DT]> And still the different arrangement of modules,.
<thelema> don't get me wrong - I like the generated documentation.
<thelema> but I imagine that's still producable without the glue .ml files
<Yoric[DT]> afk
<Yoric[DT]> back
<Yoric[DT]> Again, the role of glue is not very interesting for ExtLib.
<Yoric[DT]> It's bound to become much more interesting when we start introducing libraries which we're not going to include but for which we need to make interface changes.
<thelema> agreed. But why have unnecessary complexity in the cases it doesn't buy us anything?
<Yoric[DT]> Didn't I agree 1h ago that glue/extlib could be removed? :)
<thelema> glue/base?
<thelema> also?
<Yoric[DT]> I don't agree for removing glue/base.
<thelema> sorry, I'm just making sure I understand some more of what I'm doing.
<Yoric[DT]> Sure.
<Yoric[DT]> I believe that glue/base is important because, well, the base lib is something we can't modify.
<Yoric[DT]> On the other hand, we're going to get rid of some stuff from it (which will be removed from the .mlis).
<thelema> extlib extends the base library in a very reasonable way (file: extXXX, module XXX include XXX <new code here> end)
<thelema> why not do the same thing to any other module from stdlib we intend to change.
<thelema> and you want to remove things from .mlis so you can put a subset of functions into a Batteries.foo.bar.xxx module?
<tar_> Should ocaml-ao have put its files in lib/ocaml/ as well as lib/ocaml/site-lib/ ? Or am I to use something like -I +site-lib/ao for building stuff that uses it?
<thelema> tar_: ocaml-ao?
<tar_> thelema: It's a wrapper for libao (audio out)
<thelema> The current plan for other libraries is to findlib-require it
<thelema> err, not related to batteries. sorry. Use findlib to package it
<thelema> s/package/install/
<Yoric[DT]> thelema: yes, some modules may be split.
<Yoric[DT]> I'm also thinking about [channel_in], [channel_out] and [Stream.t].
itewsh has joined #ocaml
<Yoric[DT]> But yes, the idea of [ext*] is actually good.
<thelema> findlib will take care of where it gets installed, as well as the compilation flags
<Yoric[DT]> Probably better than the dychotomy between [glue] and [additions].
* thelema appreciates it much more now than yesterday.
<Yoric[DT]> "it"?
<thelema> it = extlib organization, although it=findlib also true
<Yoric[DT]> Yes.
<Yoric[DT]> My biggest issue with extlib organization is that it doesn't pack all its modules, hence polluting the global namespace.
<tar_> thelema: Thank you
<thelema> Yoric[DT]: can you give one example, or are you referring to a compiler flag that affects low-level representatino?
<Yoric[DT]> thelema: one example of what?
<thelema> not packing
<thelema> tar_: you're welcome
<thelema> tar_: what do you think of http://savonet.sourceforge.net/?
<tar_> thelema: Looks like a web site, likely a front for an agency gathering radio play data for the RIAA
<Yoric[DT]> thelema: well, module UTF8 is not packed.
<thelema> tar_: it's the site for some ocaml software that does radio station automation. It may already have libao code.
<Yoric[DT]> Which means that you simply can't have a project containing ExtLib and Camomile.
<tar_> thelema: Oh yeah, I checked it out before for its jack code. ocaml-ao has its own SourceForge project where I got the code I'm using now.
<thelema> Yoric[DT]: I admit I still don't follow what you mean by packing modules.
<Yoric[DT]> thelema: I was thinking of [ocamlc -pack].
<Yoric[DT]> Or of some equivalent manoeuver.
<thelema> ah. so you wish UTF8 were -pack'ed into an extlib.<something> library.
<Yoric[DT]> Yes.
<Yoric[DT]> And while they're at it, every other module which doesn't start with Ext.
<Yoric[DT]> And while they're at it, every module :)
<thelema> so all libraries should have a toplevel module that contains all the code in the library.
<thelema> seems pretty straightforward - just use -pack
<Yoric[DT]> Yes.
<Yoric[DT]> On the other hand, ExtLib doesn't do that.
<thelema> and there's no reason for our local copy of extlib to do that, because it'll get packed into Batteries.*
<Yoric[DT]> Well, I still did that for our local copy, just in case.
<Yoric[DT]> And for clarity of aliases.
<thelema> as you will.
<Yoric[DT]> It doesn't cost much and I think it's good policy.
<Yoric[DT]> For every project in src/additions/
<Yoric[DT]> Oh, and as you probably realized, your problem/fix with the Unix module seems to be related to the fact that version 3.11 adds support for ipv6.
<thelema> ok. hmm, this'll cause us trouble...
<thelema> can .mli's get [include]d?
<Yoric[DT]> Yes.
<thelema> so why don't we?
<thelema> (anytime we don't need to remove something, at least)
<Yoric[DT]> thelema: do you want the whole truth?
<thelema> I guess it doesn't preserve documentation.
<Yoric[DT]> Because I didn't think about it.
<Yoric[DT]> Oh, yeah, that, too :)
<thelema> :)
Jedai has quit [Connection timed out]
<Yoric[DT]> I'll have to leave.
<Yoric[DT]> I might come back later.
<thelema> thanks for working with me.
<thelema> look for a patch in the mail
<Yoric[DT]> Well, thanks for working with me.
<Yoric[DT]> I'll look for it
Jedai has joined #ocaml
<Yoric[DT]> Do you have any idea of when it'll be ready?
<Yoric[DT]> Just to know if I can start working on something else tomorrow.
<thelema> I think I'm done. I'm going to check on the documentation now.
<Yoric[DT]> Great.
tar_ has quit ["byebye"]
guillem has quit [Remote closed the connection]
<thelema> hmm, it looks like the documentation isn't where it was -- ocamldoc doesn't seem to find List inside Extlib.ExtList. Although this could be because of the -pack, or just because it's a submodule
<Yoric[DT]> Might be because of a hack of mine.
<Yoric[DT]> (yes, I'm still around, after all)
* thelema tries unpacking extlib
<Yoric[DT]> I need to add "@documents NameOfModule" .
<thelema> @documents would point from the documentation to the place that it should get used, or the other way?
<Yoric[DT]> That is, I've added a custom documentation tag "@documents Bar" to use when module Foo actually serves to document module Bar.
<thelema> ah. Nice. Done?
<thelema> I can add these tags to extlib
<Yoric[DT]> Yeah, that tag is part of my custom generator, which is invoked when you do "make doc".
* thelema tries it
<thelema> like this: (** @documents Data.Containers.Persistent.List *)
itewsh has quit [Read error: 110 (Connection timed out)]
<thelema> (inside extlist.mli)
itewsh has joined #ocaml
middayc has joined #ocaml
<Yoric[DT]> You have to put it inside the module documentation, i.e. the first comment.
<thelema> right after the sig.
<thelema> well, doesn't look like it's worked.
middayc_ has joined #ocaml
<Yoric[DT]> Mmhhh....
<Yoric[DT]> Actually, I haven't tried to make it work with module paths.
<Yoric[DT]> So you're in ExtList.List and you want to document Data.Containers.Persistent.List, is that it?
<Yoric[DT]> If so, the alias
<Yoric[DT]> [module List = ExtList.List]
<Yoric[DT]> inside [Data.Containers.Persistent]
<Yoric[DT]> should pull the documentation from [ExtList.List]
<Yoric[DT]> and rename it as [List].
<Yoric[DT]> mmmhhh....
<thelema> module List = Extlib.ExtList.List
<Yoric[DT]> ok
<Yoric[DT]> Although I haven't tried getting this to work with module paths.
<Yoric[DT]> Only with single modules.
<Yoric[DT]> I'll try and improve the documentation generator tomorrow.
<Yoric[DT]> For the moment, time to call this a night.
<Yoric[DT]> Thanks for the work.
<thelema> good night.
<Yoric[DT]> Cheers.
Yoric[DT] has quit ["Ex-Chat"]
jlouis has joined #ocaml
middayc has quit [Read error: 110 (Connection timed out)]
itewsh has quit [Read error: 110 (Connection timed out)]
itewsh has joined #ocaml
Camarade_Tux has quit []
longh has quit [Read error: 104 (Connection reset by peer)]
itewsh has quit [Connection timed out]
itewsh has joined #ocaml
jderque has left #ocaml []
blue_prawn has joined #ocaml
<blue_prawn> hello
JohnnyL has joined #ocaml
itewsh has quit ["KTHXBYE"]
marmotine has quit ["mv marmotine Laurie"]
tomh_-_ has quit ["http://www.mibbit.com ajax IRC Client"]
middayc_ has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
hkBst has quit [Read error: 104 (Connection reset by peer)]
jlouis has quit ["Leaving"]
blue_prawn has quit ["Client exiting"]
nuncanada has joined #ocaml
<kig> http://glimr.rubyforge.org/cake/array_helpers.ml hmm, still need to copypaste that for strings
Jedai has quit [Read error: 110 (Connection timed out)]
Jedai has joined #ocaml
mbishop_ has joined #ocaml
mbishop has quit [Read error: 113 (No route to host)]
Palace_Chan has joined #ocaml