gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
myu2 has quit [Remote host closed the connection]
elehack has joined #ocaml
<lewis1711> is it possible at all to define an arbitrary numeric type?
<lewis1711> type rating = 1..5 of Int;;
<lewis1711> something like that
<elehack> lewis1711: not really, particularly with constraints.
<elehack> the closest you can come is a private type
<elehack> and that way your constructor/conversion functions can verify the extra constraints.
<lewis1711> looking at it now
sepp2k has quit [Quit: Leaving.]
myu2 has joined #ocaml
myu2 has quit [Remote host closed the connection]
<thelema> lewis1711: module Rating : sig type t = abstract int val to_int:t->int val of_int:int->t end = struct type t = int let of_int x = x let to_int x = x end
<thelema> oops, forgot to require 1..5
<thelema> let of_int x = assert (x >= 1 && x <= 6); x
<flux> abstract int? you mean private?
<thelema> yes, that too
<flux> time to go sleep?-)
<thelema> I was just today re-reading my old thread on doing exactly this
<thelema> it's been a long day
zzz_ has quit [Ping timeout: 272 seconds]
zzz_ has joined #ocaml
dooode has quit [Ping timeout: 265 seconds]
elehack has quit [Ping timeout: 264 seconds]
elehack has joined #ocaml
Associat0r has joined #ocaml
Amorphous has quit [Ping timeout: 272 seconds]
joewilliams is now known as joewilliams_away
Amorphous has joined #ocaml
Associat0r has quit [Quit: Associat0r]
elehack has quit [Quit: Farewell, programs.]
myu2 has joined #ocaml
yroeht has quit [Ping timeout: 240 seconds]
<eye-scuzzy> moin
<strlen> so a stupid question about a first class module...
<strlen> suppose i use a functor to make a module with a signature
<strlen> and then i'd like to pass that module to a function
<strlen> i am looking through that doc and it seems to handle modules that aren't made by a functor
<strlen> but what about those that are? having some issues... one sec let me get a compiler error message
yroeht has joined #ocaml
<strlen> https://gist.github.com/805455 <-- here is the code and the error message
<strlen> is there an elegant way to do what i am trying here
<strlen> namely pass a created module to a function that uses it as just an implementation
<strlen> (without creating another functor which and then doing "with heap_t = LeftistHeap.t" etc...)
yroeht has quit [Ping timeout: 240 seconds]
yroeht has joined #ocaml
yroeht has quit [Ping timeout: 250 seconds]
ikaros has joined #ocaml
arubin has joined #ocaml
ulfdoz has joined #ocaml
yroeht has joined #ocaml
jcwjcw_ has joined #ocaml
<jcwjcw_> question: How do I say that a function takes a param p of record type my_record
<jcwjcw_> my_record has an x, y and x field
<jcwjcw_> Inside the function, I should be able to access p.x
<jcwjcw_> p.y
<jcwjcw_> p.z
arubin has quit [Quit: arubin]
ymasory has quit [Quit: Leaving]
eye-scuzzy has quit [Ping timeout: 240 seconds]
ikaros has quit [Quit: Leave the magic to Houdini]
eye-scuzzy has joined #ocaml
ulfdoz has quit [Ping timeout: 260 seconds]
Yoric has joined #ocaml
<flux> let foo p = p.x + p.y
<strlen> ah i think i got my situation figured out a bit
joewilliams_away is now known as joewilliams
<strlen> https://gist.github.com/805455 <-- updated the gist -- any way to make it even more elegant?
Snark has joined #ocaml
oriba has joined #ocaml
<oriba> hi. I'm using vim and want to try omlet, a different syntax support
<oriba> someone here who also uses it?
<oriba> I hae installed it, but don't know how to activate, or to check if it's already running....... any vim experts here?
<jcwjcw_> what's omlet!
<jcwjcw_> hey oriba
<oriba> hey jcwjcw_
<jcwjcw_> what syntax?
<oriba> ?
<jcwjcw_> the alternative ocaml syntax
<oriba> I talk about vim editor
<jcwjcw_> ocaml has multiple syntaxes
<jcwjcw_> oh
<jcwjcw_> i see
<jcwjcw_> yah.. do you know how to get autocomplete?
<oriba> the highlighting I use has some problems with many comments, especially if mixed with ocamlyacc-stuff, when there is (* *) as well as /* */
<oriba> autocomplete?
<oriba> never use that
<oriba> I also had to look for it
<oriba> do you use that? you use vim also?
edwin has joined #ocaml
Yoric has quit [Quit: Yoric]
<jcwjcw_> I use vim
<jcwjcw_> can't find autocomplete for it
<jcwjcw_> might switch to f# to get that in visual studio
ttamttam has joined #ocaml
<oriba> jcwjcw_, as mentioned, I don't use that feature, but there might be some articles...
<oriba> jcwjcw_, ah, just tried word completion... works out of the box.... but I type faster without that
avsm2 has quit [Ping timeout: 246 seconds]
<lewis1711> jcwjcw_: geany has autocomplete, and ocaml syntax highlighting
<jcwjcw_> word completion is not auto completion
<lewis1711> it's more of an editor than an IDE though
<lewis1711> right
<jcwjcw_> autocompletion will let you say match x with
<oriba> if I need completion for things like "match" for example, this is more typing with the completion stuff...
<jcwjcw_> then it expands out ALL of the options.
<jcwjcw_> rihgt
<oriba> jcwjcw_, look at the article
<lewis1711> just keep using vim like a man
<jcwjcw_> I do use vim like a man
<oriba> glorious ;)
<jcwjcw_> While hunting
<oriba> ex mode?
<jcwjcw_> Kill a dear, hack up some ocaml
<jcwjcw_> then fix my engine
avsm2 has joined #ocaml
<oriba> let f x y = match .... [ autocompletion... would say match x? ] ... :P
<jcwjcw_> if you said x, then it could use type inference to tell all the possible states
<jcwjcw_> in the "enum"
<oriba> hmhh
<oriba> maybe this can be done when using tags also
<oriba> but I never tried it
<oriba> afaik some colleagues used it with python
lewis1711 has left #ocaml []
ftrvxmtrx has quit [Quit: Leaving]
<strlen> https://github.com/afeinberg/ocaml-pfds/blob/master/lib_test/TestHeaps.ml -- okay, i think i finally get first class modules. is this a correct application of them?
orion1010 has joined #ocaml
<strlen> in terms of libraries for amazon web services, i see barko/aws and williamleferrand/aws-ocaml. any specific preference between the two here?w
<gildor> strlen: williamleferrand uses it for sure, I don't know about barko
oriba has quit [Quit: Verlassend]
<strlen> they both seem recently updated
<thomasga> strlen: williamlefferrand uses ocsigen, barko's one is self-contained
<thomasga> but barko uses it as well
<thomasga> sorry, barko = cohttp
Yoric has joined #ocaml
<thomasga> (and a little bit of ocamlnet which can be replaced)
<thomasga> (or not)
<jcwjcw_> Does anyone know how to extend a Variant from what is already declared?
<jcwjcw_> Like "append" to it?
<gildor> you mean like type t = Foo of int | Bar of string
<gildor> and add Baz of float ?
mfp_ has quit [Ping timeout: 250 seconds]
<avsm> thomasga: did you have a cohttp tree with the ocamlnet/pcre dependency removed? i was updating cohttpserver for a student and noticed it's way out of date
<thomasga> avsm: no I haven't pushed back the changes from mirage to my tree, I need to do it ...
<thomasga> will do it now
<avsm> i'll sort out a release when you do. that library has too many darn users now ;)
ftrvxmtrx has joined #ocaml
yroeht has quit [Quit: leaving]
Yoric has quit [Ping timeout: 255 seconds]
hto_ has joined #ocaml
hto__ has joined #ocaml
hto__ has quit [Client Quit]
hto_ has quit [Client Quit]
Yoric has joined #ocaml
orion1010 has quit [Quit: Lost terminal]
yroeht has joined #ocaml
avsm has quit [Quit: Leaving.]
mfp has joined #ocaml
eye-scuzzy has quit [Quit: leaving]
eye-scuzzy has joined #ocaml
eye-scuzzy has quit [Client Quit]
eye-scuzzy has joined #ocaml
_andre has joined #ocaml
<gildor> adrien: Current Aggregate Statistics for All Time (forge.ocamlcore.org)
<gildor> Site Views 1,323,974
<gildor> Downloads 3,275
<gildor> and it only accounts for the last month (after the migration in fact)
<adrien> heheh, that's awesome :-)
<adrien> and you'd have to add all the SCM operations too
<flux> how much accounts for search engines?-)
<gildor> flux: should be none, it uses awstat AFAIK
<gildor> moreover the number of page viewed by project is not flat
<gildor> and quite representative
<gildor> e.g. Batteries or OASIS -> 4300 pages viewed
<gildor> and CamlSpikes 171
<gildor> yypkg -> 1039 pages viewed
<adrien> \o/
<adrien> thanks ;-)
eye-scuzzy has quit [Quit: leaving]
ftrvxmtrx has quit [Remote host closed the connection]
<gl> good morning #ocaml
<gildor> hi gl
seafood has joined #ocaml
eye-scuzzy has joined #ocaml
Snark has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
<jcwjcw_> hey guys
<jcwjcw_> quick question
eye-scuzzy has quit [Quit: leaving]
<jcwjcw_> how to you represent "any" type
<jcwjcw_> not 'a
<jcwjcw_> not 'b
<jcwjcw_> but any type
eye-scuzzy has joined #ocaml
Snark has joined #ocaml
<jcwjcw_> seafood?
<jcwjcw_> adrien?
<jcwjcw_> The reason why you'd want to do this..
<jcwjcw_> Is you might have a list of objects
<jcwjcw_> each of the object's type is (x*int*y)
<jcwjcw_> You know that the middle is int, but you don't care about the ends
<jcwjcw_> gildor do you know?
<gl> the comments are interesting, in this post
<strlen> yep
<strlen> i think hiding in a ref seems to best way to do it
<jcwjcw_> hmm.
<jcwjcw_> I'm such a n00b
<jcwjcw_> why wouldn't ocaml have a top level type
<jcwjcw_> the equivalent of Object in java
<jcwjcw_> makes so much sense
<f[x]> 'a is precisely what you if you don't care
<f[x]> makes no sense at all
<jcwjcw_> It helps you structure your types so powerfully
<jcwjcw_> I want to define this:
<jcwjcw_> a list
<strlen> java didn't originally have polymorphic variants
<strlen> and even now polymorphism is much weaker
<jcwjcw_> where each obect in the list consists of a 3-tuple
<strlen> that's why java has 'Object'
<jcwjcw_> the middle element is an int
<jcwjcw_> I don't care what the others are
<gildor> jcwjcw_: you can probably do something with property list
<strlen> right
<strlen> there's likely better ways to do this
<f[x]> ('a * int * 'b) list
<jcwjcw_> the goal is to NOT bypass the type system
<strlen> gildor: ah interesting
<jcwjcw_> wait f[x]
<jcwjcw_> your example won't work
<strlen> looks like the discussion in the jane street blog
<jcwjcw_> 'a*int*'b
<mfp> jcwjcw_: what's wrong with ('a * int * 'b) list for your use case?
<jcwjcw_> i can't have a list of them
<mfp> what do you mean?
<jcwjcw_> where the ends may vary
<jcwjcw_> It's like the middle part is the interface
<jcwjcw_> the api
<jcwjcw_> the contract
<jcwjcw_> the outer parts might vary.
<jcwjcw_> I won't touch them so it doesn't matter
<mfp> do you want the "outer types" to change across list elements
<jcwjcw_> In my world.. (srting, int, string) is a subtype of (*, int, *)
<mfp> or "globally" in the whole list?
<jcwjcw_> and so is (int, int, string)
<f[x]> how would this list be useful?
<jcwjcw_> I don't care if they change
seafood has quit [Ping timeout: 265 seconds]
<jcwjcw_> It is useful in my program
<f[x]> how?
<mfp> jcwjcw_: if you have functions that only use the 2nd element, they won't care about the 1st or the 3rd
<jcwjcw_> It was so useful that they put something similar into the object system
<f[x]> how are you going to access 1st and 3rd elements?
<jcwjcw_> mfp correct
<jcwjcw_> I won't
<strlen> yep
<f[x]> so why does it exists at all?
<strlen> then you don't need an 'object' type here
<mfp> jcwjcw_: then ('a * int * 'b) list is OK
<jcwjcw_> Because something made them that way
<mfp> let foo (a, b, c) = (a, b + 1, c);;
<f[x]> how is that something going to use it?
<mfp> val foo : 'a * int * 'b -> 'a * int * 'b = <fun>
<jcwjcw_> I'm going to access the middle element
<jcwjcw_> I need to define a type
<jcwjcw_> that is List of (anything, int, anything)
<jcwjcw_> because I'm going to operate on that list
<f[x]> this list is nonsense
<jcwjcw_> No it's not
<jcwjcw_> It's part of a larger type def
<mfp> foo works with any ('a * int * 'b), and the 1st and 3rd elements can be set to anything
<jcwjcw_> but now i need to define a type that is:
<f[x]> answer the question : how anybody is going to use 1st and 3rd elems of the list
<jcwjcw_> they won't
<f[x]> so why does it exist??
<gildor> jcwjcw_: does your list contain at the same time (string * int * string) and (float * int * float) ?
<jcwjcw_> but the objects exist
<jcwjcw_> yes
<jcwjcw_> it may
<mfp> jcwjcw_: you see, everybody is trying to get you to justify the need for an universal type instead of just a polymorphic type ('a * int * 'b) list :)
<jcwjcw_> To be clear
<jcwjcw_> :
<jcwjcw_> I need something that is of the form:
<f[x]> I give up
<gildor> what is the purpose of this list ?
<jcwjcw_> Type thingy = Node | (x, x->int, y)
<gildor> jcwjcw_: ^^^
<f[x]> gildor, bwahaha
<f[x]> dejavu
<jcwjcw_> am i missing something?
<jcwjcw_> a list of those
<jcwjcw_> so a "thingy list"
<jcwjcw_> where each element, in the list is of the form thingy
<gildor> jcwjcw_: most of the time, OCaml people try to avoid universal types (for good reason)
<jcwjcw_> but each element could have a different x
<jcwjcw_> Sure, but a universal type is just a way to solve my problem
<jcwjcw_> there could be another solution.
<jcwjcw_> Called the i don't care because i won't touch it type
<mfp> OK, so you want an existential type
<jcwjcw_> well i suppose i might touch it.
<jcwjcw_> Ill pass the first into the middle
<jcwjcw_> do you see?
<jcwjcw_> (I don't know what existential is)
<f[x]> so use the list of objects, not tuples
<jcwjcw_> I love static type systems
<jcwjcw_> wait
<jcwjcw_> f[x]
<jcwjcw_> what do you mean
<jcwjcw_> For each element in the list, I'm going to stick the first thing into the second
<jcwjcw_> I need it to be type safe, so it needs to be of that form
<jcwjcw_> I like that.
<jcwjcw_> And this *is* type safe
<jcwjcw_> if ocaml would let me express this type
<jcwjcw_> This should totally be doable
<mfp> jcwjcw_: if you're not going to use x directly, besides applying the 2nd element to it, you can as well have a (unit -> int * 'b) list
<mfp> where the unit -> int function just sticks x into the x -> int function you had
<jcwjcw_> hmmm wrap it in a closure
<jcwjcw_> preprocess the list
<jcwjcw_> and mfp. What if I didn't want to stick it in
<mfp> it'll only be applied when you do match x with (f, _) -> f ()
<jcwjcw_> Even if i didn't want to stick it in
<jcwjcw_> the 'b kills it
<jcwjcw_> I still cant have a list with different 'bs
<jcwjcw_> right/
<jcwjcw_> ?
<jcwjcw_> type 'b listything = (unit-> int, 'b)
<jcwjcw_> I can't have a list of those
<jcwjcw_> where b varies
<gildor> jcwjcw_: I'll do a property list
<jcwjcw_> so bypass the type system :)
<jcwjcw_> eff that.
<jcwjcw_> I'll try a thousand years before admitting defeat
<gildor> jcwjcw_: type listything = (int * prop_data) list
<gildor> jcwjcw_: you don't really bypass the type system
<jcwjcw_> really i thought that was like a hash map
<gildor> jcwjcw_: you'll still have type checking
<gildor> jcwjcw_: this is a hash map
<jcwjcw_> gildor this is something that a good type system should allow me to express
<gildor> but the type is hold by the variable that retrieves the data
<jcwjcw_> Even java has this
<gildor> java go trough Object, I think
<gildor> isn't it ?
<jcwjcw_> A couple of ways.
<jcwjcw_> Either that.
<jcwjcw_> Or there would be an interface
<jcwjcw_> that only exposes the middle information
<gildor> going through Object is a real violation of the typesystem
<jcwjcw_> makes no claims about the first and third
<jcwjcw_> No it's not
<strlen> Java has an 'object' type because it lacked polymorphism until 1.5
<jcwjcw_> Purely static
<jcwjcw_> Using it in that sense is
<jcwjcw_> And casting
<jcwjcw_> but in this case
<mfp> jcwjcw_: the downcast you'll do eventually in order to use the elements is not static
<jcwjcw_> It would not be
<jcwjcw_> I'll NEVER use it though
<gildor> you have to cast the object, which implies keeping type information at runtime
<jcwjcw_> I'll never downcast
<strlen> 'object' is essentially from the same opera as 'null'
<jcwjcw_> No strlen that is so wrong
<jcwjcw_> (not to be rude)
<f[x]> oh what a pretty wtf show
<jcwjcw_> null is a subtype of anything
<jcwjcw_> anything is a subtyp of object
<jcwjcw_> complete opposite actually
<mfp> jcwjcw_: somebody will, eventually, if the elements are to be used in a non-trivial way (using a method not in Object)
<jcwjcw_> I could have a class with three methods getFirst
<jcwjcw_> getSecond
<jcwjcw_> getThird
<strlen> to get something out from an object you have to up cast.. that creates an issue
<strlen> (from an object)
<jcwjcw_> I make an interface called getSecond();
<jcwjcw_> getSecond<Int>
<jcwjcw_> thousands of classes could impement that
<jcwjcw_> whether or not their third attribute is string/int/whatever
<mfp> can you use 3.12? You can encode existential types quite easily by using first-class modules
<jcwjcw_> It's funny that java's type system is more powerful than ocaml's in this case
<jcwjcw_> yes!
<jcwjcw_> I'll take a look
<mfp> module type S = sig type a type b val x : a * (a -> int) * b end;;
<mfp> let mk (type _a) (type _b) (a : _a) f (b : _b) = let module M = struct type a = _a type b = _b let x = (a, f, b) end in (module M : S);;
<jcwjcw_> Could you explain in one sentance what they are?
<mfp> modules that can be passed around as any other value
<gildor> mfp: maybe objects are better in this case ?
<jcwjcw_> gildor they would accomplish this
<jcwjcw_> but I don't see why we can't have this power without them
<gildor> jcwjcw_: so use them
<jcwjcw_> Nah.. Trying to not
<gildor> jcwjcw_: well good lucj
<gildor> luck
<jcwjcw_> thanks!
<jcwjcw_> being able to do this, has nothing to do with objects/encapsulation/state
<jcwjcw_> it is a pure subtyping problem
<strlen> well here's you're essentially using dynamic dispatch
<strlen> dynamic dispatch in objects can often get you to the same result
<strlen> it's late and i am not too lucid, sorry
<strlen> existential types is another way if you want to avoid objects
<jcwjcw_> It would be great if the type system just allowed matches.
<jcwjcw_> Like List of <%x, int, %x>
<jcwjcw_> x is not something I specify but just a constraint on the form of each element in the list
<jcwjcw_> Any of you know the ocaml guy?
<jcwjcw_> You know.. It might just be the case, that as long as i don't try to define the types.
<jcwjcw_> Ocaml is just smart enough to know that I only have a restriction on the middle element!
smerz has joined #ocaml
<mfp> jcwjcw_: I believe what you want to do can be expressed with existential types (the easiest way being to use first-class modules) or objects, but apparently none of us really understands what you're trying to do exactly so it seems you're on your own :)
<jcwjcw_> I think we all understand, but ocaml doesn't offer a nice solution
<mfp> well, you said Java has got one, but the mechanism you used (subtyping) is not lacking in OCaml, so ?
<jcwjcw_> subtyping is lacking in the non-object part of ocaml
<jcwjcw_> which is very strangs
<jcwjcw_> *strange
<jcwjcw_> Seems like that should be the basis, upon which objects are built
<jcwjcw_> imho objects should be simple convenience wrappers around a more flexible low level subtyping system
<gildor> mfp: did you have time to do a release of ocaml-sqlexpr with detached thread ?
<gildor> mfp: a 0.4.0 release ?
<mfp> gildor: 1 sec
<mfp> gildor: I'm also switching to batteries in the process
<mfp> it's needed for estring anyway
<gildor> gildor: you depend on extlib before ?
<gildor> mfp: ^^^
<mfp> yes, I originally linked against extlib
<mfp> IIRC batteries was not packaged in the Debian when I first wrote this
<mfp> -the
<gildor> mfp: ok great, I will finish by replacing extlib by batteries
<mfp> what do you mean?
<mfp> I've already pushed the commit that does extlib -> batteries
seafood has joined #ocaml
<gildor> mfp: AFAIK, batteries contains an updated extlib
<mfp> yes, you can just use open Extlibcompat (or something) but then this links the whole lib
<mfp> so I used BatXXX directly in order to minimize the footprint
<gildor> mfp: until now I used extlib, because it was simple, but I'll switch to batteries
<mfp> ah, you mean in some codebase of yours?
* mfp uploading 0.4.0 tarball
<gildor> mfp: in some codebase -> yes
<gildor> mfp: I also need to learn batteries in fact
* gildor ashamed
* adrien needs to learn more oasis, ashamed too
<gildor> adrien, mfp: at least there are still things to learn in the OCaml world ;-)
<mfp> to start with, you can use batteries as extlib + some Enum and print stuff per module, I guess
<adrien> there has been enough activity in the ocaml world recently to keep me busy, that's for sure
<mfp> ocaml-sqlexpr 0.4.0 tarball https://forge.ocamlcore.org/frs/?group_id=190
<mfp> hope I won't need a quickfix 0.4.1 :)
myu2 has quit [Remote host closed the connection]
myu2 has joined #ocaml
<gildor> mfp: what time it is for you ?
<mfp> same timezone as you, CET (12:40)
<gildor> mfp: ok, will see this in the afternoon so
<gildor> mfp: I don't see any reference to Batteries into 0.4.0
<mfp> hmm did I upload the wrong tarball
* mfp checks
myu2 has quit [Ping timeout: 240 seconds]
<gildor> mfp: grep -r "Bat" * -> nothing
<mfp> yes, I didn't regenerate the tarball after the last commit correctly, re-uploading
seafood has quit [Quit: seafood]
<mfp> re-uploaded & double-checked
jcwjcw_ has quit [Ping timeout: 265 seconds]
ikaros has joined #ocaml
f[x] has quit [Ping timeout: 264 seconds]
f[x] has joined #ocaml
smerz has quit [Quit: Ex-Chat]
rixed has quit [Quit: rebooting]
rixed has joined #ocaml
eye-scuzzy has quit [Quit: leaving]
eye-scuzzy has joined #ocaml
Yoric has quit [Read error: Connection reset by peer]
Yoric has joined #ocaml
sepp2k has joined #ocaml
myu2 has joined #ocaml
jm has joined #ocaml
eye-scuzzy has quit [Quit: mimimi]
ikaros has quit [Ping timeout: 260 seconds]
ikaros has joined #ocaml
<flux> soo, I've taking a look at XCB, the new(er than libX11) X interfacing library
<flux> and I found there's been some discussion on generating ocaml bindings with the same technology (that is, from xml descriptions)
<flux> I guess nobody's actually done it?-)
<adrien> well, qtcaml reads gcc-xml's output
<flux> but it's different. qtcaml uses it for generating bindings.
<flux> in the XCB solution one would actually construct/deconstruct messages based on the XML.
<adrien> you have examples?
<flux> actually I think those are only for extensions..
<flux> but still a big part of actually doing something with X :)
<adrien> hmm, they most probably agree on some kind of IPC/RPC/whatever which is not described here (to map the names to the actual in-memory representation)
<flux> how is it not described there? of course, various things have a meaning there, but they for example mention data sizes (ie. CARD16) and command numbers (opcode="4")
<flux> it's not described down to the lowest level, but what is shown there is what goes into the message (in addition to some other stuff)
<adrien> flux: right, I was under the impression it lacked some details but actually less than I initially thought (the transport is missing, but that's it)
<adrien> transport/lowest level
<adrien> flux: are you aware of a formal specificatin for the xml format? (a dtd for instance)
<flux> adrien, well, there is a python script..
<flux> actually there's a document as well
<flux> actually it seems everything is covered by those files..
drunK has joined #ocaml
<adrien> I was looking for the definition of "card8"
* f[x] used to generate wrappers for dbus calls from introspection xml data, guess it is a common approach
<flux> adrien, a byte
<flux> perhaps they are defined in even older X documentation, if not there
<flux> hm, I think an unsigned byte actually
<adrien> I hate that they don't validate their xml files against a strong definition: you always end up discovering new types and that makes your code awful =/
Associat0r has joined #ocaml
rudi_s has quit [Ping timeout: 246 seconds]
eye-scuzzy has joined #ocaml
ttamttam has quit [Quit: ttamttam]
ttamttam has joined #ocaml
ttamttam has quit [Client Quit]
ttamttam has joined #ocaml
Yoric has quit [Ping timeout: 255 seconds]
Yoric has joined #ocaml
Yoric has quit [Read error: Connection reset by peer]
rudi_s has joined #ocaml
gmarik has joined #ocaml
bzzbzz has joined #ocaml
Yoric has joined #ocaml
Yoric has quit [Client Quit]
ikaros has quit [Quit: Leave the magic to Houdini]
jado has joined #ocaml
<jado> hello, how can i create a token for 'string' http://www.lri.fr/~marche/tpdb/format.html? my token for 'id' was: "| (['A' - 'Z'] | ['a' - 'z'] | ['0' - '9'] | '_' | '\'')+ as i { ID (i) }"
<flux> I typically have something like | '\'' { insert code for lexing strings properly here }
<flux> it's tricky if you have escaping etc
<flux> I don't remember the negation syntax, but that should work too. | '\'' (( not '\'' ) * as i) '\'' { STR(i) }
<flux> possibly something like [ ^ '\'' ], but not sure really..
<jado> with double quotes? \"?
<flux> '"' ?
<gildor> jado: | '"' { str lexbuf }
<flux> or "\" string \""
<jado> flux: yes ok
<jado> gildor: ?
<gildor> and define str as 'and str = parse | '\\' _ as esc { ... }
<gildor> even better, use a buffer for that
<gildor> jado: you want to parse string between "..." ?
<jado> no i just want a token, but at the end i will ignore it
<gildor> using a second lexer to parse string should work
<gildor> ie. rule token = parse ... and str = parse ...
<gildor> and you call str when you encounter the start of a string
<jado> gildor: ok i see, and how i make str look for the next '"'? just | '"' { STRING }?
<gildor> indeed, this will return STRING
<gildor> and you can | _ { str lexbuf } to ignore all other char
<jado> yes ok
<gildor> put | '\\' _ { str lexbuf } before to not ignore escaped char
<gildor> (e.g. "\"")
<jado> if i would have wanted the content, i would have to use negation right?
<gildor> no
<gildor> you would have use an additional argument to the str rule
<gildor> and str buf = parse
<jado> yes the negation is actually done by the matching
<gildor> | '\\' _ as esc { Buffer.add_char buf esc; str buf }
<gildor> | _ as c { Buffer.add_char buf c; str buf }
<gildor> | '"' { STRING (Buffer.contents buf) }
<gildor> (invert the two last rule in fact)
<jado> yes i see thanks
<thelema> http://ocaml.pastebin.com/83V8Q6Gn <- please help w/ super-optimizing my inner loop
ccasin has joined #ocaml
<flux> ..drop the polymorphic variants?
<flux> but, off from irc for a while :)
<thelema> I thought they were pretty much the same as regular variants, except for the extra indirection sometimes
<thelema> and the types involved are ugly
<mrvn> gildor: _ as c is the same as c
<mrvn> or where does that come from?
<thomasga> avsm: I've push my changes to my cohttp tree (quite a lot of tweaks actually) -- will make it version 1.0 when it will be a bit more tested
<thelema> wow, removing one unneeded indirection and annotating a type as int has dropped the runtime from 3.03s to 1.89s
<thelema> (and de-tupling some arguments)
ikaros has joined #ocaml
<mrvn> the first and the last saves allocs, GC work and indirections. The int can prevent generic functions from being used where special int flavours are known. Makes a big difference with Bigarray for example.
<mrvn> Such a speedup is no big surprise. If you happen to shrink below the cache size due to something like that you can get much more.
<thelema> mrvn: yup, I was comparing that value, int compares are significantly cheaper than polymorphic compares
<thelema> switching from polymorphic variants to plain variants seems to have had much less performance change (sadly, not isolated)
<thelema> although this change does mean I can remove the unnatural annotation on my int
<jado> now what if i want to parse 'id' exactly as it is specified negatively and not positively? i can write 'rule token = parse ... and id = parse ...' but what should i do if i encounter a parenthesis in 'id'? i could returns ID(Buffer.contents lexbuf) but then i'm losing the parenthesis
<jado> the code that you posted (gildor) at 16:37 is weird: you add c to the buffer, and calls str on it again?
<mrvn> thelema: polymorphic variants just use more memory. I don't see where they should be slower otherwise.
<jado> also, my code is using Lexing and not Buffer so this does not compile: http://ocaml.pastebin.com/JwSBVSpV; the code is also probably wrong because 'id' ignore the first character :(
<gildor> jado: use a regexp for id, far more simple
<jado> where is the syntax used for the regexps of menhir?
<gildor> jado: I can add a char to buf and call it again, because Buffer is modified in place
<gildor> jado: I don't know menhir
<thelema> http://ocaml.pastebin.com/18MxbJMn <- more optimized version - thanks all
ounit has joined #ocaml
<gildor> whois ounit
* adrien lost precise location of exception and is now getting Assert_failure("/tmp/caml*", *, *), perfectly useless
<ounit> gildor: ubuntu and ounit, is both me
rixed has quit [Ping timeout: 240 seconds]
<gildor> any relation to ounit ?
<ounit> gildor: only my question
<ounit> or better said questions
<jado> the documentation of http://gallium.inria.fr/~fpottier/menhir/ doesn't talk about negation in regular expressions :/
rixed has joined #ocaml
<ounit> i made ocamlbuild ocamlc -package oUnit ... but it replies ounit not found
<gildor> jado: AFAIK, menhir is a replacement for ocamlyacc, not ocamllex
<gildor> jado: and we are talking about lexer
<gildor> ounit: you have to install it
<ounit> from where?
<thelema> ounit: ocamlfind list | grep oUnit
<thelema> ounit: I'm sure you can google ounit to get the download
<gildor> or just follow the link I give you 10 lines before
ftrvxmtrx has quit [Quit: Leaving]
<ounit> thanks a lot, again, but now i have unbound Graph as an error
<ounit> i have -I folder1/graph.ml
drunK has quit [Remote host closed the connection]
<ounit> someone a idea?
rks has quit [Quit: foo]
<thelema> ounit: what's the whole command?
<gildor> ounit: just -I folder1 will do
<ounit> thelema: ocamlfind ocamlc -package oUnit -I /folder1 test.ml -o test
<thelema> /folder1? don't you mean ./folder1 or just folder1/?
<ounit> ocamlfind ocamlc -package oUnit -I folder1/ test.ml -o test , that doesnt work either
<thelema> without any /?
<ounit> still unbound module error
oriba has joined #ocaml
<thelema> ah, have you compiled graph, or is there only graph.ml in folder1/?
<thelema> mrvn: I think I just fit inside the cache - I noticed that two arguments were just carried along together, and put them in a single tuple. This increased performance by about 33%
<mrvn> hehe.
<ounit> thelema: thanks that module problem is solved
<ounit> thelema: i have several modules in one file how do i call them out of my ounit test file
<thelema> Filename.Modulename
<thelema> Filename.Modulename.value_name
<ounit> Reference to undefined global `Filename'
<thelema> not literally "Filename" - if your file is called graph.ml (and has been compiled), and it has a module called "Edge", with a function in that module "print_name" then "Graph.Edge.print_name"
<ounit> i did that
<ounit> what could be the problem
<ounit> =
<thelema> ounit: I can't guess - pastebin as much as you can and I/we can likely spot the mistake
bp has joined #ocaml
drunK has joined #ocaml
<bp> hi, I have changed the license of a project hosted on the ocaml forge. Does someone know how to change the license in fusion forge too ?
<thelema> bp: gildor might be able to help with that - he runs the ocaml forge
<thelema> bp: he's very responsive to tickets on the forge itself, if he doesn't appear when his name is invoked here.
<bp> maybe someone else knows? gildor said on the ocaml-debian-maint list he would spend less time while now he's got a family
rks has joined #ocaml
ttamttam has quit [Remote host closed the connection]
jado has quit [Ping timeout: 255 seconds]
ski has quit [Ping timeout: 264 seconds]
ski has joined #ocaml
<adrien> bp: try: "admin" -> "edit trove" (it's a button)
<bp> adrien: thanks!
<adrien> had troubles finding it myself when I needed it :P
kaustuv_ has joined #ocaml
cyanure has joined #ocaml
ftrvxmtrx has joined #ocaml
ulfdoz has joined #ocaml
nejimban has quit [Changing host]
nejimban has joined #ocaml
ulfdoz has quit [Ping timeout: 272 seconds]
<gildor> bp: thanks for caring (but I have a family since 3 years already)
<gildor> bp: I would probably spend less time on some debian matters -- in order to still have time to spend on OCaml topics
<gildor> bp: typically I will ask for help on package like unison for which I really don't have time to take care
<gildor> bp: do you solve your license problem ?
eye-scuzzy has quit [Quit: leaving]
ulfdoz has joined #ocaml
eye-scuzzy has joined #ocaml
jonafan_ has joined #ocaml
jonafan has quit [Ping timeout: 240 seconds]
myu2 has quit [Remote host closed the connection]
ygrek has joined #ocaml
ymasory has joined #ocaml
ymasory has quit [Client Quit]
ymasory has joined #ocaml
oriba has quit [Quit: Verlassend]
_andre has quit [Quit: leaving]
jonafan_ is now known as jonafan
ymasory has quit [Remote host closed the connection]
drunK has quit [Remote host closed the connection]
eye-scuzzy has quit [Ping timeout: 272 seconds]
remy_o has joined #ocaml
remy_o has left #ocaml []
elehack has joined #ocaml
<elehack> Anyone want to test a GODI package for PGOCaml for me?
eye-scuzzy has joined #ocaml
eye-scuzzy has quit [Client Quit]
eye-scuzzy has joined #ocaml
eye-scuzzy has quit [Client Quit]
eye-scuzzy has joined #ocaml
eye-scuzzy has quit [Client Quit]
seafood has joined #ocaml
tnguyen has joined #ocaml
<adrien> how to test?
arubin has joined #ocaml
<elehack> in $GODI_LOCALBASE/build/godi, check out the packages with 'svn checkout https://godirepo.camlcity.org/svn/godi-build/trunk/godi/godi-pgocaml'
<elehack> then install the godi-ocaml package.
<elehack> the checkout will prompt to approve the SSL certificate but will not need authentication.
<elehack> adrien: thanks :)
<elehack> and basically just make sure it installs without errors.
tnguyen has quit [Remote host closed the connection]
<adrien> waiting for the build to finish :P
<adrien> built and installed
<elehack> great :)
<elehack> which OS and OCaml version are you on?
<adrien> ocaml 3.12.0, Linux 64bit
<adrien> fastest svn checkout I've ever seen :P
<elehack> lol yeah, package scripts aren't very big.
<elehack> thank you for your time.
<adrien> no problem, always happy to help =)
<adrien> and it looks like I'm going to rebuild almost all my godi packages because of various updates
eye-scuzzy has joined #ocaml
eye-scuzzy has quit [Client Quit]
eye-scuzzy has joined #ocaml
<adrien> well, it built, I could load it, opened a connection, it seems fine =)
<elehack> great :)
rien_ has quit [Read error: Connection reset by peer]
seafood has quit [Quit: seafood]
arubin has quit []
Snark has quit [Quit: Ex-Chat]
ccasin has quit [Quit: Leaving]
ygrek has quit [Ping timeout: 240 seconds]
ulfdoz has quit [Read error: Operation timed out]
dooode has joined #ocaml
edwin has quit [Remote host closed the connection]
Yoric has joined #ocaml
elehack has quit [Quit: Headed out, possibly to home]
jm has quit [Remote host closed the connection]
gmarik has quit [Quit: Leaving.]
bp has quit [Quit: Quitte]
pmangg has joined #ocaml
Yoric has quit [Quit: Yoric]
ikaros has quit [Quit: Leave the magic to Houdini]
sepp2k has quit [Quit: Leaving.]