flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 4.00.1 http://bit.ly/UHeZyT | http://www.ocaml.org | Public logs at http://tunes.org/~nef/logs/ocaml/
eikke has quit [Ping timeout: 248 seconds]
yezariaely has quit [Remote host closed the connection]
yezariaely has joined #ocaml
emmanuelux has quit [Ping timeout: 276 seconds]
cdidd has quit [Remote host closed the connection]
ben_zen has joined #ocaml
ben_zen_ has joined #ocaml
ben_zen_ has quit [Client Quit]
ollehar has quit [Ping timeout: 240 seconds]
darkf has joined #ocaml
cdidd has joined #ocaml
dsheets has quit [Ping timeout: 264 seconds]
tane has joined #ocaml
oriba_ has quit [Quit: oriba_]
madroach has quit [Ping timeout: 248 seconds]
madroach has joined #ocaml
ontologiae has quit [Ping timeout: 276 seconds]
Fnar has quit [Ping timeout: 256 seconds]
ontologiae has joined #ocaml
q66 has quit [Remote host closed the connection]
osnr has quit [Quit: Leaving.]
Fnar has joined #ocaml
ontologiae has quit [Ping timeout: 248 seconds]
raichoo has quit [Quit: leaving]
tane has quit [Quit: Verlassend]
ben_zen has quit [Ping timeout: 260 seconds]
breakds has joined #ocaml
Watcher7 is now known as Watcher7|off
Watcher7|off is now known as Watcher7
Drup has joined #ocaml
talzeus has joined #ocaml
talzeus has quit [Remote host closed the connection]
breakds has quit [Quit: Konversation terminated!]
zpe has quit [Read error: Connection reset by peer]
zpe has joined #ocaml
mattrepl has quit [Quit: mattrepl]
Tobu has quit [Remote host closed the connection]
osnr has joined #ocaml
osnr has quit [Changing host]
osnr has joined #ocaml
Tobu has joined #ocaml
yacks has quit [Quit: Leaving]
shinnya has quit [Ping timeout: 248 seconds]
yacks has joined #ocaml
Kakadu has joined #ocaml
gour has joined #ocaml
ttamttam has joined #ocaml
gour has quit [Disconnected by services]
gour_ has joined #ocaml
gour_ is now known as gour
ttamttam has left #ocaml []
Neros has joined #ocaml
zpe has quit [Ping timeout: 264 seconds]
Kakadu has quit [Read error: Connection reset by peer]
Kakadu has joined #ocaml
foo808 has joined #ocaml
<gour> Kakadu: your qt & wxocaml bindings seems to be quite new and not many people behind it...moreover, my feeling is that ocaml community is not so much interested for GUI apps or let's say less than f#/c#
foo808_ has quit [Ping timeout: 256 seconds]
<gour> and g# is nicely supported...
<gour> lack of utf-8 support out-of-the box is another concern as well as lack of editor/IDE support (i gave up on emacs and use ST2 and there is monodevelop with autocompletion)
<gasche_> gour: it's right that the OCaml community is not that good at GUIs
<gour> gasche_: yeah, unfortunately
<Drup> gour: it's getting better on the IDE side
<gasche_> people have been bridging to other languages to do the UI part of their applications
<gasche_> Java (with OCaml-Java) or C# at Lexifi
<gasche_> that works relatively well, I hear, but indeed native bindings would be interesting
<Drup> I don't think having bindings is enough (mostly, we have them), it's just that you have to rework the paradigm to make it fit into ocaml.
<Drup> (and that's hard :p)
<gour> i'd rather not mix too many languages...otherwise i could stay with python+cython+whatever gui i like
* adrien still believe that it's not that ocaml people don't like/do GUI stuff but mostly incomprehension of the available bindings
<adrien> or lack of knowledge
<gour> hmm...then f# definitely looks as better option for my use-case
<adrien> and a big "issue" is that GUI stuff is imperative while most ocaml programs are going to be functional (at least for the most important part)
<adrien> so that will class at some point
<adrien> and that's where FRP helps
<Drup> adrien: yeah, I think it's the biggest problem
<gour> adrien: but, isn't it the same/similar issue with f# which is also 'functional-first'?
<adrien> I had forgotten about it but it means making your code and design and suddenly things break
<gour> i remember work on FRP from haskell world, but nothing was ready then
<adrien> or making the UI and being forced to adopt an imperative style throughout your code
<adrien> gour: I don't know how F# "solves" that
<adrien> I've seen a number of libs/packages but I have no idea how they fare
<Kakadu> adrien: they write GUI in C# I think
<gour> now, i want to be pragmatic and use practical language to do the job where language is not C(++)
<adrien> as for FRP, I've done some stuff with it (with React) and I've been happy about it
<gour> one can simply use/call GTK# bindings from f#
<Drup> gour: well, If you're happy with that, lablgtk will be enough
<adrien> but then FRP still has two issues: it requires some more design when starting (maybe because there are no FRP design patterns yet so you need to reinvent them)
<gasche_> I personally think that just using GUI bindings in the style of the original library is ok
<adrien> and introductions to FRP are either scarce or too long
<gasche_> (I mean we can write imperative code in OCaml as well, and I think it's ok, especially when it's contained to the GUI area)
<gasche_> we can wait for FRP to be a great, usable idea but in the meantime shouldn't constrain ourselves
<gasche_> that said, gour, if you have tried lablgtk and found gtk# more to your liking, go ahead and use it
<gasche_> (the performances will not be as good, if you're hesitating between this and Python you probably don't care)
<adrien> well it matters when the button press callback is (bool -> unit) and you have no way to update your program state functionaly
<gour> here - http://pastebin.com/NdNztVkL is stub for gtk app created by monodevelop
<gour> Drup: i do not see much activity there...
<adrien> and FRP helps because your callback becomes : ~callback:(fun b -> React.E.send some_react_value (`ButtonXTicked b))
<Drup> gour: maybe because it's stable and don't need any more activity :D
<gour> Drup: afaict, there is even no support for latest 2.x
<adrien> (and if you believe that this is boilerplate and should be automated, don't; I've tried it and ended up Factory Factories)
<gour> how does ocaml's support for parallel/async compare with f#-3.0?
<adrien> gour: I'm a maintainer of lablgtk, although with almost no time for the past year
<adrien> gour: it's mostly that gtk+3 is fairly annoying
<gasche_> gour: currently it's inferior
<adrien> hmmm, which GTK+ version would be an issue?
<adrien> API coverage is not 100% on purpose
<gasche_> gour: we have good things for parallelism but they use multiprocessing instead
<gasche_> (see eg. Parmap)
<gour> adrien: i remember your name in regard to gtk bindings ;)
<adrien> we don't bind APIs noone use and which bitrot
<adrien> :-)
<gasche_> F# code tends to be easier to parallelize, but is also slower to start with
<gasche_> (especially if you use Mono)
<gasche_> so it seems performance-conscious people still rather use OCaml
<gour> recently i looked at two obscure languages and although they're nice as language, ecosystem sucks...that's why i want something which is actively developed/maintained
<adrien> gour: looking at the F# GTK code you linked to, lablgtk code will be very similar
<gour> gasche_: yeah, i'd be using mono being on linux
<adrien> there might be more RAD stuff in F# however
<gour> yep
<adrien> (tbh I've tried to do stuff like that and it didn't end up much simpler while the use of an additional library added some overhead)
<gour> what about utf8 support? it will always stay like 3rd party module? i'm not native speaker and need good i18n support
<adrien> it's in a 3rd party module, yes
<adrien> however the ocaml strings don't care about what you put inthem
<Kakadu> adrien:+1
<Kakadu> In case of simple localization OCaml is OK
<gour> having lablqt in ocaml would be nice
<Drup> not sure about that
<Drup> oh, you mean as a lib ? yeah sure.
<Drup> (I understood "in the standard distribution")
<adrien> well, as long as libraries don't crap themselves because you gave them unicode (which they most probably won't do), it doesn't matter where the unicode support comes from
Yoric has joined #ocaml
<gasche_> gour: note that the unicode displayed here is not specific to Qt
<gasche_> I mean any string can contain unicode in COaml
<gasche_> ^t
<gasche_> the only "detail" is that the usual function of the String module work at the byte level, not at the codepoint level
<gasche_> (so eg. String.length will not return you the width of the string in monospace font, but it's memory-use size)
<gasche_> (and this is where a dedicated UTF8 library kicks in: bringing functions to compute on codepoints)
Kakadu has quit [Ping timeout: 276 seconds]
Watcher7 is now known as Watcher7|off
zpe has joined #ocaml
<gour> gasche_: son one can write proper i28n apps?
<gour> *i18n :-)
<gour> gasche_: in regard to performance, iirc, there was time when ocaml was beating ghc, now to so, right?
zpe has quit [Ping timeout: 256 seconds]
<gour> now, according to language shootout is even behind f#mono...
<gour> actually on multi-core is faster, i see now for e.g. nbody
<adrien> that benchmark game is like the tour de france
<adrien> some have spent a _lot_ of time optimizing for it
<adrien> in some cases the code isn't idiomatic at all
<gour> ada is still fast
<gour> right, both ocaml and f# does not look ver FP :-)
<adrien> hmm, maybe that GHC code there looks FP, maybe a bit too much :p
ggole has joined #ocaml
<gour> :-)
<Drup> is there a clever way to have an optional field in a functor ?
<gasche_> gour:
<gasche_> have a look at the Shootout code
<gasche_> and you'll quickly understand that it does not invalidate, and in fact would tend to support, the fact that *sanely written* code is faster in OCaml than F#
<gasche_> I'll make no statements about Haskell (I believe there are essentially on par, but the problems related to laziness may make non-debugged-to-death Haskell code slower)
<gasche_> hm
<gasche_> well in fact, I had a look at the benchmarks you quote, OCaml is clearly faster than F# mono
<gasche_> what were you referring to, gour?
<gasche_> Drup: when you define modules and functors, clever is the new bad
<gour> gasche_: those language shootout benchmarks
<gasche_> well if I look at http://benchmarksgame.alioth.debian.org/u64/benchmark.php?test=all&lang=ocaml&lang2=fsharp , and play with the architecture, there is no setting under which OCaml programs are consistently faster than F#-mono's
<gasche_> (I mean that nearly all programs are in the category "OCaml used less time", often by an important margin, while only a few outliers are in the "F# used less time" category, by a small margin)
<gasche_> that would correspond to my experience on e.g. StackOverflow
<gasche_> where people often report "I ported my software from OCaml to F#, the performance are disappointing, what should I do?"
<Drup> gasche_: what do you mean ?
<ousado> gasche_: that's often due to exceptions, no?
<ousado> (not that I had the slightest idea about F#)
<flux> gasche_, in mono or in microsoft platform? I was under the impression that mono is not that much of a performer.
<gasche_> flux: the shootout benchmarks are on Mono
<gasche_> the stackoverflow threads are not always explicit about which backend is used
<ousado> mono is doing quite fine there
<gour> ousado: do you use f#?
<ousado> nope
<gasche_> (yes, exceptions are the main source of performance issues)
<flux> also I imagine F# plays better with multi-core&threads, even in mono?
<gasche_> the Microsoft runtime reportedly has a good multi-threaded implementation
ulfdoz has joined #ocaml
<gasche_> I've been underwhelmed by the "hey it's cool, we're moving from <this sucky GC implementation> to <this less sucky but more buggy one>" reports from Mono
<gasche_> but that was some years ago, maybe they've paid the blood price and now have a good GC
<gasche_> so I guess the answer is "yes", flux, but with the subtitle "what is the price?"
<gasche_> (in term of performance on sequential programs, in particular)
<ousado> they're testing a generational GC now, I've read, IIRC
<gasche_> wow, great
<gasche_> OCaml only got this 20 years ago
<ousado> :)
<adrien> gasche_: I still have some issues playing OpenRA
<adrien> it's awful to think that you have to take care not to generate too much garbage for even simple tasks
<gasche_> hm I'm not sure what you're referring to, but real-time is a whole can of worms of its own
<adrien> what kills me: in JS, set the length of your arrays to 0 and reuse them
<adrien> because the GC is too slow
<gasche_> ousado,flux,gour: I am quite curious about how OCaml-Java2 will turn out in term of performance on a multi-thread-aware runtime
<gasche_> (and the multicore work of OCamlPro or OCamlLabs, of course)
<flux> is it possible to have, say, opam work with ocaml-java?
<flux> so I could just replace my current system using ocaml to using ocaml-java and have everything work?
<flux> I imagine it requires all C lib bindings to be rewritten?
<gasche_> yeah, I don't think that's possible as-is
<flux> so it's not that interesting
<flux> I suppose it is if you were using it commercially and really have a goal :)
<gasche_> or in a well-controlled environment, more generally
<flux> and to replace those c-binding libraries you need to have java expertice
<gour> i do not need to squeez last drop of performance juice otherwise i'd just use C(++)), but to hae good-enough platform with developed ecosystem (tools support, build system, GUIs...)
<gasche_> flux: or JNI
tane has joined #ocaml
ollehar has joined #ocaml
<gasche_> ollehar: I had a look at your StackOverflow question
<gasche_> I think that I either don't know or did not really understand the requirements
<ollehar> gasche_: hey
<ollehar> hm ok
<gasche_> (in particular I don't understand your functor suggestion)
gasche_ is now known as gasche
ben_zen has joined #ocaml
Kakadu has joined #ocaml
ben_zen_ has joined #ocaml
ben_zen_ has quit [Quit: leaving]
<ollehar> gasche_: ok, I added an example, objlen, and removed the functor part
<flux> can I somehow do this? module FaceMap = struct include IdMap type t = face IdMap.t end
<flux> IdMap is an IntMap
<flux> the point would be to have a module that can only associate ids to faces
<Drup> flux: I think you want the "with type" annotation
Snark has joined #ocaml
<flux> well, I suppose it cannot be done, this is the closest I got:
<flux> module FaceMap : Map.S with type t = face IdMap.t = IdMap
<flux> In this `with' constraint, the new definition of t does not match its original definition in the constrained signature: ..
ttamttam has joined #ocaml
Kakadu has quit [Read error: Connection reset by peer]
Kakadu_ has joined #ocaml
<Drup> I'm not sure to understand what you want :/
Snark_ has joined #ocaml
<flux> in the end I would like to have a module like: module FaceMap = struct type key = id type t val empty : t val add : key -> face -> t end
<flux> without that 'a nonsense ;)
madroach has quit [Remote host closed the connection]
<wmeyer``> hi
Yoric has quit [Ping timeout: 252 seconds]
<adrien> o/
<wmeyer``> \o
ben_zen has quit [Ping timeout: 276 seconds]
madroach has joined #ocaml
ollehar1 has joined #ocaml
zorun has quit [Ping timeout: 256 seconds]
zorun has joined #ocaml
<wmeyer``> morning everybody!
xavierm02 has joined #ocaml
<xavierm02> hey
<xavierm02> Is there some way to include a .mli in another .mli?
<xavierm02> include give me: File "Magma.mli", line 1, characters 8-11: Error: Unbound module type Set
<xavierm02> open gives : File "_none_", line 1, characters 0-1: Error: Files Magma.cmo and /usr/lib/ocaml/stdlib.cma(Set) make inconsistent assumptions over interface Set
<gour> /c
gour has left #ocaml []
<asmanur_> xavierm02: include module type of Bla
<asmanur_> (because include Blah means include the module Blah which does not make any sense in a signature)
<asmanur_> (so you need to extract the signature of whatever module you want to include)
<xavierm02> hm
<xavierm02> ok ty
<xavierm02> but since
<xavierm02> wait
<xavierm02> does it make sense to have a signature without a coresponding module?
<asmanur_> it's like having a type without a corresponding value
gautamc has quit [Read error: Connection reset by peer]
<gasche> flux: what about simply
<gasche> having Facemap
gautamc has joined #ocaml
<gasche> and then type t = id Facemap.t
<gasche> and manipulate t in your program
<gasche> I think that it may be occasionally useful to know that your t is in fact an instance of the Facemap structure, to be able to express transformations that (locally) use maps to something else
<gasche> for example (Facemap.fold (...) (Facemap.map (fun face id -> (id, some computation ...)) foo))
<gasche> xavierm02:
<gasche> I think the best design is to have your signature, and then talk about it from both places
<xavierm02> well
<gasche> instead of using (module type of ...), which is an advanced feature we shouldn't really need
<xavierm02> I wanted to do a signature for groups etc.
<gasche> module type S = sig ... end
<gasche> and then use that in two different .mli
<xavierm02> and then I'd have several groups
<xavierm02> matching that signature
<ousado> it would be very nice to have a tool that abstracts the specific CFFI away for several platforms
<xavierm02> I guess I misunderstood something
<gasche> is it only for groups, or do you have more ambitious wishes of capturing an algebraic hierarchy? (because the latter has been attempted and there are experience reports available about several techniques used)
<gasche> xavierm02: then what about module type Group = sig type t val neutral : t val op : t -> t -> t val inv : t -> t (** group laws: ... *) end ?
<ousado> .. so that e.g. ocaml, ocaml-java, js_of_ocaml/node.js all use the same code on the C-side of things, and the bindings are being generated for each platform
<xavierm02> I want to implement the hole hierachy
<wmeyer``> gasche is right, polymorphism is much easier in many cases (means type t = id Facemap.t, is of course a good solution)
ontologiae has joined #ocaml
<gasche> xavierm02: the focal/focalize people did some work on that
<gasche> xavierm02: why don't your reuse this ~chris thing directly?
<xavierm02> because I want to understand how it works
<gasche> well read his code :-'
<xavierm02> yeah
<xavierm02> well I don't exactly understand everything
<wmeyer``> sadly polymorphism is underused most of the time, in favor of functors.
<xavierm02> like
<xavierm02> he's got only signatures
<xavierm02> for many structures
<xavierm02> but someone said just above that it's like "having a type without a value"
<xavierm02> T.T
<gasche> xavierm02: asmanur_, in all respect, was wrong :-'
<gasche> if you see signatures as .mli only, *in general* it doesn't make sense not to have a corresponding .ml
<gasche> but you can define signatures and name them and manipulate them
<gasche> just as you can define new types
<xavierm02> ok
<xavierm02> but I can't
<xavierm02> use a .mli for that?
<xavierm02> I have to keep them in the same file?
<gasche> not necessarily
<xavierm02> then
<gasche> you should not use a .mli for that
<xavierm02> how do I import a mli in another mli
<xavierm02> hm
<gasche> the idea is that just as your type definitions go into the .ml
<gasche> so should the module type definitions
<gasche> but you can *refer to them* from a .mli
<gasche> include Map.S will work in a .mli
<gasche> note the difference with eg. "include IntMap"
<xavierm02> ok
<gasche> IntMap (if it comes from, say, intmap.ml), is a *module*, and including it in a signature doesn't make sense
<xavierm02> ty :)
<gasche> Map.S is a *module type*, so you can include it in any module tpe (and .mli are just module types)
<wmeyer``> a small chime in, you might find a good solution of your problem to have a single file that fully consists of these module types.
<wmeyer``> just a collection of the module types you use, and that's it.
<wmeyer``> this is solution which some projects or libraries used
<gasche> yes
<gasche> and in this case it does not matter whether it's a .ml (without .mli) or a .mli (without .ml)
<xavierm02> ok
<xavierm02> I'll do that
<xavierm02> another question
<xavierm02> I have a type group
<xavierm02> a module type
<xavierm02> no
<xavierm02> I have a module type ring so if it exists, the multiplicative inverse is unique but it might not exist so I have a function "has inverse". How do I then make a type "Field" that force "has inverse" to return true?
<xavierm02> module type
<xavierm02> is there a way to add a function to all modules of a given type
<xavierm02> or do I have to do a MODULE_DESCRIPTION with the necessary things to define the type and then a function that tranforms it into a MODULE that has the same things plus convenience functions?
<xavierm02> like in a RING
<xavierm02> I can define a RING with (add, neg, mul) but I could use (sub, div)
<xavierm02> (substract and divide)
q66 has joined #ocaml
<gasche> I think the answer to your last question is "not there is no way, you have to use a functor"
<xavierm02> :/
<gasche> I'm not sure about your previous question about "if it exists"
<gasche> you may want to have a signature Ring with inv : t -> t option to indicate partiality
<gasche> and then a signature Field with inv : t -> t
<gasche> (with the understanding than division by zero is handled differently, eg. by an exception)
<gasche> I'm not sure there is value in giving an 'inv' function to Ring
<gasche> (I would rather attach the partial inverse as a different structure on the same base type)
<xavierm02> I don't understand your last parenthesys
<xavierm02> oh
<xavierm02> you mean some rings would have inv and others wouldnt?
<xavierm02> it wouldn't be required?
<xavierm02> ------------------------
<xavierm02> new question: Can I have a (+) function that would take any two elements of any field and give back their sum?
<xavierm02> I feel like I could if I gave the field a function that took an element and returned a tuple containing the elements and the operations
<xavierm02> and then I'd only use those
<xavierm02> making it easier to write functions working for any field
ontologiae has quit [Ping timeout: 256 seconds]
<gasche> xavierm02: you can do that indeed
<gasche> type 't group = { neutral : 't; inv : 't -> 't; op : 't -> 't -> 't }
jayprich has joined #ocaml
<gasche> in more complex use case you will find out that it behaves rather differently from the module system in the way you manipulate the base types
<xavierm02> what do you mean?
<gasche> making field-polymorphic functions is not "easier", it's only that they take the field as a parameter instead of being inside a functor on the field
<xavierm02> yeah
<xavierm02> but that makes you able to have one (+) function instead of 10
<xavierm02> which is great
<gasche> how so?
<gasche> (it is also less type-safe if you mix different group structures on the same base type)
<xavierm02> well the + would work on any field
<gasche> yes but what's the difference vs. calling the + function of the field that is the functor parameter?
<gasche> if you write (add field v1 v2) instead of Field.add v1 v2, indeed you have a single (add) function instead of (FieldA.add, FieldB.add...), but is it really more convenient?
<gasche> I don't see this as a big advantage
<xavierm02> well
<xavierm02> if u start writing non trivial expressions
<xavierm02> you need the (+) and (*)
<xavierm02> or it becomes impossible to read
<gasche> you can do that with modules as well
<xavierm02> and it looks to me like the number of infix operators we can have is limited
<gasche> let open RealField in foo + bar
<xavierm02> oh
<gasche> (I would however advise to maybe not use (+) and (*) directly, maybe +/ and */ instead, to be able to conveniently call the integer operations that have a tendency to pop up under any scope)
<xavierm02> I'll do that. Thank you :)
<xavierm02> why is the "contains" method called "mem"?
<def-lkb_> xavierm02: fwiw, the RealField.(foo + bar * baz) notation is also handy
<def-lkb_> like "member" I think ?
<ousado> xavierm02: as in "member" ?
<xavierm02> oh >_< right
dsheets has joined #ocaml
<xavierm02> there is no way to define (-) so that i can take one or two arguments right?
<gasche> no
<gasche> but you can define ~- as an infix
<def-lkb_> (and the parser will rewrite -x as (~-) x)
<xavierm02> how do I defined (*)
<xavierm02> or (*/)
<xavierm02> it thinks I want to start a comment >_<
<def-lkb_> just add a space :)
<xavierm02> awww >_<. thank you :)
Fnar has quit [Quit: Client exiting]
<ousado> aren't operators expected to be infix anyway?
<Drup> except those beginning by ! and ~
<Drup> (those are prefix)
<ousado> ah ok.yep. I see
<wmeyer``> hello ousado
<ousado> wmeyer``: hey :)
<wmeyer``> :-)
<ousado> wmeyer``: have you seen the sun meanwhile ?
<wmeyer``> ousado: of course these is sun here!
<wmeyer``> especially for the past few days
<ousado> nice.. yes here too
<ousado> finally
<wmeyer``> maybe saturday today is not so sunny
<wmeyer``> but we have a good weather, and I can't complain
<wmeyer``> I fully trust it will remain the same.
<adrien> (for england)
<xavierm02> is there some wway to define a postfix operator?
<ousado> it's starting to get a little too warm for my dog though..
<ousado> for her the extended winter was a gift
<wmeyer``> fortunately there is only me who can complain about the weather today!
<wmeyer``> it was sunnier before.
<wmeyer``> but I am going to cycle to Makespace today
<wmeyer``> I bought a bike
<ousado> wmeyer``: Makespace looks interesting
<wmeyer``> specifically to travel around Cambridge
<ousado> I've looked at the website last time you mentioned it
<wmeyer``> it's growing
<wmeyer``> we have a lot of good people there.
<wmeyer``> it's very hard to resist not going there :-)
<wmeyer``> and i got my samsung chromebook working these days
<gasche> xavierm02: no way
<wmeyer``> oh i just reminded myself about the ocamlbuild stuff i have to merge.
<wmeyer``> tens of commits.
<gasche> wmeyer``: are you looking for reviewing eyes?
<wmeyer``> oups. It will take some time, anyway. :-)
<gasche> I must say I don't understand why you didn't commit them more incrementally before
<wmeyer``> gasche: me either, maybe it's just a habit.
<gasche> (I guess some of them are part of an unfinished series, but for the bugfixes / single-feature impls. that could be done individually)
<gasche> do you have a publicly accessible VCS with the patches in it?
TaXules_ is now known as TaXules
<gasche> I think it'd be better to have a look before they get in trunk
<wmeyer``> nope
<wmeyer``> Ok
<gasche> I can lend a hand, maybe other people on the chan would be interested as well
<wmeyer``> I will consider that.
<gasche> well if you have a github account you can just fork github/ocaml/ocaml
<gasche> and have a branch for your patches
<gasche> as a basis for review/discussion
<wmeyer``> sounds good.
<wmeyer``> actually if we fixed performance problems in ocamlbuild, it would very competetive
<gasche> (for the next release you *must* be more incremental)
<xavierm02> I'm trying to define the module type RING as ADDITIVE_GROUP plus MULTIPLICATIVE MAGMA but I get and error saying that I defined t twice even though it got defined the exact same way in both... http://pastebin.com/i4qQbRwf
<wmeyer``> patches welcome.
<gasche> (it's putting more work on Damien to have a look at the stuff that changes just before freeze)
<wmeyer``> gasche: Ok, thanks.
<gasche> xavierm02:
<gasche> MULT with type t := t
<wmeyer``> you know in the industrial setting gasche , we used staged approach for fixes
<wmeyer``> maybe not merging them at the same time
<xavierm02> thank you :)
<wmeyer``> gasche: but I fully agree, I should merge them along
<wmeyer``> (industrial, let's say, in my company; OCaml *is* industrial setting)
<adrien> I only merge stuff that might break when others are away
<adrien> then I hide
<wmeyer``> good strategy, commit & hide.
<wmeyer``> that what i do in at daytime job :-)
<wmeyer``> anyway, tired ...
* wmeyer`` having yet another coffee to ensure he can work
<gasche> I'm on a two-weeks coffee break
<gasche> (not that I particularly needed one, but it was a jest)
<gasche> you should try
<wmeyer``> gasche: I was just two weeks ago on a break
<wmeyer``> i do this from time to time
<wmeyer``> it feels different
<wmeyer``> not nesercailly bad
mcclurmc has quit [Ping timeout: 252 seconds]
jayprich has quit [Changing host]
jayprich has joined #ocaml
ben_zen has joined #ocaml
ollehar1 has quit [Ping timeout: 276 seconds]
<xavierm02> I have the same problem again (t being declared twice) but this time, it's in functors http://pastebin.com/9x1tucVR
<gasche> well
<gasche> include (Foo(Bar) : Sig with ...)
eni has joined #ocaml
eikke has joined #ocaml
ontologiae has joined #ocaml
<xavierm02> ty :)
beginner42 has joined #ocaml
<beginner42> how can i include a c library i use in my c stub into a Makefile that uses ocamlmakefile?
jcao219 has joined #ocaml
<adrien> beginner42: iirc you need to set LDFLAGS
<adrien> and CFLAGS
ttamttam has quit [Quit: ttamttam]
Neros has quit [Remote host closed the connection]
<beginner42> adrien: hi, thanks i am going to try that
eikke has quit [Ping timeout: 248 seconds]
jayprich has quit [Ping timeout: 252 seconds]
ollehar1 has joined #ocaml
BiDOrD has quit [Read error: Connection reset by peer]
BiDOrD has joined #ocaml
spanish has joined #ocaml
<spanish> hi
ben_zen has quit [Ping timeout: 264 seconds]
<spanish> can somebody tell me how this construction is called? http://pastebin.com/UTns5YBi
ben_zen has joined #ocaml
<gasche> spanish: it's a sum type, which is an instance of "algebraic datatypes"
<gasche> the fact that it begins by "and" rather than "type" indicate that it's part of a block of mutually-recursive type definitions
<gasche> (with "expr" and "type_path", I assume)
<spanish> ah, thanks
<spanish> how difficult is ocaml, though
<spanish> wouldn't change my good old c for nothing
<gasche> C has a pathetic type system
<gasche> it cannot express sum types in a type-safe way
<gasche> lacking this concept is a mistake (that was understandable at the time C was designed, but is grave when made by language designer nows)
<spanish> it get things done if you know how to use it, can't see an operating system or kernel written in ocaml, though
<gasche> and it does not make the language "easier", because you end up with ugly encoding when you need sum types
<gasche> well
<gasche> assembly also gets things done if you know how to use it
<spanish> I've never had a single problem with it's "restricted" syntax
<gasche> and indeed, OCaml is not well-suited for kernel programm
<gasche> ing
eikke has joined #ocaml
<gasche> but OCaml programs also get a new vulnerability each month due to some shitty buffer overflow problem
<gasche> C/C++ programs are a security *nightmare*
<spanish> I only need to integrate gnu cpp into mtasc, after that I don't think I'm using ocaml any more, honestly
<gasche> so using them for system programming is maybe not that good an idea, I'd say
<spanish> I come from embedded, so cross-platform and security is something I know eyes-shut
<gasche> (I sometimes wish people had kept Pascal for OS interfaces instead of moving to (Objective-)C)
<gasche> I may have been coming to this conversation with a too-aggressive tone
<gasche> I respect C as a language
<gasche> but really I don't think that sum types make OCaml "difficult"
<gasche> it's more than you have to learn something which is actually important
<gasche> and hm
<spanish> I've been studying, with open-mind others, but, honestly, there's nothing I would replace it with
<gasche> well all languages have flaws, and OCaml certainly has some
<gasche> Cyclone was a very interesting attempt at fixing some of the problems with C
<gasche> ATS is also interesting
<gasche> but they're both complicated
<gasche> (ATS is much more difficult to learn than OCaml)
<spanish> sure others have some nice things and all, but at the end of the day, you're behind a program with simple syntax, easy to follow, and to maintain
<gasche> except for the security issues I mentioned above
<Drup> I don't find C code easy to follow ...
<gasche> (I don't know about you; but in general I don't believe about the implication "I come from embedded *therefore* I know about security"; the unix systems that we're all using now are extremely bad from a security point of view because they don't encourage appropriate confinement of rights at a fine-grained program/processus level)
<Drup> it's so low level that my mind have to fill a huge gap to put it into the level I design my programs ...
<gasche> Drup: it's true that experienced C programmers know about these patterns well and are surprisingly able at encoding various things into C
<spanish> you don't even use operating systems in embedded, most of times, but even then, there are things you can change to secure it
<spanish> you never use to give the user access to the system as you do with a computer, so it's not the same really
<spanish> what I'm saying about the syntax is
ben_zen has quit [Ping timeout: 264 seconds]
<spanish> you have something in front of you you don't know what it is, and if you're programming "right" according to c, have a decent editor like emacs, you just have where it comes from at a keypress, so you can continue from there, other languages with more complex syntaxes obligate you to have more of it on your head, slowing down the whole thing
<spanish> making it harder to maintain, reuse, etc
<Drup> spanish: don't make the mistake of saying "complexity" for "C-likeness" please.
<Drup> what you're asking is C-likeness
<Drup> not simplicity
<spanish> that's the conclusion I've come up with, the simpler the syntax the programming language has, the quicker it is
<spanish> c is about the most simple you can find Drup
<Drup> No it's not, you're used to it, that's a different thing
bobzhang1988 has joined #ocaml
<spanish> yes, I'm fully used to it, but I was being objective, how it could be any simplier, yet as powerful?
<gasche> I'm not sure you're talking about actual syntax
<gasche> or code formatting/indentation choices
<spanish> I'm talking about expressing things to the computer that allows doing things, the simplest way, which in turn, makes further development simplier
<Drup> spanish: Lisp syntax is utterly simple and as expressive :D
jpdeplaix` has quit [Ping timeout: 256 seconds]
<gasche> indeed, Lisp/Scheme would be an example of syntax that is simpler than C
<spanish> nowadays there's nothing you can do with whatever the language I couldn't do even better with c, cpp, and the build system
<gasche> that's not true
<gasche> and I don't really understand how you could even say that
<gasche> you're either quite ignorant or intentionally trolling
<spanish> yes, that level of simplicity goes bellow the "hysteresis" point, or would you do and maintain an operating system in lisp?
<Drup> spanish: could you please code a correct compiler of C in C ?
<gasche> spanish: operating systems have been written in lisp
<spanish> of course you can
<gasche> go learn some history, pal
<Drup> some people have tried it and for now, they have all failed
<Drup> so I welcome your compiler :3
<gasche> quite a few operating systems have been written in lisp
<spanish> hajve failed? do you know what gcc is?
<gasche> and all publicly-available C compilers have bugs
<Drup> yes, and it's not "correct"
<gasche> that's what Drup was pointing at
<spanish> sure gasche, are they being used and/or being actively developed?
<gasche> probably not
<spanish> so, why?
<gasche> but it's more for politics rather than technical reasons
<spanish> no, that's not the reason
<gasche> well for one things, some of the Lisp people jumped on the rather bad idea of having Lisp Machines
<gasche> at a time where the hardware evolved very quickly
<spanish> free software doesn't care about politics, but about quality
<gasche> so there were soon obsolete
<gasche> ...
<gasche> again, you are either impressively naive or a troll
<Drup> this not an interesting conversation, you seriously need to be more open-minded. C is useful in some specific cases like very low level programming and embedded system, but that's all.
<spanish> should that be a suitable, sensible option over c, and lisp would have been used for operating system and tools
<tane> funny, i had this conversation yesterday as well
<gasche> Lisp *has* been used for operating systems and tools
<Drup> (and it was fast)
<gasche> but it was in proprietary product sold by specialized companies
<spanish> yes, has, but isn't
<gasche> that did not get the right contracts, and died
<gasche> well
<gasche> there's an 1/2 chance that you're using a text editor that is massively implemented in lisp
<spanish> I know all that, but the problem wasn't about the contacts, really
<gasche> and the GCC compiler you cited was originally implemented in lisp
<spanish> I use emacs indeed and know lisp, have even made interpreters for it just for fun
<spanish> yes
<gasche> I don't think it was ported to C because it was a better language
<gasche> probably to try to bootstrap, or because more people knew C and they thought that would therefore make progress easier
<gasche> (I haven't looked at GCC history)
<spanish> I didn't said better, but suitable on the long term
<gasche> well if you think that only technical concerns dictate adoptions (in the free software world or elsewhere), you're a fool
<adrien> spanish: C is *made* to build operating systems
<adrien> it's *made* to be low-level and close to the hardware
<gasche> OpenStep was strictly better than all desktop environments available at the same time, yet faded into irrelevance
<spanish> that's what I'm saying adrien, simple and powerful
<adrien> so you can map as closely as possible to the hardware
<adrien> spanish: for a specific task, yes
<adrien> interacting with the hardware
<adrien> but I'm not sure having schedulers in C is that great
<gasche> Ada was strictly better suited than C/C++ at writing secure, reliable system software, yet mostly faded in irrelevance as well
<Drup> spanish: you must have a very strange mind to find thing close to a computer "simple and powerful"
<spanish> for any you want really, there's no difference between some programming language's libraries and others
<gasche> (probably due to the lack of avaibility of a free compiler for a very long time)
<gasche> spanish: you say that, yet you apparently don't know what a sum type is
<gasche> from which I deduce that your knowledge of programming languages is actually very simplistic
<spanish> no, I don't know ocaml's slang, sorry
<Drup> it's not an ocaml thing ..
<gasche> "sum type" is used in programming language theory since the seventies
<spanish> Well, I studied computer science in spanish, many years ago
<gasche> you may know what the concept is, but not what the usual syntax for it is
<Drup> gasche: do you have an order of magnitude of how much faster marshalling is with No_sharing ?
<gasche> no idea
<gasche> you should try
<Drup> huum
ollehar1 has quit [Ping timeout: 248 seconds]
<gasche> spanish: one major flaw in your vision of things
ttm is now known as The_third_man
<Drup> I wonder if js_of_ocaml is going to handle this well.
<gasche> is that a language is characterized not only by what it makes possible
<gasche> but also by what it makes *impossible*
<spanish> hehe, didn't get that
<gasche> the mistakes (or the genuinely good programs) its static analayses refuses to accept
ollehar1 has joined #ocaml
<spanish> but if there's something I can't do with it, it's certainly not a language I'd use
<gasche> note that you can have that with a static analyzer as one of your programming tools
<gasche> well
<gasche> "not having segfault" for example is a rather good property
ben_zen has joined #ocaml
<gasche> the question is what is the cost of this guarantee
<spanish> you mean a high-level language
<gasche> I mean any language
<gasche> sum types, the feature we started discussing, is encodable as a library (or a code pattern) in C
<spanish> so?
<gasche> the problem is that you don't get analyses that are as good as what, eg. OCaml, implements
<Drup> but gasche, C let you have the segfault if you want, is a fantastic sign of freedom and powerfullness of the langage </troll>
<gasche> you won't be told if you're missing a case
<gasche> (with the usual encoding with an int-tag and an union type)
<gasche> the fact that OCaml can check that pattern-matching is exhaustive is a very important part of the language in practice
<gasche> it is why having a notion of sum type is not necessarily encodable as "a library", if you don't have the accompanying static analyzer
<spanish> I'm not saying omcal, or any other language have improvements over c, but there are tools for c you can use to output and analyize it to have your own results
<gasche> well
<spanish> I'm just saying this complex and un-natural syntax, for me, at least, doesn pay off at all
<gasche> for a lot of various reasons, most (free software) static analyzers for C are much less good than the type systems of OCaml
<wmeyer``> gasche: the trouble is always during the implementation. When we are not sure about semantics of pattern matches or some nodes are still in progress. Then warnings are really desired.
<gasche> wmeyer``: indeed
<gasche> or | Foo => failwith "TODO"
<gasche> spanish: the syntax of sum types in OCaml is not complex
<gasche> it's just that you complain about learning something new
<spanish> if you know how to use a proofiler, a debugger, and a memory checker, and, obiously, programming c, there's nothing you can do better than I do, wheter you use ocaml, or any other language
<gasche> to start with spanish
<gasche> that's wrong
<gasche> to start with
<gasche> there is no tool that can check if a given piece of code is actually a valid C program
<gasche> as defined by the C standard
<gasche> because whether a given program has undefined behaviors is undecidable
<spanish> and there's many things I can do, you could never achieve with ocaml with all it's improvements
<gasche> that much is true
<Drup> exemple ?
<gasche> but there are many things you can't do in portable C that you can do in assembly
<gasche> and yet you somehow don't write *all* your programs in pure assembly code, right?
<spanish> I mean, achieve in a sensible way, for example writing firmware, a kernel, an operating system
<spanish> no, that's what c is for
<spanish> you play with the compiler to output your assembly
<Drup> spanish: sure, that's what C is for and we agree on that
<Drup> spanish: but C is not good for *everything*
<Drup> and you seem to have difficulty on accepting that.
<gasche> until two years ago, the official C standard had no definition of what a multi-threaded program is
<spanish> having libraries you can link with, why not? I fail to understand that
<gasche> spanish: when we say that a language feature make a language "strictly more expressive"
<gasche> we mean that there are programs using this feature that cannot be encoded purely as libraries in a convenient way
<gasche> in some cases it's because you *also* need a good static analysis to support this feature well (eg. sum types)
<gasche> in others it's because you need a *compilation step*, that is a global transformation, to express the feature in the source language
<gasche> (eg. call/cc)
<spanish> the point is whether all that can be called "unnecessary complexity"
<gasche> the answer is that it can't
<spanish> but I agree I'm too on the c side because that's what I program in the whole time
Watcher7|off is now known as Watcher7
<gasche> sometimes you need those more complex features
<gasche> (not always; and maybe not for most of what *you* do)
<spanish> yet I have never had the need for a programming language to take me as a retarted person
<gasche> that's a fallacious argument; we all make mistakes and catching them early makes you more productive
<gasche> it's true that sometimes a safe language won't let you write something that you want to write, and in that case there are escape hatches available
<spanish> actually, whether you're not low-level. all reduces to that, if ocaml lets you be productive, it's fine I guess
<gasche> it may be the case that your particular kind of programs would always use the escape hatches, and in that case choosing a less-safe language is reasonable
<gasche> but it's foolish to draw general conclusions out of that
ben_zen has quit [Ping timeout: 264 seconds]
<gasche> well one of the reason why MTASC is written in OCaml is that it is extremely productive when writing compilers
<spanish> that's why I said I'm too much on the c side, if I want classes I want to implement them as I want to, and do whatever I want to to get my target, rather tha dealing with premade concepts
<spanish> yes, I've noticed
<spanish> ocaml has sevberal nice features, I even see it better than java, which I hate
<spanish> and a lot of work behind, not saying the opposite
<Drup> spanish: so you re-implement classes from scratch ? What do you do if you want genericity ? re-implement it too ?
<spanish> re-implement? I write programs to fit a purpose
<gasche> in general C programs emulate genericity with a top datatype (eg. (void*)) and forget about safety
<gasche> s/programs/programmers/
<Drup> spanish: genericity fit a purpose too.
<spanish> that depends on your meaning of genericity for each case in particular, you normally write modules that interact with each other to get there
crlf has joined #ocaml
<spanish> being that modules reusable for other projects if you know how to program
<gasche> (my pet example of generic code would be a linked-list library)
breakds has joined #ocaml
<ggole> Interesting choice, since linked lists are one of the few data structures that can be written in generic form in C without massive hacks
jcao219 has quit [Ping timeout: 260 seconds]
<spanish> I very rarely use linked list as such, on it's own, but even then, you might better get them from a pre-alloc'ed memory-aligned block that you then link with the next one if more are needed
<adrien> agreed, after 40 years, there is almost a fine number of data structures of ok-ish stability and usability that are available in libraries for a few basic tasks
<ggole> Most of the C linked list libraries I know of that are worth using don't allocate at all.
<gasche> indeed
<gasche> and more generally, dynamic arrays are often a better choice than linked lists
emmanuelux has joined #ocaml
<ggole> They become problematic when you need to maintain pointers to the elements. That's when a list really shines.
<ggole> Other than that, yeah.
<spanish> it's very rare to need just a linked list
<spanish> you normally need more data together with the pointers
<gasche> still, C doesn't allow to encode type safety for generic collections
<gasche> (well you can use a template-like forms with macros, as iirc some BSD systems have)
<ggole> There's a queer union hack which allows for some checking in the list case (although I can't recall whether it relies on typeof() being available).
<ggole> But in general, yeah, pretty awful.
<ggole> And the silent conversions. Ugh.
<ggole> Well, C is what it is.
<spanish> hehe, all reduces to knowing what you're using, about "maintaining" pointer to elements, that's one of the reasons you use blocks instead of list cells
mattrepl has joined #ocaml
<spanish> you get pointers and offsets for the same price
ben_zen has joined #ocaml
<gasche> (I'll stop trolling and go back read this thesis)
ben_zen has quit [Ping timeout: 252 seconds]
<flux> hmm, I suppose nobody's written a BigDynArray
<flux> also Batteries' Bigarray cannot be built out of an enumeration
<flux> but I suppose it can be understood, Bigarray's don't have 'slack' so it would always need to build&copy at least twice..
tane has quit [Quit: Verlassend]
bobzhang1988 has quit [Ping timeout: 276 seconds]
ttamttam has joined #ocaml
<gasche> flux: I'm not sure what you mean by 'slack' (do usual arrays have slack?), but I think a BigDynArray would be possible
<gasche> what would your need for it be?
<flux> gasche, well, when converting an enumeration to a structure C can make use of?
<flux> 'slack'ky data structure would be for example c++'s vector
<flux> it has separately the size and the capacity reserved
<gasche> well you can over-size a Bigarray just as well, can't you?
<flux> yes, but when I ask its size it'll tell the size allocated
<gasche> yes, you'll have to use a dedicated interface
<flux> I suppose I wouldn't need to actually put stuff to those unused elements
<gasche> DynArray has a record on top of an usual OCaml array
<flux> with some Obj.magic
<gasche> or request one element at create time
<gasche> just like Array.make
<flux> which requires knowing the size beforehand
<gasche> I don't follow
<flux> Array.make has an argument for size
<flux> but you might not know the size before you reach the end of your source data
<gasche> the point of a DynArray is to dynamically reallocate it when you need more space (but not too often)
<flux> ah, I thought you meant Array.make literally
<gasche> well Array.make, besides the size, requests a default element
<gasche> which is used to fill all slots
<gasche> in a dynamic-array setting you would also use that to fill the slots that are beyond the "current observable size"
<flux> sometimes that's tricky as well. not as tricky with Bigarrays though, as they cannot contain anything complicated.
<gasche> I think for Bigarrays you don't even have to provide this element
<gasche> as they live outside the OCaml heap anyway
<flux> correct, they don't require a default value
<gasche> batteries' bigarray have a to_enum function (called "enum" by convention)
<gasche> but not of_enum indeed
<ggole> Actually, you don't need Obj.magic for extensible arrays even if they are built with normal caml values
<gasche> yes because you have values available at resize time
<gasche> but not necessarily at creation time
<ggole> Right
<ggole> The trick is in how to support a method like reserve
<flux> gasche, you mean you have a value to use when you append an element?
<gasche> flux: feel free to provide an implementation for BatBigarray.of_enum
<ggole> Which is also possible: you just have to check capacity lazily
<gasche> well
<gasche> the arrays you dynamically resize are generally not-empty
<flux> gasche, but if you do use that value for extension purposes, then you might get a space leak, if you later on reset the used values
<ggole> Yeah, that's the disadvantage of the type-safe way.
<gasche> I think that's a reasonable cost to pay as long as it is documented
<flux> I don't think it's very risky to use Obj.magic 0 for that
<flux> other Obj.magic tricks are more dangerous :)
Tobu has quit [Ping timeout: 256 seconds]
<gasche> I don't think it buys you much
<ggole> It would be quite a tricky thing to track down any problem, though
<gasche> (in either cases)
<flux> I really don't want to have a big piece of software leaking memory, and then have a line in the documentation "may refer to once-inserted values even after removal"
<ggole> True enough.
<gasche> recently we had a problem in Batteries with some library, I don't remember which, accessing the memory at the non-existing string index (String.length str)
<gasche> it turns out that you can't actually notice that you're screwing up in OCaml because strings are padded with couple of bytes at the end
<gasche> and by chance, the padding at this position always return 0, which is exactly what the library needed to return (morally) to be correct in that case
<ggole> I assume the access was with unsafe_get?
<gasche> yes
<ggole> It's funny how these edge cases make their way into software
Tobu has joined #ocaml
<flux> well, it's a by-design C-compatibility feature, so it's not 'by chance' in that sense?
<ggole> Any little crevice of oddness always ends up mattering in some strange way
<gasche> flux: if you want
<gasche> then the chance is that it was not length+1 or whatnot
<gasche> (but you could say that length+1 is less likely; indeed it was a <-vs-<= thing)
<flux> my most annoying ocaml bug was that the Str module is not thread safe
<gasche> anyway
<ggole> 0 is a poor fill value for that reason
<flux> not even the functions that look like they are (ie. split)
<gasche> someone eventually noticed when they compiled it under js_of_ocaml that performs no such padding
<gasche> and was yelled at by the JS engine
<ggole> It used to be recommended to fill interesting unused memory with a value that was simultaneously a remarkable pointer, float and int value
<ggole> So that if one turned up it could be not be mistaken for a real value by accident.
<gasche> in this case as flux say, you need to have 0 there
<gasche> to have null-terminated strings when talking to C
<gasche> well
<gasche> at least "it's better to"
<ggole> Yes, string has its hands tied. I won't critique that, terminating everything is a good choice.
Tobu_ has joined #ocaml
<gasche> flux: re. BigArray.of_enum, I think we could have something simpler than the usual realloc-and-copy policy
<gasche> you can just keep a list of temporary buffers while filling
<gasche> (you don't even need an exponential policy, even though that may be beneficial for performance)
<gasche> and then reallocate to concat/append once and forall when the enum is consumed
Tobu has quit [Ping timeout: 256 seconds]
<gasche> if you're interested in implementing this for Batteries, you're welcome :)
<gasche> (and if you seriously tell me that you don't have time to implement it yourself, but would use it if it was there, I would consider doing it)
Tobu has joined #ocaml
<flux> gasche, but that will always result in two copies. not sure if it's much better than Bigarray.Array1.of_array (Array_of_enum ..) I have now
<flux> well, it's better amount-of-bytes-allocated-at-a-time-wise
Tobu_ has quit [Ping timeout: 256 seconds]
Tobu_ has joined #ocaml
<gasche> it may even be slower if accessing the bigarray does some index-mangling logic
<gasche> but will have better locality
<flux> and produce more garbage :)
<flux> well, not necessarily
<flux> that could probably be optimized
<gasche> hm
Tobu has quit [Ping timeout: 256 seconds]
<gasche> in fact the way Array.of_enum is implemented is by counting the enum beforehand
<gasche> it would be trivial to implement
<gasche> and also produces some amount of garbage
<gasche> (more than what we've been discussing so far, I'm afraid; but garbage outside the heap is more vicious)
mattrepl has quit [Quit: mattrepl]
ollehar1 has quit [Ping timeout: 256 seconds]
crlf has left #ocaml []
walter has quit [Ping timeout: 245 seconds]
walter has joined #ocaml
ttamttam has quit [Quit: ttamttam]
darkf has quit [Quit: Leaving]
eikke has quit [Ping timeout: 260 seconds]
breakds has quit [Remote host closed the connection]
ben_zen has joined #ocaml
ollehar1 has joined #ocaml
shinnya has joined #ocaml
<ollehar> spanish = fasta???
<adrien> doubt it
<spanish> what?
<Drup> ollehar: oh no, fasta is obsessed by build systems, not low level languages.
<spanish> no, I'm not that person
ontologiae has quit [Ping timeout: 252 seconds]
tane has joined #ocaml
Yoric has joined #ocaml
<spanish> heh, what does that fasta says about build systems?
<spanish> I'm from the canary islands, even though mi nick is spanish, we don't really like spaniards, arround
jpdeplaix` has joined #ocaml
<adrien> it's difficult to pretend there's nothing to improve in the ocaml build systems
Yoric has quit [Ping timeout: 264 seconds]
<spanish> a ok, ocaml-specific build systems
jayprich has joined #ocaml
<spanish> by build system I understand more what's on top of the language, such as make, autoconf, shell, perl, etc
<Drup> perl ?
<spanish> yes, automake relies on perl
xavierm02 has quit [Remote host closed the connection]
<gasche> funny how things goes
<gasche> I had a look at implementing an Array1.of_enum for flux
<gasche> and I'm not sending a pull request to iTeML (qtest)
<gasche> s/not/now/
<flux> hm?-)
<flux> I'm yet to be distracted from my goal..
<flux> I want to have a module for representing a 3d scene formed of triangles (or maybe polygons)
<flux> and functionality to manipulate it with relative ease. decided to go the functional way, wondering if that was a good idea..
Snark has quit [Disconnected by services]
Snark_ is now known as Snark
Yoric has joined #ocaml
eikke has joined #ocaml
osnr1 has joined #ocaml
<jayprich> function composition maps extremely well to non-linear spaces and fractals .. not really necessary for vanilla 3d scene data where OpenGL is the most portable library and has hardware accelerated rendering on most platforms
<flux> well, I first to scene construction/manipulation and then generate the vertex array representation
osnr has quit [Ping timeout: 276 seconds]
<flux> I'd like to experiment with some subdivision algorithms
<ollehar1> in a module sig, why can I define
<ollehar1> type empty = unit * unit
<ollehar1> but not
<ollehar1> type any = [< `table | `string | `float ...]
<ollehar1> ?
<flux> ollehar1, hmm, what do you mean by latter? maybe you don't want < there?
<ollehar1> maybe not
<ollehar1> do'h
<flux> [< `foo | `bar] means 'a type that is a subtype of [ `foo | `bar ]
<flux> do if you really do mean that you would write: type 'a any = [< `foo | `bar] as 'a
<flux> as now type 'any' is actually a set of types, parametrized by which subtype is chosen
<ollehar1> so [< `foo | `bar] means [`foo] OR [`bar]?
<flux> OR [`foo | `bar]
<ollehar1> ok
<flux> I wonder though if [] is possible
<ollehar1> and [> `foo | `bar] would be AND?
<flux> well, not quite, in that case you could have something in addition to those.
<flux> I think < could be read 'something is a subset of this' and > as 'this is a subset of something'
<ollehar1> like also [`foo | `bar | `blah]?
<flux> yes
<ollehar1> I see
<flux> for example
<ollehar1> gotta wright this down :P
<flux> # type 'a any = [> `foo | `bar] as 'a;;
<flux> type 'a any = 'a constraint 'a = [> `bar | `foo ]
<flux> # (`baz:(_ any));;
<flux> - : [> `bar | `baz | `foo ] any = `baz
<flux> you can play in the toplevel like that :)
<gasche> the best idea being not to use polymorphic variants
<gasche> (unless they are demonstrably helpful to solve the problem at hand)
<adrien> but it's difficult to know whether they are until you've played with them =)
<adrien> but in doubt, yeah, prefer "regular" variants
<ollehar1> never seen keyword "constraint" before
<ollehar1> there should be a ocaml wiki...
<ollehar1> *an
<gasche> well isn't the manual for that?
<gasche> which additional information would you have on a wiki?
<ollehar1> more elaborate examples, maybe. maybe real world ocaml will fill a gap.
<gasche> the Part I of the OCaml manual has space for example
<gasche> do you have more precise ideas of what could be added?
<gasche> (Part I : An introduction to OCaml, as opposed to Part II which is meant to stay a concise reference of all constructs)
<Drup> gasche: on small value, in js, Marshalling is almost not faster with No_sharring. It's interesting to note that, when the Jit kick in, it became "only" twice as fast.
<Drup> (by "in js" I mean "with js_of_ocaml")
<gasche> indeed
<Drup> I should try to compare to manually converting to js_string but that sounds heavily dependent on what you're converting.
<gasche> yeah and boring as hell
<gasche> what are you doing that is performance-critical?
<Drup> nothing, I'm just curious
mattrepl has joined #ocaml
gfredericks has joined #ocaml
<Drup> Dom in Js is so slow that you virtually care about everything, performance-wise ;)
<Drup> but right now, I was just playing with the Html5 drag&drop API that allow to convey string while dragging, so I tricked it with ocaml's marshalling.
<gasche> that's nice
<Drup> Indeed, I was actually a bit surprised that marshalling works, js_of_ocaml is really magic :D
gfredericks has left #ocaml []
<Drup> (you can't marshall dom objects, however, but that's not really surprising)
jknick has quit [Quit: Lost terminal]
<flux> gasche, cool!
jcao219 has joined #ocaml
<spanish> snd is a keyword in ocaml?
eikke has quit [Ping timeout: 256 seconds]
<flux> no, it's a value (function)
<flux> simple proof: let snd = 42 :)
<spanish> ah thanks, let me see
<gasche> it can be readily defined as
<gasche> let snd (_, x) = x
<ollehar1> gasche: wish I knew! ocaml.org and its tutorial are neat, hopefully it will be extended. the examples in the manual can be quite theoretical. like made for compiler programmers.
<gasche> ok
<Drup> well, the manual is a very good manual but not really a good tutorial
<gasche> well if you feel some precise need for a missing tutorial, do not hesitate to put an issue on the ocaml.org bugtracker or something
<ollehar1> I will!
<spanish> ok, iit means to return the second element of a list, doesn't it? I can see that within the pervasives file, while it's definition not being clobbered in mtasc
eni has quit [Ping timeout: 256 seconds]
<Drup> spanish: of a tuple, not a list
<spanish> a ok, yes, a pair says the pervasives file
<spanish> not too bad, I just have left to integrate the '# number "filename"' construction gnu cpp uses so front-ends can keep track of file names, and see how I mix it with mtasc's error reporting functions
<spanish> apparently, it uses has tables to find out line number of errors or warnings
<spanish> *hash
iZsh has quit [Quit: Coyote finally caught me]
<spanish> s/file names/line number
<ollehar1> a fun tutorial might be on how to make polymorphic behaviour in the OO sence but with modules and functors, and then use a very basic-like example with cars: a car is a vehicle, volvo and saab are cars. and show how the record is like the "object instance" in a module system. so "car" and "vehicle" is signatures, etc. they can also implement a to_string signature, to make it java like. :) one might argue that in real life programmin
<ollehar1> (example from java text book)
eikke has joined #ocaml
<gasche> spanish: you can post your final patch here if you want some code review
<gasche> re. lexer directives, the easiest thing to do is probably to integrate it directly at the lexer leve
<gasche> l
<spanish> sure, thanks I will, the final resulting compiler will be put on git-hub or somewhere else together with the audio and video players we wrote
<spanish> yes, probably, I'll be asking as I get things done, learning new things is never a bad thing
<spanish> we would have done this before but deadline was over, so we simply integrated calling cpp for each input file, and then
<spanish> oputput .lst files to see where the error really was, a nightmare
<spanish> during compilation I mean, we did output the pre-processed files, so we could see the error where mtasc was seing it
<spanish> all that because the audio and video players neede tight integration with a fast-cgi written in c, so we wanted to shared definitions both ways
tane has quit [Quit: Verlassend]
<spanish> amazingly enough, haxe, which is mtasc's predecessor, still doesn't look like a tool you can easily integrate with an external building system
<gasche> you mean mtasc's successor
<spanish> yes, sorry :D
<spanish> of being me, and even more when haxe is sort of a cross-platform compiler, I'd split it in several binaries, for example, an assembler taking text input and giving swf's as output, a php front-end, a c++ fron-end, etc
<spanish> it has grown a lot, and it's starting to be a bit of a mess
osnr1 has quit [Quit: Leaving.]
ttamttam has joined #ocaml
<spanish> a linker would be fine as well, the assembler could convert images or graphics to abc's, not having to be done by any front-end, etc, luckily I don't have to deal with swf's or flash for that matter anymore
<gasche> isn't it open-source? I'm sure they would welcome contribution suggestions.
ttamttam has quit [Client Quit]
<spanish> I told to someone called simon, which is one of the maintainers, but he didn't seem to like any of my ideas
<spanish> yb that time I already had half of the code written for mtasc, so
<spanish> *by that time
<spanish> how they use that for big projects, I don't know, they don't seem to use configure/make or others
<spanish> in fact, haxe has some built-in thing resembling a subset of make, in xml hehe
fraggle_laptop has joined #ocaml
<ollehar1> I need a short-hand def of [< `foo | `bar], but not as
<ollehar1> type 'a t = [< `foo | `bar] as 'a
<ollehar1> cause I want to use it in a function signature, as phantom types. possible?
<gasche> type t = [ `foo | `bar ]
<gasche> then use [< t ]
<ollehar1> smart
<ollehar1> thanks
<gasche> ( [ `foo | `bar | u ] also works if you want to merge two closed cases )
jayprich has quit [Ping timeout: 256 seconds]
iZsh has joined #ocaml
mattrepl has quit [Quit: mattrepl]
eikke has quit [Ping timeout: 256 seconds]
osnr has joined #ocaml
osnr has quit [Changing host]
osnr has joined #ocaml
<rgrinberg> why do fold_left and fold_right take their arguments in their different order?
<flux> it can make sense in considering how the arguments are applied
<flux> but I don't think it's a good reason
<flux> for example the core library has uniformal argument order for all folds (AFAIK)
<rgrinberg> no, the arguments for the f are flipped
<rgrinberg> but also the initial value is labelled
<rgrinberg> and so is f
<rgrinberg> so its less of a hassle
jayprich has joined #ocaml
transfinite has quit [Quit: WeeChat 0.4.0]
fraggle_laptop has quit [Remote host closed the connection]
eikke has joined #ocaml
<gasche> rgrinberg: I consider that _left and _right indicate where the accumulator is
<gasche> fold_right is ('elem -> 'acc -> 'acc), while fold_left is ('acc -> 'elem -> 'acc)
<gasche> (the order being indicative of which is computed "first", in a sense; fold_left starts with acc [x;y; ...], and computes from "f acc x", while fold_right starts with [...;y;z] acc, and computes from "f z acc")
gautamc has quit [Read error: Connection reset by peer]
osnr has quit [Quit: Leaving.]
gautamc has joined #ocaml
ollehar1 has quit [Ping timeout: 264 seconds]
beginner42 has quit [Quit: irc2go]
ttamttam has joined #ocaml
eikke has quit [Ping timeout: 256 seconds]
ggole has quit []
m4b has joined #ocaml
<m4b> if I use ocamlopt -output-obj factorial.ml, and I want to call that factorial function from a c program, (1) what should the -o file be named? and (2) to call that function from a basic c program I just #include in the c program and call the function, correct?
<adrien> that doesn't sound like a good idea
<m4b> adrien: ok, I'll check the article; but from the man page: "Cause the linker to produce a C object file instead of an executable file. This is useful to wrap OCaml code as a C library, callable from any C program."
<adrien> yes but OCaml needs to initialize a number of things
<m4b> not sure exactly what you mean; could you elaborate?
<adrien> when you start an ocaml program, all the toplevel expression of the modules that are linked in are evaluated
<adrien> that means that if you have that code in a file by its own 'let () = print_endline "weeeeeeeeeee"'
<adrien> and you link against the corresponding module, that will be evaluated and the message will be printed
<adrien> I believe the method you described would skip such initializations
<m4b> so what is the point of that command line switch?
<adrien> well, the link I gave you uses it
<adrien> but it also does more things
<adrien> link against asmrun.a, call caml_main()
<m4b> adrien: ok, yea reading that now; thanks for the link; little more involved than I thought, but that's fine ;)
<adrien> :-)
LeNsTR has joined #ocaml
LeNsTR is now known as lenstr
ben_zen has quit [Quit: Wheeeeee]
Watcher7 is now known as Watcher7|off
Kakadu_ has quit [Ping timeout: 256 seconds]
<wmeyer``> adrien: hi
<adrien> (oh, crap, I have no excuse tonight)
<adrien> oh, hi wmeyer`` :-)
<m4b> for writing literate programs including both C and OCaml, I'm looking at noweb. Does anyone have any suggestions, etc.?
jcao219_ has joined #ocaml
jcao219 has quit [Read error: Connection reset by peer]
<wmeyer``> m4b: noweb is good, but it requires some configuration in Emacs
<wmeyer``> there is ocaml-web, but my impression is not that good
<m4b> wmeyer``: yea, was reading on website no emacs mode currently supports in for >=24
jcao219_ has quit [Read error: Connection reset by peer]
jcao219_ has joined #ocaml
<wmeyer``> m4b: it's very hard to get right, even for such a seasoned Emacs geek like me.
<wmeyer``> (not evangelising myself here)
<m4b> wmeyer``: hmmm. You mean just syntax highlighting, etc., or something else, by "hard to get right"?
<wmeyer``> but I got it to work actually, and I was happy with it
<m4b> wmeyer``: you should write an emacs mode :D
<wmeyer``> you mean noweb?
<m4b> yes
<wmeyer``> so the problem here is that it requires two modes :)
<wmeyer``> inside a single buffer
<wmeyer``> you can also try org-mode, with babel
Nahra_ has joined #ocaml
pippijn_ has joined #ocaml
<wmeyer``> i appreciate your comments always on this side, as i haven't yet done any serious literate programing
<wmeyer``> with org
<m4b> wmeyer``: ok i think you know what I mean; for example, in haskell's literate mode for latex, the latex is just unmarked, but the \begin{code} blocks are haskell highlighted, etc.
<wmeyer``> I think that's what you want, org-mode babel
<wmeyer``> yes
bacam_ has joined #ocaml
<m4b> forgive me, what do you mean by org-mode babel?
<wmeyer``> if you use Emacs, then there is an excellent structured text editing mode, and it's called org-mode
<asmanur_> wmeyer``: are you an org-mode user ? if so, would you be interested by a parser for it in OCaml that leverages the dependancy to emacs (to export especially) ?
<m4b> wmeyer``: right, i know that; but what is the babel part? do you mean the latex package?
Snark has quit [Quit: leaving]
<wmeyer``> in fact is not for structured editing, but rather for organising tasks, or markup
<wmeyer``> asmanur_: to some large extent yes :)
cross_ has joined #ocaml
foo303_ has joined #ocaml
<asmanur_> \o/
<wmeyer``> asmanur_: at the moment, I think ocsigen, ocsimore project might benefit from such parser
<adrien> you've found someone more to work on merlin? :P
<wmeyer``> if we can edit stuff inside Emacs, using org mode, and then convert it to wiki, that's great
<wmeyer``> also, mobile-org is not very good on android
<Drup> wmeyer``: using org-mode instead of wiki markup ? huuum.
<asmanur_> wmeyer``: I have such a project actually, I should release it very soon: a little demo: http://kiwi.iuwt.fr/~asmanur/projects/mlorg/docs/SYNTAX.html
Watcher7|off is now known as Watcher7
rks__ has joined #ocaml
<wmeyer``> asmanur_: that looks great asmanur_ , thanks for sharing
josch has joined #ocaml
josch has quit [Changing host]
josch has joined #ocaml
mk270_ has joined #ocaml
mathieui has quit [Ping timeout: 246 seconds]
Nahra has quit [Ping timeout: 246 seconds]
pippijn has quit [Ping timeout: 246 seconds]
mk270 has quit [Ping timeout: 246 seconds]
josch_ has quit [Ping timeout: 246 seconds]
cross has quit [Ping timeout: 246 seconds]
orbitz has quit [Ping timeout: 246 seconds]
bacam has quit [Ping timeout: 246 seconds]
foo303 has quit [Ping timeout: 246 seconds]
bitbckt has quit [*.net *.split]
PM has quit [*.net *.split]
rwmjones has quit [Excess Flood]
kaktus__ is now known as kaktus
rks_ has quit [Write error: Broken pipe]
ulfdoz has quit [Write error: Broken pipe]
bitbckt has joined #ocaml
PM has joined #ocaml
walter has quit [Write error: Connection reset by peer]
gustav___ has quit [Ping timeout: 289 seconds]
<wmeyer``> adrien: so we are these camlrs right? Alone Caml riders, that do 10x more then a single pythonist, a single man projects thwarts best incomplete python attempts, within the touch of magical wand of type inference ...
walter has joined #ocaml
orbitz has joined #ocaml
gustav___ has joined #ocaml
walter|r has joined #ocaml
<ollehar> how reasonable is it to have a "constructor" in a ocaml module?
<ollehar> *an
walter has quit [Read error: Connection reset by peer]
<wmeyer``> asmanur_: so I'd rewrite mobile-org on android using your parser, that would be my best bet. The second best bet is to allow org wikiks on ocsimore.
rwmjones has joined #ocaml
<asmanur_> is ocaml+android convenient ?
<Drup> and we could have customs quotation blocs with ocaml plugins
<wmeyer``> asmanur_: it's probably possible, but hard though.
cross_ is now known as cross
<Drup> asmanur_: there is an intern on this subject right now :3
yacks has quit [Ping timeout: 243 seconds]
<wmeyer``> third bet would be to implement Camlp4/Fan quotation to embed org
<rks__> Drup: where are you working?
<asmanur_> Drup: what do you mean ?
rwmjones has quit [Client Quit]
<Drup> rks__: eliom team
<wmeyer``> oh hi rks__
<rks__> oh ok
<rks__> hi wmeyer``
rwmjones has joined #ocaml
<wmeyer``> rks__: how are you?
mathieui has joined #ocaml
<rks__> fine thanks, and you?
ulfdoz has joined #ocaml
<wmeyer``> my saturday is dead already as for this hour
yacks has joined #ocaml
<Drup> asmanur_: one of the intern is working on trying eliom on mobiles
<wmeyer``> rks__: yes, i am fine, thank you.
<asmanur_> Drup: what do you mean "custom quotation blocs with ocaml plugins" ?
<Drup> you can have quotation blocs in org-mode
<asmanur_> yes
<Drup> #+BEGIN_BLA truc bidule #+END_BLA
* wmeyer`` feels very sad - he didn't do much today
<Drup> so we could handle those BLA with a plugin in the "parser" and do arbitrary stuff
<asmanur_> mlorg allow you to execute code in such blocks, is that what you meant ?
<wmeyer``> my fourht bet would be to rewrite Emacs and support org at very first
<wmeyer``> (of course rewrite in OCaml)
<Drup> wmeyer``: or we can use patoline
<Drup> (for the whole "document" part)
<wmeyer``> Drup: what's patoline?
<Drup> a latex-like system in ocaml
<wmeyer``> oh
<Drup> indeed :D
<wmeyer``> there are so many librarires and applications in OCaml i just dont know
<wmeyer``> and really good ones
* wmeyer`` a bit exhausted today, but feeling OK
<adrien> I only saw a few mentions of Patoline
<adrien> and that's pretty unfortunate because latex/tex is really crap
<adrien> well, rather, after 40 years, it shows some weaknesses
<spanish> tex is crap? ah
<asmanur_> Drup: were you able to compile it ?
<Drup> Didn't try yet
<adrien> spanish: it's not crap but it has so many issues
<asmanur_> i tried several time (darcs + tarball) never was able to
<spanish> issues like which adrien?
<Drup> spanish: for first, the programming language part is fucking terrible
<Drup> (and you *have* to use it if you want to do interesting stuff)
<adrien> that and it's slow and has very poor error reporting and handling
<spanish> yeah, it has a step learning curve, but you can do anything once you get hang of it, I've always used tex
<adrien> it's like ed (the editor
<adrien> )
<adrien> you get a '?'
<adrien> and then you press any random combination of C-c and C-d to exit
<spanish> of latex I think is some macro-crap, you see
<spanish> it's a bit hardy, but so powerfull, and a propper class on programming if you get to it's source
<spanish> quite a proffesional, donald
<asmanur_> still, according to patoline's dev, even the typographic engine of TeX can be improved
<m4b> adrien: lol, totally right; C-c C-d, or x, or q
<spanish> that's for sure, not to mention the libkpathsea and other patches some guys did
<adrien> I tried to fix my mistakes in the latex prompt once or twice; I'll never try again
<spanish> haha
<wmeyer``> adrien is on the dark side of VIM. The very dangerous sect.
<m4b> _beautiful_ front page for patoline.org :D
<spanish> yes, looks nice, I will bookmark it to see it some other day
<Drup> patoline just finished to compile, what problem do you got with it ?
<adrien> there are too many emacser in the ocaml community :P
<Drup> adrien: you have to admit tuareg is quite good.
<Drup> (that's the only reason I started using emacs)
<m4b> what font is the patobook written in?
<spanish> pdfinfo should tell you, if you have xpdf installed
<adrien> Drup: I agree that the vim support for ocaml has not been as good
<adrien> but all I want is what Merlin provides
<spanish> the only thing I don't like of emacs is that I have to resort to nano on small systems
<adrien> and I know its devs are working hard, even right now
<adrien> right?
<adrien> *RIGHT*?
<m4b> spanish: pdfinfo doesn't give font
<Drup> spanish: TRAMPS
<spanish> no, sorry. pdffonts was it?
<wmeyer``> adrien: yes, I praise the Emacs church!
<m4b> spanish: ya
<asmanur_> adrien: well, merlin works now so there is no need to work on that :P
<asmanur_> merlin -- issues-free since several weeks
<m4b> and thank you :)
<wmeyer``> asmanur_: nice
<Drup> asmanur_: merlin doesn't work on *my* code ;)
<Drup> there is too much ##, {{ and }} in it.
<spanish> you're welcome :D
beginner42 has joined #ocaml
<asmanur_> Drup: we had a talk with Vincent as to whether merlin could be extended to handle .eliom files
<spanish> you use it only for programming then Drup?
<asmanur_> long story short: it's a mess :P
<Drup> asmanur_: I know, I was there.
<asmanur_> oh
<asmanur_> then
<asmanur_> that was you
<adrien> asmanur_: it has support for everything related to lablgtk?
<Drup> asmanur_: I'm just trolling you ;)
<asmanur_> hm
<asmanur_> adrien: I heard of an experimental branch yet to be merged (cc def-lkb_) handling object
tane has joined #ocaml
<asmanur_> but nothing on labels I believe
<wmeyer``> asmanur_: so I see two solutions for Camlp4 support in merlin
<Drup> spanish: what do I only use ?
<spanish> emacs
<wmeyer``> first one, just don't use merlin for pre-processed files, and use something that uses toplevel to do the analysis, then it would require to recompile files, but it might be still usable.
<Drup> a very little bit for org-mode
<spanish> gnus is quite well done as well
<wmeyer``> second, provide plugins that ignore some stuff. For instance quotations in Camlp4 are fine, they are still the same class of code.
<wmeyer``> gnus rocks.
<asmanur_> wmeyer``: yes
<wmeyer``> spanish: I use Emacs for everything apart from terminal and browser
<asmanur_> It would be better if people designing extensions used quotations instead of horrible syntaxes (Drup)
<spanish> as I always have the git version, been even using elisp to access some hardware through the serial or usb->ttl
<wmeyer``> oh oh oh :D
<spanish> nice
<asmanur_> wmeyer``: gnus is a bit slow isn't it ?
<wmeyer``> nope, I appreciate people using other stuff equally :-)
<wmeyer``> it hangs Emacs
<Drup> asmanur_: hey, it's quotations ! (almost)
<def-lkb_> hi everyone, I won't stay long
<wmeyer``> asmanur_: emacs is single threaded
<wmeyer``> asmanur_: it used to spawn starttls process, but these days uses C bindings
<asmanur_> yes I know, that's what makes reading mail in emacs not so convenient
<wmeyer``> so it's much faster than 3 years ago
<wmeyer``> 4 years actually
<Drup> asmanur_: but I will change the syntax when I will do the extension point version anyway
<wmeyer``> asmanur_: but you either read emails or use Emacs.
<def-lkb_> object support has effectively been merged, by object I mean support for completing method; beside, the parser is still very sensitive to syntax errors inside classes and objects...
<asmanur_> wmeyer``: indeed but still, never found a mail client in Emacs that was like mutt, so I'm still using mutt
<def-lkb_> in git version, there is support for js_of_ocaml and ignoring camlp4 expression quotations (that, those are typed as "forall a. a")
<wmeyer``> I have to admit, i am interested in Emacs being multithreaded
<beginner42> does it make much difference if preprocess some parameters before i give them to an external c function or should do that on the c side?
<wmeyer``> spanish: I also use git version
<Drup> def-lkb_: do you also ignore {server{ }} quotations ?
<wmeyer``> asmanur_: yeah mutt is nice.
<def-lkb_> Drup: no, zero support for {{ }} syntax
<Drup> (those are not really quotations but ..)
<Drup> ok
<def-lkb_> did you manage to give good semantics to eliom syntax ?
<spanish> heh, nice, you used to get it from repo.cz (was it like that?) when emacs guys opted to promote bazaar wmeyer``?
<Drup> def-lkb_: wip
<spanish> nowadays they've gotten a bit more sensible it seems
<wmeyer``> spanish: I used git mirror
<wmeyer``> but if i have to install on a fresh machine then i use tarball with snapshot
<Drup> def-lkb_: but the type system is done, probably, eventually, If I didn't do any mistakes (which I did)
* wmeyer`` ended up joking about himself today
<spanish> a year back or so there wasn't any, cose gnu guys wanted to "twist the market" on bazaar
<spanish> actually, stallman
* wmeyer`` very tired. Hopes really to get a nice sleep.
<wmeyer``> spanish: I think, bazaar is a GNU project.
<wmeyer``> likewise Emacs, so it has to be supported properly
<spanish> yes, it is, but there wasn't a reason to kill git just because git wasn't, it's still free software
<spanish> but a after several months, they got back to allowing git
<wmeyer``> spanish: git is excellent, but for other reasons, the Emacs uses bazaar. I have nothing bad to say about it, apart that it's just more difficult to use and I lost my patches once or two.
<spanish> hehe, I never used it, we switched to git, and it works quite fine
<wmeyer``> but it's doable to use bazaar :-)
<spanish> so, no need for bazaar really
<spanish> sure it is, I guess
<wmeyer``> there are some workflows
<spanish> bazaar got promoted too late, it was alive even before git, iirc
<adrien> doesn't bzr require a _canonical_ contributor licensing agreement?
<spanish> does it? amazing
<wmeyer``> first of all, there is always a git gate, apart from that bazaar is seen as distributed version control so still with enough caution can be very nice
<def-lkb_> Drup: ok, I fear it will still be a pain to implement :P. Got to go though, bye
<adrien> yup, CLA to canonical
<adrien> or something like that
<wmeyer``> bazaar AFAIK seeks for contributors, so i am not sure if the licensing agreement is needed
ulfdoz has quit [Ping timeout: 256 seconds]
<wmeyer``> but maybe for non trivial patches
<wmeyer``> in Emacs there is no need to sign the agreement if the patch is below some threshold
<adrien> webkit has a threshold of 3 lines
<adrien> but C++ vs. elisp
<wmeyer``> I don't like idea of any agreements actually myself, let it be always open. The trouble is that Emacs is the most important GNU project. So no surprising is that it has to have procedures for contributing.
<wmeyer``> I lost faith at some point with the patches to Emacs, but have to try again. Just because it's so nice to be able to contribute to Emacs.
<spanish> pretty much anything regarding gnu does, it's a lawsuit thing they must convery to really
<wmeyer``> spanish: yep.
<wmeyer``> but they really wait for the real developers.
<spanish> we were once to send a project to gnu, and they wanted us to sign, we said we could understand, but no thanks
<wmeyer``> maybe not everyone knows how active is the mailing list
<spanish> not really willing any us company having our details just to share software freely
pr_ is now known as pr
pr has quit [Changing host]
pr has joined #ocaml
<wmeyer``> the difficulties are always with copy left, and IP
<wmeyer``> especially patents, you see, looking how it looked like before, and now, i can see a big improvement.
<adrien> the CLA is really something people disagree on and there are even differences between FSF and FSFE
<spanish> yes, I was talking to karl berry it was, we even said we would remove any mention to us and give the software for them to register as their, they wouldn't accept that either
<adrien> in any case, I wanted to do some work on libtool
<adrien> but I stopped because of the agreement
<wmeyer``> i see
<wmeyer``> that's sad
<spanish> I've gotten several patches in, though, not signing anything
<wmeyer``> sorry about this
<adrien> it's 15 pages of legalese that takes weeks (or at least used to)
<wmeyer``> it took 8 months to come to conlusion i cant really contribute to Emacs
<spanish> it's grown then, back when we were arround it it was three pages iirc, with details we had to fax or send through postal mail
<wmeyer``> so your company is not that bad at all :-)
<wmeyer``> spanish: yah.
<spanish> the problem is they have to resort to that so they can protect the software legally
<wmeyer``> spanish: it's difficult, and I still like coding in OCaml :-)
<spanish> haha
<wmeyer``> :)
<spanish> I'm not lawyer, but never understood why they can also accept bsd licensed software, being able to protect it same as fine
<wmeyer``> I use to like GPL to that extent that every piece of code I did, was always meant to be GPLed, because I was impressed how GPL changed the world, and how philisophical it is
ttamttam has quit [Quit: ttamttam]
<wmeyer``> there are difficulties for companies of course
<adrien> spanish: ah, maybe only three pages; I haven't gotten them myself, only watched people have to get them
<spanish> as long as they can prove, if needed, such software already existed on their systems and/or servers
<spanish> yes, it a great idea, though it already existed as bsd, really
<wmeyer``> spanish: but BSD is not copy left let's say it up-front, it's nice for companies, but not really so nice at protecting your rights
<wmeyer``> what makes sense id dual licensing :-)
<spanish> companies break the gpl everyday, there might be a time where they get as busy as they can't follow up with all of them, so I can't really see where the bsd fails
<wmeyer``> they break, but you know, there is always a risk of doing that
<spanish> companies can also use your work, as I could as a particular, if you opted for such a license, else, just don't publish it
<wmeyer``> but my name will not be there
<adrien> it's not because people break the law that you need to get rid of the law :P
<wmeyer``> it's implicit copy right
<spanish> there have never been problems with the bsd license, and thanks to that, you can at least have more or less same network code for mostly used OS'es
m4b has quit [Ping timeout: 248 seconds]
<spanish> I think the real problem is the copy-right law, which is non-sensical in many aspects
* wmeyer`` can't stop listening to a single song
<wmeyer``> spanish: law is non sensical always, and not objective
<spanish> well, sometimes is fair, but yes, most of it is crap
<spanish> at the service of the power
<wmeyer``> now i know, what heavy Emacs user means, it was for me always the one who contribute, and I remember my patches, and liked them a lot, but at that point i was unconcious about the process
<spanish> but that won't change until people continue to pay taxes and tributes on behalf of something they call "democracy"
<wmeyer``> now I know the first thing you do before contributing to a project, read the contribution rules
<spanish> yeah, hehe
<adrien> spanish: there are been issues with BSD license*S*
<spanish> for example adrien?
<adrien> the fact there isn't a single one is the proof
<wmeyer``> it might sound like a compliment, but GNU people were very polite, and responded promptly, reminded me
<adrien> http://en.wikipedia.org/wiki/BSD_License#4-clause_license_.28original_.22BSD_License.22.29
<spanish> unix was released under such license, many vendors already had it's source though, and bsd is about the oldest operatin system, still alive
<adrien> "advertising clause"
<adrien> unix was never released under a BSD license
<spanish> let me see
<adrien> BSD is a full reimplementation, bits after bits
<spanish> where do you think bsd unix comes from?
<adrien> AT&T actually sued
<wmeyer``> there was BSD kit or something like this
<adrien> they had AT&T code and progressively it was replaced
<spanish> not that I know, at&t ended up giveng them the source or something like that
<wmeyer``> that was part of Berkeley Unix released freely by the university
<adrien> this process was made faster when AT&T sued
<adrien> that issue made BSD weak and dangerous
<adrien> and at the same time the linux kernel appeared
<adrien> and this is likely one reason of the success of the linux kernel
<spanish> well, that was 20 years later
<wmeyer``> spanish: I don't know the history that well ...
<spanish> but either way, what's wrong if you write some software, share it and someone else makes profit out if it? whether a company or an individual?
<wmeyer``> i am pretty bad with my memory of resembling historical facts, but i do read wikipedia curiously
<spanish> I just don't recall it well really
<wmeyer``> spanish: I just wish my name was there :-)
<spanish> hehe, I'd love to have been with ritchie and the other guy when they were writting it
<adrien> I never said there was anything wrong with licensing as BSD/MIT/X11/zlib/Zope/Apache/...
<wmeyer``> I don't see problems with companies using my code
<spanish> ken thompson
<wmeyer``> but I'd like to see attribution
<adrien> but nothing's perfect
<adrien> and also it depends on what you're trying to achieve
<adrien> however I don't want my work to be used to add even more restrictions on users than there already are
<Drup> what, I cant use my WTFPL for everything ? :(
<spanish> I don't really care, you just risk to that when your work is publicly available, yo you should live with it, and hope in the future people will become more sensible
<wmeyer``> in fact this is what i wanted and not other profit to be honest, recognition of the work is maybe more important than other stuff
<spanish> that's a problem, the restrictions, yes
<wmeyer``> it depends how much you value your product ;-)
<spanish> but again, I think we're just in the niddle of a change, so
<wmeyer``> and what are the most important factors, right?
<wmeyer``> GPL might be annoying though
vpm has quit [Ping timeout: 240 seconds]
<spanish> I don't see a need to sue anybody for that, if you don't want that to happen. just don't publish your source, or do it in a "controlled" environment, that's what I think
<spanish> I really think in a future things will change and one won't have to worry about this sort of things, though
<adrien> that's basically like saying that if you don't want someone you dislike to take the tomatoes at your window, you should keep the tomatoes inside
<adrien> it's your work/property/whatever, you ought to be able to put some conditions on it
<spanish> well, not every software is critical
<wmeyer``> adrien: nice explanation :-)
<spanish> yet, you have to give to get something back, and honestly, in law the one with more money is the one who wins
<wmeyer``> i can say only, that both licensing schemese have different gotchas
<wmeyer``> btw: do you see how different is BSD bazar style of development
<wmeyer``> especially in the industrial setting?
<wmeyer``> for fast evolving projects?
<wmeyer``> it's very tough.
<wmeyer``> to draw wider picture, LLVM :-)
<wmeyer``> there *are* and *will be* clashes among companies wanting to upstream similar batch of changes
<spanish> I don't see bazaar going anywhere to be honest, git is kernel-proven to work like a charm, so I fail to see where a company would opt for the former
<spanish> perhaps of being there a couple of years sooner, but nowadays 90% of people uses git
<wmeyer``> spanish: yep. But the driver code is usually developed by the company
<wmeyer``> right?
<wmeyer``> the same
<Drup> well, git does have a very terrible cli
<wmeyer``> and imagine something standarised
<spanish> what you mean with driver code?
<wmeyer``> Drup: it used to have much worse and terrible ;-)
<spanish> I also hate python, but man, it works
<Drup> wmeyer``: it's still not good :p
<wmeyer``> most of the Linux stuff is kernel drivers that work in bazzar context
<wmeyer``> the company develops hardware, and the driver and upstream it
<wmeyer``> no competition
<wmeyer``> imagine company which develops something standarised
<wmeyer``> the standard is there, so other company want to do it too
testcocoon has quit [Read error: Connection reset by peer]
<wmeyer``> they hide and brew the LLVM branch with their stuff
<wmeyer``> the pressure rises
<wmeyer``> and one of these companies will try to upstream it
<wmeyer``> but the third company, the gate keeper for the project, will be deciding
<wmeyer``> see?
<wmeyer``> interesting isn't it ? :)
<spanish> we're far from people to stop doing the doughnougth. still it's the first time I hear dirvers for the linux kernel run bazaar
<wmeyer``> with GPL is different, first of all the companies are not allowed to brew their own branches :-)
<spanish> or anything to that matter, never seen a project outside gnu using bazaar to be honest
vpm has joined #ocaml
<wmeyer``> spanish: OH :-)
<spanish> hehe
<wmeyer``> apologises, i didn't get you, you didn't know about Open Source model :-)
<wmeyer``> sorry, now I think conversation is more clear.
<spanish> heh, eri raymond? :D
<wmeyer``> yep
<wmeyer``> so no linux kernel does not use Bazzar VCS but uses git and bazaar model of development
<wmeyer``> spanish: sorry, a tiring day.
<spanish> sure, you're fine
<spanish> ok, so it could be, I'm not too familiarzed with the kernel at that level
<wmeyer``> i am not either!
<wmeyer``> but the example what kind of problems in the industry both license have
<wmeyer``> so BSD is fine, but weird too
<wmeyer``> GPL is more streamlined but also makes development difficult
<spanish> yes, I do know the problems of gpl when it comes to low-level hardware development
<adrien> 23:27 wmeyer`` : with GPL is different, first of all the companies are not allowed to brew their own branches :-)
<adrien> they definitely are
<wmeyer``> Drup: is not so good but at least works ....
<spanish> and for sure, legally one migth give problems the other doesn't
<wmeyer``> but they can't release the product!
<wmeyer``> (to adrien)
<adrien> code goes with the binaries; if the binaries go nowhere...
<wmeyer``> so yes, brewing branches is fine, but gets nowhere, if the code can't be released
<adrien> yup, but many companies don't need to do that
<spanish> but all that behind low-level hardware stuff, to protect innovations from others, really means
<wmeyer``> spanish: this is the main reason of companies to be pre-cautiuis of GPL
<wmeyer``> and they do infringe GPL on many ocassions
<spanish> protecting that same information from the end-user, every single company knows exactly what the other is doing, is quite a harsh environment the elctronics field
<wmeyer``> but that's how it works, at least myself i observed this
<wmeyer``> yep
<wmeyer``> it's indeed
<spanish> yes, but that won't change until by law, a product to made will see everything released, say, x years after being obsoleted
<wmeyer``> i am not that far to say, that GPL is a good choice for Linux kernel though.
<spanish> again, power makes laws, and they got the power, but things would change in the future if power sees people behaves differently
<spanish> still, both licenses say clearly you can use my work, whether a company or an individual, for fun or profit, which is the key point for me
Yoric has quit [Ping timeout: 264 seconds]
jayprich has quit [Ping timeout: 256 seconds]
bkpt has joined #ocaml
<wmeyer``> spanish: yep, and I do love open code (not saying open source).
<wmeyer``> open source is process, "open code" is here that the code is published.
<spanish> me too, it's the only way the human being will advance, extending that same policy to other fields
<wmeyer``> exactly
beginner42 has quit [Quit: irc2go]
<spanish> I've always though one of the biggest problems of current economical model is it will always make it easier for a reduced number of companies to grow until they finally predominate the market
<spanish> so one solution would be to just prohibit companies at all, and enforce cooperation as self-employed indivudals, I bet that would even stop the premade sinusidal curve capitalism draws
<spanish> where there are 10 years of crisis, ten or twenty no, again 10 years crisis..
<spanish> where, crisis might be a spanish word, I don't know, just talking about the collapse we're going through
bkpt has left #ocaml []
bkpt has joined #ocaml
osnr has joined #ocaml
osnr has quit [Changing host]
osnr has joined #ocaml
eni has joined #ocaml
ben_zen has joined #ocaml
spanish has quit [Quit: Leaving]
<ollehar> anyone awake_
<ollehar> ?
<jpdeplaix`> wmeyer``: feel free to propose a patch for ocsimore :)
<ollehar> hm
Nahra_ has quit [Quit: leaving]
gnuvince has quit [Remote host closed the connection]
<wmeyer``> jpdeplaix`: thanks :-)
gnuvince has joined #ocaml
<Drup> ollehar: last time I check, I was.
<ollehar> why can't I do
<ollehar> module type GRADSTUDENT (S : STUDENT) = sig ...
<ollehar> include one sig into another?
<ollehar> Drup: ;)
<wmeyer``> ollehar: you can, using functor notation
<jpdeplaix`> ollehar: you want « include type of » no ?
<jpdeplaix`> euh « include module type of » sorry
<wmeyer``> ah yes jpdeplaix` is right
<Drup> ollehar: if you wan to include one sig in another, you don't need a functor for that
<Drup> want*
<ollehar> a functor produces an implementation, right? no, I don't need that.
<ollehar> jpdeplaix`: yes, it compiles now, thanks
<jpdeplaix`> you're welcome :)
gautamc has quit [Ping timeout: 248 seconds]
eni has quit [Ping timeout: 264 seconds]
<ollehar> with `include module type of Blah`, can I abbrivate Blah to B in some way?
<Drup> since you're including, why do you want to abbreviate ?
<ollehar> right...
<Drup> The name is going to disappear anyway.
<ollehar> yep
<Drup> If you want to have an abbreviation (and don't include) you can declare a module type
<Drup> module type B = Bla
<ollehar> another question: when including a struct, I can't seem to access record fields that or not present in the sig
<ollehar> e.g.
<ollehar> include Student
<ollehar> but record Student.tests is unbound
<ollehar> because `student` is abstract in Student sig?
<Drup> when you include, you put everything in the current "namespace" (that's not the proper thing, but it can be understood this way)
<Drup> so "tests" should be bound
<Drup> could you show the code ?
<ollehar> I could, but it's 80 rows
<ollehar> mostly comments, tho
<Drup> pastebin in there for that :)
<Drup> is*
<ollehar> I'll try to strip it, just a minute
<ollehar> row 36 gives error
<Drup> that's because you restrict the module Student with the STUDENT signature
<Drup> and in the Student signature, the type student is abstract
<ollehar> I want it to be abstract for outsiders, but not for GraduateStudent
<Drup> since it's abstract, you don't have any Constructor/deconstructor.
<Drup> use a .mli for that
<ollehar> as javas "protected"
<Drup> not really
<Drup> but when constraining with a .mli, you only constraint for the outside word, so that will do what you want
<ollehar> it's ment to be a tutorial, but declaring student twise with exactly the same code... :P
<ollehar> guess I could skip the STUDENT sig all together, of course
<Drup> yeah, it's a small problem with .mli, you may have to repeat stuff
<ollehar> thanks for your time
<Drup> no problem
tane has quit [Quit: Verlassend]
emmanuelux has quit [Ping timeout: 256 seconds]
emmanuel__ has joined #ocaml
* wmeyer`` still awake. And can't sleep.
<ollehar> wmeyer``: reading a book always helps me sleep :P
<wmeyer``> ollehar: was reading a book already today :P
<ollehar> sue the author
<wmeyer``> lol
<ollehar> especially if it was never ending story
<ollehar> sorry
<ousado> o//
<ollehar> wmeyer``: you could also write diary
<ollehar> two modules includes same module, with type t. how do I put both of them in the same list?
<ollehar> now it's like M1.t is not M2.t