flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
seafood has quit []
seafood has joined #ocaml
<mrvn> How dirty do you consider this? http://paste.debian.net/32098/
<mrvn> It is safe, right?
hsuh has quit [Remote closed the connection]
<thelema_> mrvn: why the obj.magic?
<thelema_> because x isn't always unit... hmmm
<thelema_> you want a doubly-linked-list of printables... What about storing a [() -> string]
<thelema_> type base = { mutable next : base; mutable prev: base; to_string : () -> string }
<thelema_> just hide your data in the closure for [to_string]
<mrvn> for mutable data : 'a that would require storing a reference in all closures.
<mrvn> another 16 bytes per object wasted.
<mrvn> and 16 bytes or something per closure per object for the binding.
<thelema_> you're right. If you *had* to do this efficiently, your way is dirty, but would work.
<thelema_> and you would get segfaults by trying to access x.data
<mrvn> haeh?
jeremiah has quit [Read error: 110 (Connection timed out)]
<mrvn> I'm accessing x.data in the code. works fine.
<mrvn> x.to_string x.next.data would be bad.
<thelema_> what type is x.data?
<mrvn> thelema_: 'a
<mrvn> The 'a that x.to_string expects
<thelema_> I see line 11, but if you tried to do anything else with x.data...
<mrvn> in print x.data is unit as far as ocaml is concerned.
<mrvn> I'm assung unit will never be actually read no matter what you do with it.
<mrvn> assuming
<thelema_> unit == 0
<mrvn> but the compiler already knows it is unit so it doesn't have to read x.data from memory.
<thelema_> ? you think that the compiler handles unit specially?
<mrvn> well, maybe not. But what can you do with unit other than passing it to a function?
jeremiah has joined #ocaml
<thelema_> what can you do with any value other than pass it to a function?
<mrvn> true.
<thelema_> except for functional values, which you can apply.
<mrvn> (x.to_string x.data) certainly is as dirty as head.prev.next <- Obj.magic e;
<mrvn> It just hides it better.
<thelema_> Yes, that's definitely a tricky bit, but if ocaml treated unit specially, it wouldn't pass it to the print function, and you'd be stuck.
<mrvn> thelema_: hmm, haven't thought about that.
<mrvn> It definetly passes (x.data : unit) down to the closure.
<mrvn> If I make 'a base abstract and export only let to_string x = x.to_string x.data then I think I can completly hide the Obj.magic from users and keep this type save.
ched_ has joined #ocaml
Cheed has quit [Read error: 110 (Connection timed out)]
<thelema_> I'd admit that would work.
rhar has quit [Read error: 110 (Connection timed out)]
<mrvn> I miss member pointer.
<thelema_> what use do you intend for var_fun?
<thelema_> in fact, what use do you intend for this whole structure?
<thelema_> why not move data into fn?
<mrvn> I'm playing around. Trying to see different ways to get a doubly linked list of things with a common functionality.
<mrvn> thelema_: Because for any one 'a all 'a fn are const and can share one fn structure.
<mrvn> I only need one string_fn, one int_fn. millions of string data and int data.
* thelema_ still wonders about uses
<mrvn> Objects in a set of work queues where they can jump queues.
<thelema_> might as well have a lookup table [type_id -> fn]
<mrvn> thelema_: then M would need to know all 'a or you would have to register type_ids.
<thelema_> M.make "s" string_fn string_id
<thelema_> you'd have to generate unique type_ids, yes
<mrvn> And then store string_id instead of string_fn?
<thelema_> instead of fn
<mrvn> Looking up the type_id -> fn would cost time.
<thelema_> vectors are pretty fast
<thelema_> extensible arrays
jeremiah has quit [Excess Flood]
jeremiah has joined #ocaml
<mrvn> thelema_: you would use id -> 'a * 'a fn for the hashtbl though.
<thelema_> that would type nicely, but be heavier in terms of sharing.
<mrvn> A few days ago there was a similar post that used (int * Obj.repr) to store objects.
pierre_m has joined #ocaml
<mrvn> But I don't need an id at all as nobody can set or get the objects. You can only call closures they have and that will always have the right type.
<thelema_> this would allow access to the values in a type-safe way.
pierre_m has left #ocaml []
<mrvn> thelema_: but I couldn't call functions on them in M.iter
<thelema_> I think you could, if you put the functions in at create time, like you do now.
<mrvn> Only the code that calls "let (set, get) = new_property ()" has the accessors with the right typing and could call functions.
<thelema_> new_property could take a mutator function as argument
<mrvn> thelema_: In the heterogeneous containers you couldn't call Hashtbl.iter (fun id prop -> ...) tbl
<mrvn> or rather you could not access the "v" in there.
hsuh has joined #ocaml
<thelema_> (get id) |> f |> set
<mrvn> thelema_: what is get or set?
<thelema_> the accessor functions in heterogenous containers example.
<mrvn> get : t -> 'a, set : t -> 'a -> unit.
<mrvn> you can't know that 'a insdide M. That is the problem.
* thelema_ doesn't see the problem.
<mrvn> thelema_: same idea but with classes: http://paste.debian.net/32105/
<mrvn> thelema_: Where would you get the get/set from in M.iter? You can't store it in type t.
<mrvn> thelema_: you would have to take each closure and bind it to a reference of the data. Like the "v" in set/get in your url.
<mrvn> to_string : 'a -> string then become to_string : unit -> string. That you can access.
<thelema_> you want to do something (fun id prop -> ...) tbl
<thelema_> n/m, you're right. You couldn't iterare the heterogenous containers using a single function.
<thelema_> *iterate
<thelema_> you'd need different functions for each property
<thelema_> otoh, you could have mutators
<thelema_> I dunno why I was thinking mutators when you were thinking iteration...
<mrvn> thelema_: by the way, in the url why isn't it let new_property t = ... with set : 'a -> unit and get : unit -> 'a?
<mrvn> thelema_: no mutators either if you are thinking 'a -> unit or 'a -> 'a
<mrvn> unless it really is 'a -> 'a and not '_a -> '_a
<thelema_> you're probably right - it has to be '_a -> '_a
<thelema_> but you can still mutate within the given type
<mrvn> not even that.
<mrvn> mutate : type_id -> ('a -> 'a) -> unit can't work.
<mrvn> let mutate : (t -> 'a) -> (t -> 'a -> unit) -> ('a -> 'a) -> unit = function get set fn -> ... would though.
<thelema_> mutate t (set, get) f = get t |> f |> set t
<mrvn> but that would only mutate one element.
<thelema_> yes, again - impossible to iterate
<mrvn> I really need to iterate. It is for work queues. I have a queue of loaded objects, a queue of objects that are currently read from disk, a queue of objects that need to be written to disk, ...
<mrvn> reading/writing uses libaio so it starts the process in the background and goes and does something else.
<thelema_> sounds like you want typeclasses - heterogenous lists of foo-able objects
<mrvn> thelema_: In that code "s#set_next i" does not work and I can't get it to work any way. I think it is a compiler bug with "constraint"
<mrvn> And I'm too lazy to type "s#set_next (i :> vbase)" :)
<thelema_> what happens if you remove all your class types?
<thelema_> can't it infer sufficient object types?
<mrvn> and use what instead?
<thelema_> any time I see someone using object types, I expect them to run into problems with ocaml's type system, as there's no good way to give open object types (as get inferred by the type checker_
<mrvn> class type data is unused. But the vbase is needed for next.
<mrvn> And because vbase is closed I need to extend it with vbase2.
<mrvn> I hate that "class ['a] base magic data : vbase" does not work. The intermittent class type ['a] vbase2 is rather anoying. The type system should infer that itself.
<mrvn> thelema_: here is the code using constraint. Any idea why it fails?
<mrvn> That should work without class type.
<thelema_> it fails because 'a <> #vbase_type
<thelema_> set_next doesn't take a 'a
<mrvn> It should take an 'a. 'a option -> unit constraint 'a = #vbase_type
<mrvn> which is #vbase_type option -> unit
<thelema_> hmmm...
<thelema_> but it's not...
<mrvn> if you specify it as #vbase_type option -> unit then it complains about an unbound 'a that escapes.
<thelema_> hmm, I don't even have a workaround...
<mrvn> thelema_: yep. I think it is a bug in ocaml. The constraint is completly dropped.
<thelema_> it is dropped because of the :vbase_type?
<thelema_> the constraint doesn't make it to the signature of vbase_type
<mrvn> no, in the vbase_type already.
<thelema_> if you lose the :vbase_type in the declaration of vbase, what do you get?
<thelema_> I guess you do need vbase_type to work...
<mrvn> method virtual set_next : 'b option -> unit
<mrvn> with constraint 'a = #vbase
<mrvn> or rather 'b here
<thelema_> that sounds good.
<mrvn> No, the constraint is still dropped.
<kaustuv> ('a. 'a -> t constraint 'a = s) is not the same type as (s -> t).
<mrvn> The source has constraint 'a = #vbase, the signature not.
<mrvn> kaustuv: except for the syntax error
<mrvn> class virtual vbase = object val mutable next = None method virtual set_next : #vbase option -> unit end;;
<mrvn> Error: Some type variables are unbound in this type:
<mrvn> The method set_next has type (#vbase as 'b) option -> unit where 'b
<mrvn> is unbound
<mrvn> and 'a. (#vbase as 'a) gives: Error: This type scheme cannot quantify 'a : it escapes this scope.
<mrvn> kaustuv: then you need to use x#set_next (Some (y :> vbas_type))
<mrvn> kaustuv: The idea was to get set_next to accept any 'a that is a superset of vbase_type.
<kaustuv> Why is that sound?
Axioplase has joined #ocaml
<mrvn> because it gets coerced to vbase_type in the class then.
<kaustuv> That's not how type constraints work.
<mrvn> let set_next x (n : #vbase_type option) = x#set_next (n :> vbase_type option) works.
<mrvn> You can't express the same as method of a class.
<mrvn> Hmm, on the ML someone wrote for this problem: OCaml does not allow the recursive reference when the method is polymorphic.
<kaustuv> which module is the 'a option type defined in?
<kaustuv> Oh, it's built in. And invariant on the type argument. Ho!
<mrvn> class type linked = object val mutable next : #linked option end
<mrvn> class type base_type = object inherit linked method set_next : 'a. (#linked as 'a) option -> unit
<mrvn> end
<mrvn> kaustuv: that works. Just not with recursion.
<kaustuv> Is ['a . 'a -> t constraint 'a = s] interpreted as [('a . 'a -> t) constraint 'a = s], i.e., [(forall 'a . 'a -> t) constraint 'a = s]? That would explain why the constraint is ignored because 'a is not free in [forall 'a. 'a -> t].
<kaustuv> (in reference to the caml-list thread)
<kaustuv> ((of which I've only read the first post))
<mrvn> No idea.
<mrvn> It should either keep the constraint in the signature or give an error that the constraint can not be garantied.
<kaustuv> I have an inkling that the constraint is dropped because it is irrelevant.
<mrvn> kaustuv: can't be irelevant. Can only be non inforcable.
<kaustuv> A constraint on a type variable that's not free in the type is irrelevant as it can always be enforeced. Even if the constraint were 'a = void where void is uninhabited.
<mrvn> kaustuv: the constraint should be allways true. If it is only sometimes true then the compiler should give an error.
<mrvn> If the 'a is not free then the constraint is only sometimes true.
<kaustuv> class type virtual test = object
<kaustuv> method virtual set0 : 'a. 'a -> unit constraint 'a = test
<kaustuv> method virtual set1 : 'a. 'a -> unit constraint 'b = test
<kaustuv> end
<kaustuv> set0 and set1 have the same type according to the type checker.
<mrvn> kaustuv: but if I call set0 with an int then 'a <> test
<kaustuv> but the 'a is outside the scope of the constraint
<kaustuv> set0 has type ['a -> unit] full stop.
<mrvn> kaustuv: then the compiler should give an error that 'a is out of scope.
<kaustuv> Yes, perhaps a warning here would be nice.
<mrvn> I don't get why "constraint 'b = test" compiles at all. 'b is not defined there.
<kaustuv> You can constrain any type variable regardless of whether it occurs free in the type being constrained or not
<mrvn> which I would say is the problem.
<kaustuv> And I've just read the grammar and, indeed, constrain has lower precedence than .
<kaustuv> It has the lowest precedence of all type expression operators, apparently
<mrvn> class type foo = object method foo : 'a. ('a -> unit constraint 'a = #foo) end;;
<mrvn> gives a syntax error
<kaustuv> Yeah, because constrain can only be used at most once at the very outside
<kaustuv> err, constraint, not constrain
<mrvn> From a glimps at the grammar is the constraint even part of the method? Looks like it is totaly independent.
<mrvn> # class type foo = object constraint 'a = #foo end;;
<mrvn> class type foo = object end
<kaustuv> Hmm, I was looking at the grammar for type definitions...
<mrvn> # class type foo = object constraint 'a = #foo method foo : 'a -> unit end;;
<mrvn> Error: Some type variables are unbound in this type:
<mrvn> class type foo = object method foo : #foo -> unit end
<mrvn> The method foo has type (#foo as 'a) -> unit where 'a is unbound
Prael has quit ["Leaving"]
<mrvn> which is the problem that it is recursive.
<mrvn> You constrain 'a once and then any number of val or methods can use it.
<mrvn> And "'a. 'a -> unit" shadows the 'a from the constraint.
<mrvn> # class type foo = object constraint 'a = #foo val x : 'a val y : 'a end;;
<mrvn> class type foo = object val x : #foo as 'a val y : 'a end
<mrvn> Now that constraint behaviour makes much more sense.
Ori_B has quit [Remote closed the connection]
<kaustuv> The point of constraint in class types is apparently to constraint the type parameters. I'm going to have to violate my just-say-no-to-objects principle and read the manual because this is kind of interesting.
<mrvn> kaustuv: it creates a binding for a type variable restricting it to certain types.
<mrvn> kaustuv: did you see the hack to do the same with records in http://paste.debian.net/32103?
<kaustuv> No, but I'm looking at it now. Obj.magic? Highly questionable if you ask me.
<kaustuv> This is the sort of thing heterogeneous containers are good at.
<mrvn> kaustuv: verry. But it should be limited to inside the module.
<mrvn> kaustuv: no. you can't iterate over the elements in one and call closures.
<mrvn> kaustuv: in an heterogeneous container you would have to bind each function to a reference of the data so they all have the same type independent of what 'a is.
<thelema_> hmm, I wonder if we had a het. cont. with set : ('a, 'a -> unit)
<mrvn> thelema_: then M.iter can't access set.
<thelema_> err, set : t -> ('a, 'a->unit) -> unit
<thelema_> M.iter can access the hashtable elements directly and do (fun id (v, f) -> f v)
<mrvn> thelema_: that isn't the right type. you need 'a. ('a, 'a -> unit)
<mrvn> thelema_: no. you can't put objects of ('a, 'a->unit) for different 'a into a hashtable.
Ori_B has joined #ocaml
<mrvn> thelema_: If you look at the implementation of het. cont. then you see that they bind the 'a value and only put a closure unit -> unit (or something other without 'a) into the table.
<thelema_> you're right... we have to put (unit -> unit) into the hashtable...
<kaustuv> If ocaml had existential types we could do it, but existential types has a terrible price that is not worth paying IMHO.
<thelema_> but we can construct (set,get,mutate) with a known mutation function
<mrvn> let wrap x funs = let t = ref x in { fn1 = (fun () -> funs.fun1 !x); fn2 = (fun () -> funs.fun2 !x); ... } and put that into the table.
<mrvn> thelema_: nope. you can't specify a set/get that can be used to iter. set/get are element specific.
<thelema_> you're right... each set/get has a matching ref, and only one of those refs can be in scope at a time.
<kaustuv> if mutate had type [u -> unit] (where u is the type of containers) then there is no problem
<kaustuv> err, [u -> u]
<mrvn> but the mutate has also a matching ref and only one of those refs can be in scope at a time. :)
<mrvn> You can put the mutate into the hashtable but that is what the wrap up there does.
<kaustuv> what is the type of iter? [(t -> unit) -> t list -> unit]?
<mrvn> in my case ('a base -> unit) -> unit
<thelema_> kaustuv: generally yes, but it'd suffice to have (t->unit) pre-assigned
<thelema_> i.e. known at the time of construction of t
<kaustuv> Then there is no trouble if we have:
<kaustuv> make_container : unit -> (t -> 'a) * ('a -> t) * (t -> unit)
<mrvn> kaustuv: The difficult bit for iter is that for string objects string_fn.xxx has to be called and for int objects int_fn.xxx.
<thelema_> kaustuv: no trouble.
<kaustuv> or even make_container : ('a -> unit) -> (t -> 'a) * ('a -> t) * (t -> unit)
<thelema_> yes on that last one.
<mrvn> kaustuv: then you have an int container and string container but not an anything container.
<kaustuv> mrvn: I guess I've misunderstood what you want. You want a single function of type [t -> unit] that does a typecase on what t is. This is different from a number of different ['a -> unit] all compatible with [t -> unit].
<mrvn> kaustuv: I want class virtual foo = object method virtual fn : ... end; and call foo#fn for all #foo in the container.
<mrvn> but without the class.
<mrvn> typesafe, fast and with as little memory overhead as possible.
<kaustuv> Right, but this is ad hoc polymorphic, not parametrically polymorphic, so you need some form of typecase
<mrvn> kaustuv: no, just some obj.magic. :)
seafood has quit []
<kaustuv> Obj.magic is the wrong answer here. The right answer is Haskell-style type classes, perhaps.
<mrvn> The is no if type = type1 then ... else if type = type2 then ...
<mrvn> thedata stored is basically ('a, 'a -> unit). The two 'a will always match so there is no typecasing.
<mrvn> Without obj.magic there is just no way to convince the type system of that fact.
<thelema_> kaustuv: it's wrong because the ocaml type system isn't sufficient to encode this kind of hidden types
<thelema_> ?
<mrvn> thelema_: yep
<mrvn> I would encode that hidden type as # type t = 'a. ('a, 'a -> unit);;
<thelema_> the problem is that ocaml has to know it's okay to take (x,f) and apply f to x.
<mrvn> thelema_: That it knows.
<mrvn> the problem is to give up the type info for an object when e.g. doing (x, fn)::list
<thelema_> mrvn: once you have a value of type t, desctructuring it gets you two values of unknown type
<kaustuv> The type [forall 'a . 'a * ('a -> unit)] is uninhabited, I believe.
<kaustuv> Or rather, not inhabited by pure functions
<mrvn> thelema_: let (x, fn) = t should give 'a. 'a and 'a. 'a -> unit where the 'a. is the same.
<mrvn> ocaml would have to track that x and fn are bound to the same 'a.
<mrvn> kaustuv: It works with virtual methods in classes so I don't believe it is untypable.
<mrvn> A class basically is 'a. 'a * ('a -> unit) * ('a -> int -> string) * ...
<kaustuv> But that is an existential quantification, not a universal.
<mrvn> kaustuv: you can coerce classes to a common base class and build a list of them. calling a virtual function on all elements of that list is type save and does solve 'a. ('a * 'a -> unit) problem internally.
<mrvn> Somehow methods for classes must be magically typed internally to have thisfunctionality.
<mrvn> It probably does what I did with the obj.magic. It just fakes that the type is well formed because it knows that works out right in the end.
<thelema_> mrvn: wouldn't the class you want have a method of type unit -> unit? It's basically the closure solution I gave earlier
<thelema_> except the value enclosed is mutable.
<mrvn> thelema_: a method must get the class itself as first argument.
<thelema_> let gen_obj v0 mutate = let x = ref v0 in fun () -> mutate !x
<mrvn> thelema_: does ocaml actualy do that in "new foo"?
<mrvn> thelema_: I would have thought foo#fn x becomes foo_functions[fn] foo x
<thelema_> It makes a closure-like record with slots for all the instance variables plus a pointer to the vtable for method dispatch
<mrvn> thelema_: and that closure like record is passed as first argument to every method.
<thelema_> values in it are available (like a closure) to methods
<mrvn> or are the methods in the vtable already bound to that record?
<thelema_> vtable is shared amond many of the same objects
<mrvn> then you have 'a. { val1 : 'a val1; val2 : 'a val2; vtable : 'a vtable }
<mrvn> and vtable has functions 'a record -> 'b -> 'c
<mrvn> (if that syntax makes sense)
<thelema_> effectively, something like that.
<thelema_> I don't see why val1 : 'a val1
<mrvn> The type of the first val or the class.
<thelema_> same as 'a val2?
<mrvn> type of the second val of that class.
<mrvn> Could be anything but it is specific to the type of the class.
<mrvn> thelema_: The interesting question is what (foo :> bar) now does. It changes the type of foo to something that is bar. But in virtual functions dispatching changes the type back to foo. And I think that just Obj.magics the type back.
<mrvn> It just dumps type bar onto the stack/register and knows the recieving function will take it as foo.
<thelema_> it does the type equivalent of replacing the vtable
ttamttam has joined #ocaml
ttamttam has left #ocaml []
<mrvn> anyway, I can't think straight anymore. Need some sleep. :)
hsuh has quit [Read error: 110 (Connection timed out)]
nickeldeuce has joined #ocaml
nickeldeuce has quit [Client Quit]
petchema has quit [Read error: 110 (Connection timed out)]
nickeldeuce has joined #ocaml
<Yoric[DT]> Gasp.
<Yoric[DT]> GODI server issue, it seems I can't release Batteries tonight.
petchema has joined #ocaml
rhar has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
nickeldeuce has quit []
nickeldeuce has joined #ocaml
Axioplase has quit ["Lost terminal"]
nickeldeuce has quit []
rhar has quit ["This computer has gone to sleep"]
mikeX_ has joined #ocaml
mikeX has quit [Read error: 110 (Connection timed out)]
jbms has joined #ocaml
<jbms> I'm having trouble using the camomile package. (I can't seem to get it loaded.)
<jbms> I have findlib and camomile installed (version 0.7.1)
<jbms> At the top-level, with topfind loaded, after typing #require "camomile";;
<jbms> If I then do: module X = Camomile ;; I get Unbound module Camomile
<jbms> The same if I do module X = UTF8 ;;
<jbms> any idea what I can check to see why this is happening?
<flux> jbms, open CamomileLib?
<flux> at some point Camomile moved everything under that name
<jbms> That doesn't seem to do it
<jbms> There isn't any way to list the available modules, is there?
<flux> there might be with enhtop, but not with regular toplevel
<flux> what is your camomile's version? ocamlfind list | grep camomile will tell
<jbms> 0.7.1
<flux> I remembered the name wrong, it's CamomileLibrary
<flux> in any case, here's one trick: ls `ocamlfind query camomile`/*.cmi
<flux> that will list all the interfaces with the module
<flux> and those are all you can use
<jbms> ah yes, CamomileLibrary works
<jbms> thanks
<flux> camomile is difficult to get into, I wish it had real documentation
<flux> perhaps batteries will make unicode easier
<jbms> Batteries makes UTF8.t an opaque type, which seems unnecessarily annoying
<flux> well, on the other hand it's good that it's more difficult to mix utf8 and plain strings
<flux> as batteries also has unicode literals and other related goodness, the pain should be minimal
<flux> ?
<jbms> ah, interesting
<jbms> Generally, I want to work with UTF-8 basically just as an array of bytes; I generally don't need to care about individual characters
<jbms> and when processing something in UTF-8, I might want to process it byte-by-byte
<flux> so you might want to take 5 byte subsequences instead of 5 code subsequences?
<jbms> Well, I'll virtually never care about code points
<jbms> In fact it is somewhat hard to imagine an algorithm that cares about code points alone
<flux> I care about taking valid utf8 in and giving valid utf8 out :)
<jbms> well, you can pass it through validate
ygrek_ has joined #ocaml
<flux> it's better to not to make a bug in the first place
<jbms> The reason that it is a bit odd to care about individual code points is that there are combining characters like accents and such
<flux> I recently needed to write a function that converted a byte offset to a code offset
<flux> camomile didn't seem to provide that
<jbms> why did you need that?
<flux> I used Pcre library to find substrings and I needed to pass those offsets to Postgresql which was in utf8 encoding mode
<jbms> hmm I see
<jbms> well, it doesn't have a function directly to do that, but you could use UTF8.first, UTF8.last, and UTF8.next
<jbms> it is, after all, somewhat of an unusual case
<flux> I must've missed that index = int is public :). in any case, it needs a loop.
<jbms> yes (well there is compare_index)
<jbms> There isn't a more efficient way to do it than looping, though
<flux> well, if Pcre.extract_all supported unicode offsets, I wouldn't need that
<flux> I wasn't thinking efficiency but rather how complex it is to write. otoh, perhaps extlib or batteries has a function that would help doing that.
<jbms> is there documentation of the unicode literal stuff in batteries?
<flux> no idea
<jbms> how did you hear about it then? :)
<jbms> is batteries included usable, btw?
Camarade_Tux has joined #ocaml
<flux> I've basically read all the blog entries related to it, browsed through its documentation and once compiled it, and that's about it ;)
ygrek_ has quit [Remote closed the connection]
Alpounet has joined #ocaml
<Alpounet> hi
seafood has joined #ocaml
slash_ has quit [Client Quit]
Alpounet has quit [Remote closed the connection]
nickeldeuce has joined #ocaml
Alpounet has joined #ocaml
s4tan has joined #ocaml
ygrek has joined #ocaml
_zack has joined #ocaml
jamii_ has quit [Read error: 110 (Connection timed out)]
ygrek has quit [Remote closed the connection]
OChameau has joined #ocaml
hkBst has joined #ocaml
hkBst has quit [Client Quit]
hkBst has joined #ocaml
hkBst has quit [Client Quit]
hkBst has joined #ocaml
nickeldeuce has quit []
nickeldeuce has joined #ocaml
verte has joined #ocaml
komar_ has joined #ocaml
Nucleos has joined #ocaml
<Nucleos> Hello.
<Nucleos> shoud i post code here ?
<kaustuv> Use a paste site such as http://ocaml.pastebin.com
<Nucleos> Thanks
<Nucleos> In this code : http://ocaml.pastebin.com/m30f143ee
<Nucleos> I don't understand why p1 doens't give me the same result as p2
<Nucleos> In the given example, p1 gives me a non-empty set, whereas p2 gives me an empty set.
<kaustuv> Change line 21 to:
<kaustuv> let p2 = Plateau.add (5,4) p2 ;;
<Nucleos> oh gosh...
<kaustuv> Plateau.add doesn't actually modify the set. It returns a new set.
<Nucleos> ok
<Nucleos> then when p2 is redefined, "the old" p2 is unreachable ? (taken by the garbage collector ?)
<kaustuv> Yes.
<Nucleos> perfect
<Nucleos> thanks !
<kaustuv> De rien
yminsky has quit [Read error: 104 (Connection reset by peer)]
yminsky has joined #ocaml
itewsh has joined #ocaml
Camarade_Tux has quit ["Leaving"]
ched_ has quit [calvino.freenode.net irc.freenode.net]
bjorkintosh has quit [calvino.freenode.net irc.freenode.net]
Asmadeus has quit [calvino.freenode.net irc.freenode.net]
nickeldeuce has quit []
ched_ has joined #ocaml
bjorkintosh has joined #ocaml
Asmadeus has joined #ocaml
ygrek has joined #ocaml
petchema has quit [Read error: 110 (Connection timed out)]
petchema has joined #ocaml
komar_ has quit [Read error: 113 (No route to host)]
Nucleos has quit ["Quitte"]
nickeldeuce has joined #ocaml
ygrek has quit [Remote closed the connection]
seafood has quit []
Snark_ has joined #ocaml
verte has quit ["http://coyotos.org/"]
Snark_ has quit [Read error: 60 (Operation timed out)]
<mrvn> flux: If you need to do anything the strings other than pass them around then utf-8 is the wrong thing. Use utf-32.
<mrvn> +with
<flux> mrvn, well, pcre doesn't support utf32
<flux> and I don't think postgresql does either
<flux> and if the task is to find substrings from an utf8-string and report the contents and the utf8-offsets to the database, utf32 is not going to help me one bit :)
<Alpounet> application period closed for JSSP, heh.
* Alpounet crosses fingers
j_lenorm has joined #ocaml
willb has joined #ocaml
rhar has joined #ocaml
j_lenorm has quit [Remote closed the connection]
willb1 has joined #ocaml
<flux> hm, sexplib could use another extension: pattern matching s-expressions in a nice way
<flux> I suppose one of the existing pattern matching extension libraries could be used for implementing that
<mfp> what's the data type of sexps?
ulfdoz has quit [calvino.freenode.net irc.freenode.net]
totom has quit [calvino.freenode.net irc.freenode.net]
totom has joined #ocaml
<flux> Sexplib.Sexp.t is something like type t = List of (t list) | Atom of string
<mfp> uh, no separate constructors for ints or uh bools at least?
<flux> no
<flux> they wouldn't survive anyway, because s-expressions are strings like (foo bar (baz plop) ())
<mfp> the lexer could turn 234 into Int 234 instead of Atom "234"
<flux> yes, but I'm interested more in parsing responses
<flux> while that could be useful too
<mfp> so such a syntax ext would essentially turn OCaml literals into their S-exp equivalents (as Atom "whatever")?
<flux> yes
<flux> well, unless one liked to do those integer matching thingies somehow, it would complicate it quite a bit
<mfp> match_sexp t with ["foo"; 1; 2] -> match t with List [Atom "foo"; Atom "1"; Atom "2"] and so?
<mfp> the 1..10 thingy?
<flux> something like what that some regexp matching extension did
<flux> if you matched [0-9]*, the type became an integer
<flux> (nifty hack)
<flux> I'm not sure of the syntax
<flux> perahps: match_sexp t with ["foo", ["arg1"; arg : int]] etc
ulfdoz has joined #ocaml
willb has quit [Remote closed the connection]
Amorphous has quit [Read error: 110 (Connection timed out)]
Snark_ has joined #ocaml
Amorphous has joined #ocaml
hardcoding has joined #ocaml
<hardcoding> Hello does anyone know where I could find an eBook about binary trees and OCAML? (I mean an interesting one... and if you know about other ebooks related to OCAML, I'm interested as well.)
Associat0r has joined #ocaml
Associat0r has quit [Read error: 104 (Connection reset by peer)]
rhar has quit ["Leaving"]
j_lenorm has joined #ocaml
s4tan has quit []
willb1 is now known as willb
willb has quit ["Leaving"]
willb has joined #ocaml
nickeldeuce is now known as bj`sleep
<mfp> hardcoding: have you seen Okasaki's thesis?
<mfp> (legally available online)
<hardcoding> mfp, Hello! No I haven't! I'm going to check it out then!
<mfp> it uses SML, but is easily translated to OCaml (the translation is also available online; it's not a bad exercise though)
<mfp> not much about BSTs, but this (well, actually his book, which expands on the thesis) is the mandatory reference on purely functional data structures
j_lenorm has quit [Remote closed the connection]
<hardcoding> Purely Functional Data Structures
<hardcoding> yes I'm reading it
<hardcoding> september 1996^^
<mrvn> programming languages haven't changed in the last 10+ years. Nothing fundamentaly new has been discovered.
<kaustuv> mrvn: See the late Eiichi Goto's work on the Parametron for radically new stuff
<mrvn> kaustuv: and what language uses that? :)
komar_ has joined #ocaml
* mrvn doesn't google for "The use of parametrons for binary trees in ocaml"
<kaustuv> Well, I've seen a few toy programming languages based on reversible computation, but in this case theory is a few generations ahead of practice
<kaustuv> But a more mundane example of a nice new idea in prog. lang.s in the last decade is GADTs.
<hardcoding> "it is language-independent only in the sense of Henry Ford: Programmers can use any language they want, as long as it’s imperative."
<hardcoding> Okasaki starts it dynamically! haha
<kig> the only thing that's happened in the last 10 years is an extra teraflop of processing power in desktop computers (of which you can only use 2.5 because you're stuck programming single-threaded python)
<mrvn> IsZero :: Term Int -> Term Bool
<mrvn> kaustuv: Is that like Int Term and Bool Term in ocaml?
<Alpounet> yeah
<Alpounet> Term here is a parametrized type
<hardcoding> or 0.5 because you're stuck writing the factorial function in OCAML (in my case haha) kig
<kig> in ocaml your factorial runs at at least 10 gigaflops
<kig> and returns 0
<kaustuv> mrvn: Not exactly. The idea of a GADT is that the arms in a match can match different (more constrained) types than the type of the argument. In ocaml all arms match against the same type.
_zack has quit ["Leaving."]
<mrvn> kaustuv: So I could write match term with Add(x,y) -> x+y | Append(x,y) -> x^y ?
<mrvn> term -> (int | string) basically
<kaustuv> Sure, but you'd have to tag the result with a disjoint union of Int and String
<kaustuv> Either that or the function itself has tyoe Term a -> a.
drguildo has joined #ocaml
<mrvn> kaustuv: from the example I gather that haskell would automatically infere that from Add :: Term Int * Term Int -> Term Int Append :: Term String * Term String -> Term String
<mrvn> or whatever you would declare them as.
<mrvn> kaustuv: yes, Term a -> a in this case.
<kaustuv> Which example are you quoting from?
<kig> the economic downturn has imploded contest prizes as well: http://software.intel.com/en-us/articles/threading-challenge-2009-contest-prizes/
drguildo has left #ocaml []
lutter has joined #ocaml
<mrvn> kaustuv: I'm not sure how you would use GADTs. To me it seems that the type inference would have to keep track of the transformation each function does depending on its exact input type and then you just get huge sets of possible type combinations.
<mrvn> Just like allowing operator overloading would.
<mrvn> (i.e. (+) : (int -> int -> int) | (float -> float -> float) |...
<kaustuv> mrvn: I have found GADTs to be amazingly useful in my own work (viz. writing theorem provers). There is nothing ad hoc about them and ML-style rank 2 parametric polymorphism can support GADTs easily. There is even no runtime cost for using GADTs (and potential savings) if you are careful.
<mrvn> I guess one has to learn haskell and use them to understand them.
<kaustuv> To give you a simple flavour of its power, see:
<kaustuv> data Monad a where
<kaustuv> Return :: a -> Monad a
<kaustuv> Bind :: Monad a -> (a -> Monad b) -> Monad b
<kaustuv> et voila, the Monad class is now a datatype.
<kaustuv> Anyway, gotta run.
kaustuv is now known as kaustuv_
thelema_ has quit [Read error: 110 (Connection timed out)]
psnively has joined #ocaml
Alpounet_ has joined #ocaml
Alpounet has quit [Nick collision from services.]
Alpounet_ is now known as Alpounet
sporkmonger has joined #ocaml
ygrek has joined #ocaml
jbms has quit [Read error: 113 (No route to host)]
OChameau has quit [Read error: 113 (No route to host)]
psnively has quit []
kaustuv has joined #ocaml
thelema_ has joined #ocaml
Snark_ has quit ["Ex-Chat"]
jamii_ has joined #ocaml
Yoric[DT] has joined #ocaml
_andre has joined #ocaml
<mrvn> http://paste.debian.net/32155/ Which style do you think is better? base/foo or base2/foo2?
j_lenorm has joined #ocaml
<j_lenorm> what version of gtk does lablgtk need?
jbms has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
j_lenorm has quit [Remote closed the connection]
<_andre> i'm using the makefile at http://codepad.org/SPXP8odv but when i run the binary, it can't find the .cmo and .cmi files installed by ocamlfind
<_andre> is there anything i can do to make it look up the files in the correct directory?
<_andre> (it looks for them in /usr/lib/ocaml/3.10.0 but findlib installed them in /usr/local/lib/ocaml/3.10.0)
oriba has joined #ocaml
ygrek has quit [Remote closed the connection]
<jbms> What is the best way to add rules to an omake file to generate the mli files from existing ml files?
<mrvn> jbms: why do that?
<jbms> It seems like it would be cleaner to keep it all in one file
<jbms> is that not standard practice?
hardcoding has quit ["Leaving"]
sporkmonger_ has joined #ocaml
<mrvn> jbms: afaik you only need an .mli file if that should differ from what the .ml exposes, when you want to hide some internal types or functions.
<jbms> yes
seafood has joined #ocaml
<jbms> but I can achieve that by ascribing a signature to module definitions
<jbms> still, I see your point that it makes more sense to just generate it once and modify the generated file
sporkmonger_ has quit [Client Quit]
<mrvn> jbms: you can?
<mrvn> I know you can do module M : sig ... end = struct ... end. But how do you do that for foo.ml itself?
sporkmonger has quit [Read error: 110 (Connection timed out)]
Camarade_Tux has joined #ocaml
<jbms> well indeed, it only works for modules, I think
<jbms> (but often a file will consist entirely of module definitions)
<mrvn> I hardly ever have that.
<mrvn> jbms: you do know that you can create subdirs and put ml files in there, right?
<jbms> eh sure
<jbms> but the subdirectories are just a way of organizing files, right?
<jbms> ocaml doesn't care about them in any way?
seafood has quit []
sporkmonger has joined #ocaml
<mrvn> I do remember foo/bar.ml being module Foo.Bar
<mrvn> can't reproduce it with a simple testcase now though.
<hcarty> mrvn: That may be something ocamlbuild supports - http://brion.inria.fr/gallium/index.php/Using_internal_libraries
Yoric[DT] has joined #ocaml
xian has left #ocaml []
<mrvn> hcarty: I thought that when you use Foo.Bar.x then ocamlc/opt would check foo.cmi and foo/bar.cmi.
<hcarty> mrvn: I have not tried
<mrvn> File "test.ml", line 1, characters 8-17:
<mrvn> Error: Unbound value Foo.Bar.x
<mrvn> mrvn@frosties:~/t% cat foo/bar.ml
<mrvn> let x = 1
sporkmonger has quit []
itewsh has quit [Remote closed the connection]
seafood has joined #ocaml
Associat0r has joined #ocaml
Associat0r has quit [Read error: 104 (Connection reset by peer)]
koppology has joined #ocaml
palomer has joined #ocaml
<palomer> I've just spent the last 3 days trying to get lablgtk to work on my school labs
<palomer> 3 days!
<mrvn> Takes me 60 seconds to ssh home and just work there.
<palomer> im doing gui stuff
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
Camarade_Tux has joined #ocaml
Alpounet has quit ["Ex-Chat"]
<mrvn> so I add -X to the commandline
seafood has quit []
seafood has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
seafood has quit []
thermoplyae has joined #ocaml
tomaw has quit [Read error: 104 (Connection reset by peer)]
tomaw has joined #ocaml
willb has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
seafood has quit []
hkBst has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
palomer has quit ["Leaving"]
seafood has quit []
koppology has quit [Read error: 113 (No route to host)]
jbms has quit [Read error: 110 (Connection timed out)]