gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
lopex has quit []
ag4ve has quit [Ping timeout: 258 seconds]
ag4ve has joined #ocaml
ag4ve has quit [Ping timeout: 258 seconds]
arubin has quit [Quit: arubin]
cgroza has quit [Remote host closed the connection]
sebz has quit []
dnolen has joined #ocaml
The_third_man has joined #ocaml
sebz has joined #ocaml
ulfdoz has joined #ocaml
dnolen has quit [Quit: dnolen]
mattam has quit [Ping timeout: 276 seconds]
ulfdoz has quit [Read error: Operation timed out]
junsuijin has quit [Quit: Leaving.]
ikaros has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
edwin has joined #ocaml
sebz has quit [Quit: Computer has gone to sleep.]
ankit9 has quit [Quit: Leaving]
Kakadu has joined #ocaml
Cyanure has joined #ocaml
avsm has joined #ocaml
eikke has joined #ocaml
everyonemines has quit [Quit: Leaving.]
avsm has quit [Quit: Leaving.]
rixed has joined #ocaml
sebz has joined #ocaml
ankit9 has joined #ocaml
Kakadu has quit [Ping timeout: 252 seconds]
avsm has joined #ocaml
<adrien> sometimes, ocaml frustrates me: The method notify has type 'a. ([> `textbuffer ], 'a) Gobject.property -> callback:('a -> unit) -> GtkSignal.id
<adrien> but is expected to have type 'b. ([> `textbuffer ], 'b) Gobject.property -> callback:('b -> unit) -> GtkSignal.id
<adrien> .mli and .ml files
<adrien> (and I'm completely stuck making a change to lablgtk)
<hnrgrgr> adrien: you need to quantify the open variant as well.
<hnrgrgr> In the .ml at least.
<hnrgrgr> 'a 'b. ([> `textbuffer ] as 'b, 'a) Gobject property -> ...
<hnrgrgr> (if i remember correctly)
<adrien> I tried something like that but couldn't get it right; the actual type is:
<adrien> 'c. ('b, 'c) Gobject.property -> callback:('c -> unit) -> GtkSignal.id
sebz has quit [Quit: Computer has gone to sleep.]
sebz has joined #ocaml
larhat has joined #ocaml
sebz has quit [Quit: Computer has gone to sleep.]
lopex has joined #ocaml
everyonemines has joined #ocaml
f[x] has quit [Read error: Operation timed out]
emmanuelux has joined #ocaml
_andre has joined #ocaml
everyonemines has quit [Quit: Leaving.]
alang has quit [Ping timeout: 255 seconds]
alang has joined #ocaml
thomasga has joined #ocaml
f[x] has joined #ocaml
Boscop has joined #ocaml
Boscop has quit [Ping timeout: 260 seconds]
Boscop has joined #ocaml
dnolen has joined #ocaml
avsm has quit [Quit: Leaving.]
Cyanure has quit [Read error: Connection reset by peer]
Cyanure has joined #ocaml
dnolen has quit [Quit: dnolen]
* thelema is about to add church numeral-tagged types to his research code
avsm has joined #ocaml
avsm has quit [Client Quit]
avsm has joined #ocaml
Cyanure has quit [Remote host closed the connection]
* thelema needs to track the length of lists
emmanuelux has quit [Ping timeout: 244 seconds]
Kakadu has joined #ocaml
lopex has quit []
<thelema> and then gives up as he can't figure out how to do IO with such a monster.
everyonemines has joined #ocaml
<adrien> ^ ^
<thelema> I tried this once before, and had to give up for about the same reason - I can't specify the return type of my function that reads a list
<thelema> because I can't convert a plain list into a length-tagged-type list.
<everyonemines> What is considered the most elegant way of making functions for both Arrays and Bigarrays?
<thelema> everyonemines: use a functor
<everyonemines> thelema: I considered that but Array and Array1 have different functions for length...
<everyonemines> So I'm supposed to write separate type signatures for Array and Array 1, define a bunch of functions over...
<everyonemines> and then write a type signature for a functor...
<everyonemines> and then deal with the extra boilerplate of the functor itself...
<everyonemines> Honestly that's much more work than just copy-pasting code.
<everyonemines> Which is bad practice for a number of reasons, but it's what you're pushed towards because functors are a lot of work.
<thelema> module Array1_fixed = struct include Bigarray.Array1 let length a = dim a end
<everyonemines> hmm
<everyonemines> But you have to put the whole type signature of Array in the functor type sig, right?
<thelema> well, whatever you use of it, yes.
<thelema> copy/paste works pretty well.
<thelema> I often tweak modules right at functor application:
<thelema> module Razor2 = Razor(struct include Otern let lrmerge = lrmerge_pairing let concat = concat_simple end)
<edwin> does that require 3.12.0 or would it work with 3.11.x too?
<everyonemines> I like the module system but functors seem kind of awkward, like they could be less work.
<everyonemines> Maybe I'm using them wrong, or don't have enough practice.
<thelema> edwin: works with 3.11 - no first class modules here
<thelema> everyonemines: writing the module signature is the only hard part of functors, and 3.12 has a cheat for that - you can take the signature of a module by... well, I don't know
<edwin> can ocamlc -i write the functor signature?
<thelema> edwin: yes, that too.
<thelema> edwin: but this is done automatically at compile time, no copy/paste involved
<edwin> cool
lopex has joined #ocaml
avsm1 has joined #ocaml
avsm has quit [Read error: Connection reset by peer]
ankit9 has quit [Quit: Leaving]
<everyonemines> I was copying from toplevel output of Module X = Y;;
<everyonemines> meh
<adrien> module X (A : module type of Array) = struct ... end
<everyonemines> Well, that's if you want the entire type signature.
<adrien> yeah, no surprise there
<adrien> but writing the signature is _easy_
<adrien> you need to write 5 to 10 lines which are pretty easy
<adrien> you can even do that in the toplevel:
<adrien> module X = Array;;
<adrien> and take only the lines you want
<everyonemines> Well, I decided to try using a functor for that and now I get
<everyonemines> Values do not match: val length : ('a, 'b, 'c) t -> int is not included in val length : 'a array -> int
<thelema> everyonemines: you'll have to abstract the type as well...
<thelema> which means you'll have to fix 'b and 'c
<everyonemines> Putting aside the extra work, are there performance penalties for this?
<thelema> there's a slight performance penalty for using functors, as each operation is retrieved from a structure
<edwin> how about first class modules, is the penalty higher than functors?
<thelema> s/operation/value from the functor parameter/
<thelema> edwin: I believe the two are implemented the same, although IIRC one benchmark oddly showed first class modules as faster than no modules
<edwin> so no inlining/specialization?
<thelema> Functors can't be inlined in general because of separate compilation.
<thelema> in theory functor inlining could take place at link time, but it doesn't.
<edwin> well even if not inlining, specialization would be useful, i.e. if I use a functor a lot with module X, then it could compile an implementation specialized with module X
<thelema> Everyone agrees it would be useful, it's just a bunch of tricky code for a tiny benefit in most cases
<everyonemines> I feel like it would be easier to define in a module a set of function options, like
<everyonemines> let length = (Array.length | Array1.dim)
<everyonemines> interesting
<edwin> but is it possible to optimize first class modules at link time?
<edwin> they look much more complicated than functors
<edwin> (I mean in theory, I doubt its implemented in ocamlopt)
<thelema> if I understand correctly, first class modules just expose some of what's been going on under the scenes in order to implement functors - modules are effectively treated as records.
<everyonemines> thelema: That article's thing won't let you define functions for multiple modules, it's just another semi-solution to complaints about +. I think.
<everyonemines> and I don't mind +. as much as copying code.
<thelema> everyonemines: yes, the real solution is here: http://web.yl.is.s.u-tokyo.ac.jp/~furuse/gcaml/ (by the same author)
<everyonemines> Does INRIA incorporate stuff from compiler variants like that or Alice?
<thelema> not so much.
<thelema> Historically, it was an issue of copyright assignment vs. france's copyright system, but it seems that's been resolved, so now it's probably just inertia.
<everyonemines> I don't really want to develop for compiler variants that won't be as supported. :-/
<everyonemines> But that sort of thing is important for progress.
<everyonemines> thelema: But yeah, this GCaml seems like something a lot of people wanted in OCaml.
<everyonemines> ...but it has run-time types? You should be able to use type inference to determine which function definition to use when compiling.
<everyonemines> based on matching the type signatures. It complicates the type inference, maybe you even need a SAT solver, but it's possible.
<everyonemines> SAT solvers for type inference, now that's something I think is interesting
ankit9 has joined #ocaml
<thelema> everyonemines: if you extend ocaml's type system much, it becomes undecidable, meaning that even a SAT solver wouldn't suffice.
<thelema> in practice, once you're using a SAT solver for type inference, exponential time cost of SAT will cause some programs to effectively fail to compile.
<everyonemines> All of the inputs (constants, read_int, etc) are known.
<thelema> which is generally seen as a bad thing.
<everyonemines> Hmm, in theory I can see how that would occur, but...
<everyonemines> in practice I don't think it would be a big problem.
<everyonemines> Restricting type signatures to make inference easy would not be very hard on programmers.
<thelema> might as well do what C# and java are now doing - starting from no type inference and adding touches of it when things are obvious.
<everyonemines> Just require that no 2 function options can have the same type sig, problem solved.
<everyonemines> I think that makes everything decideable quickly.
<everyonemines> Er, I mean function input options.
<everyonemines> Then if a function has known input types, its output type is known.
<everyonemines> No SAT solver needed, actually.
<thelema> and how does polymorphism work in this system?
<everyonemines> let ( + ) = ( + ) | ( +. );;
<everyonemines> then 2.2 + 2.3 automatically chooses the correct variant by matching the type sig of the input
<everyonemines> to the types of the input
<thelema> let length = (Array.length | (Array.length : int array -> int))
<thelema> or for your (+) example, what is the type of :`let add_x x = (+) x`
<everyonemines> That gets inferred down from the input. If you just look at the function you don't know.
<everyonemines> But the input to the function is known.
<everyonemines> Your first example is pointless, but there are 2 options: match the most specific option when possible...
<everyonemines> and the general option otherwise. OR reject it because of input type sig overlap.
<thelema> yes, the first example isn't a very good one.
<everyonemines> type of let add_x x = (+) x would be (type of x)
<thelema> when you compile `add_x`, you don't have `x`.
<thelema> it may be in a different module, compiled at a different time
<everyonemines> How do you get an X with unknown type as input?
<everyonemines> Where does it come from?
<thelema> a program yet to be written.
<everyonemines> Then you need to keep the type signatures if you do partial compilation.
<thelema> add_x is library code, and needs to be compiled
<everyonemines> and finish the type inference then.
<thelema> you're doing whole-program compilation, which results in extremely slow compilation
<thelema> some SMLs do this (I forget which one)
<everyonemines> but obviously this is incompatible with ocaml's compilation model.
<thelema> and they produce very good output code.
<thelema> but the cost is the quick compile, which I value highly in ocaml.
<everyonemines> MLton?
<thelema> I think that's the one.
<bitbckt> MLton is a whole-program optimizing compiler. It's naturally a little slower.
<thelema> bitbckt: quadratically, in some cases - no?
<everyonemines> You don't need to compile libraries. You just need to save type information to choose from compiled functions.
<bitbckt> thelema: as far as I remember, yes.
<everyonemines> That can be fast.
<thelema> everyonemines: then you have libraries with exponentially many versions of functions - a huge code bloat
<thelema> also, at runtime, a polymorphic function can run faster than ten monomorphic ones because of cache size.
<thelema> so keeping the output code small has advantages
<everyonemines> thelema: Only as much bloat as the current situation with ocaml...
<thelema> everyonemines: if you monomorphize by hand, yes - you'll get code bloat.
<everyonemines> You can strip the unused functions...more compilation yes, and not something ocaml does, but that can be fast too.
<everyonemines> Extra library size isn't a big deal, at least not for ML
avsm1 has quit [Quit: Leaving.]
eikke has quit [Ping timeout: 245 seconds]
joewilliams_away is now known as joewilliams
Kakadu has quit [Ping timeout: 240 seconds]
Kakadu has joined #ocaml
larhat has quit [Quit: Leaving.]
joewilliams is now known as joewilliams_away
Cyanure has joined #ocaml
ohwow has joined #ocaml
<ohwow> Hello
<ohwow> Guys, what's a good book on OCaml? I know functional programming, and I have some experience with Scheme (Racket), but I don't know much about type systems.
<ohwow> Do you think it would be helpful to read TaPL before learning ocaml
<thelema> ohwow: files.metaprl.org/doc/ocaml-book.pdf
thomasga has quit [Quit: Leaving.]
<ohwow> hm well it appears to be a draft
<edwin> I found the ocaml tutorials quite useful, especially if you have programming background already: http://mirror.ocamlcore.org/ocaml-tutorial.org/
ulfdoz has joined #ocaml
Associat0r has joined #ocaml
<thelema> I learned most of my ocaml from the reference manual: http://caml.inria.fr/pub/docs/manual-ocaml/index.html
* thelema is amused that batteries-included made his list of package deps but as far as I can see isn't actually required by the skeleton
<bitbckt> heh.
<bitbckt> not a bad idea.
<bitbckt> sort of a "starter kit" for OCaml.
<thelema> compilation is definitely a point of arcanity.
<bitbckt> The starter kit should come with a rubber chicken and a goat sacrifice instruction sheet.
<asmanur_> I think oasis is a good starter kit, compilation-wise
<bitbckt> it simplifies a great deal.
<thelema> asmanur_: except for getting it installed in the first place
<bitbckt> the interaction with _tags is under-documented... and what thelema said.
<asmanur_> thelema: indeed
<thelema> odb should be the easiest way to get it and all its bazillion dependencies installed under most systems
<thelema> maybe time is the proper fix, as distros will have packages for oasis in time
<asmanur_> by the way, has oasis made his way in godi 3.12 ?
<bitbckt> it didn't accept -prefix the last time I installed it, so I had to hack it to respect my install path.
<thelema> bitbckt: odb?
<bitbckt> no, oasis.
<bitbckt> s/accept/obey/
<thelema> that's odd - all the oasis scripts I've worked with have had a working -prefix
<thelema> gotta go, back in 1.5hr
joewilliams_away is now known as joewilliams
joewilliams is now known as joewilliams_away
joewilliams_away is now known as joewilliams
avsm has joined #ocaml
<ohwow> Does OCaml has infinite numbers? Like in Racket (Scheme)?
<ohwow> or haskell if i recall correctly
<ohwow> I guess not by default, at least
<Kakadu> # 1.0 +. nan;;
<Kakadu> - : float = nan
<ohwow> welll
<ohwow> # 2.0**100.0;;
<ohwow> - : float = 1.2676506002282294e+030
<ohwow> and I want to get an actual result
<ohwow> what can I use?
<Kakadu> I don't know. I have never used floats at all.
mattam has joined #ocaml
<zorun> ohwow: you could use Bigint
<zorun> +s
<ohwow> Hm, I see, but I wouldn't be able to use mathematical notation with it, would I?
Anarchos has joined #ocaml
<zorun> it depends on what you call "mathematical notation" :)
<zorun> see file:///usr/share/doc/ocaml/libref/Big_int.html
<zorun> oops!
<zorun> (you got the idea)
<zorun> but you can still define (+) as bigint's "add_big_int"
Anarchos has quit [Ping timeout: 260 seconds]
<zorun> (which is quite ugly, btw, but could be acceptable if you don't use any "classic" int)
<ohwow> What about `Num'?
<ohwow> (I read about it on wikipedia page for OCaml)
<zorun> oh, I've never used that one
<zorun> interesting!
junsuijin has joined #ocaml
Boscop has quit [Ping timeout: 260 seconds]
Boscop has joined #ocaml
The_third_man has quit [Read error: Connection reset by peer]
The_third_man has joined #ocaml
joewilliams is now known as joewilliams_away
Boscop_ has joined #ocaml
Boscop has quit [Ping timeout: 252 seconds]
lpereira has joined #ocaml
<edwin> ohwow: delimited overloading might be useful when dealing with the various arithmetic packages
<edwin> but if you only use one type its probably easier to just open the module, and define the operators
<edwin> Kakadu: good point about eclipse flavour, this table only makes it worse: http://www.eclipse.org/downloads/compare.php. Guess for ocaml you'd need the platform + EGit, so probably the eclipse for C/C++ Linux developers package would be a good start
<edwin> especially that ocaml projects contain C stubs sometimes
<edwin> not much of an eclipse user though, last I used it was 5 years ago :D
Anarchos has joined #ocaml
djanatyn is now known as sad-djan
<Kakadu> edwin: no problem)
<Kakadu> eclipse-testing version works
ulfdoz has quit [Ping timeout: 260 seconds]
Kakadu has quit [Remote host closed the connection]
joewilliams_away is now known as joewilliams
Boscop_ has quit [Ping timeout: 244 seconds]
Boscop_ has joined #ocaml
edwin has quit [Quit: Leaving.]
sad-djan is now known as djanatyn
sebz has joined #ocaml
_andre has quit [Quit: leaving]
oriba has joined #ocaml
lpereira has quit [Quit: Leaving.]
avsm has quit [Quit: Leaving.]
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
joewilliams is now known as joewilliams_away
Boscop__ has joined #ocaml
Boscop_ has quit [Ping timeout: 276 seconds]
avsm has joined #ocaml
junsuijin has quit [Quit: Leaving.]
junsuijin has joined #ocaml
joewilliams_away is now known as joewilliams
Associat0r has quit [Quit: Associat0r]
emmanuelux has joined #ocaml
avsm has quit [Quit: Leaving.]
Amorphous has quit [Read error: Operation timed out]
sebz has quit [Quit: Computer has gone to sleep.]
oriba has quit [Quit: oriba]
Boscop__ is now known as Boscop
Boscop has quit [Changing host]
Boscop has joined #ocaml
Amorphous has joined #ocaml
joewilliams is now known as joewilliams_away
alang has quit [Ping timeout: 248 seconds]
arubin has joined #ocaml
arubin has quit [Client Quit]
arubin has joined #ocaml
Cyanure has quit [Remote host closed the connection]
arubin has quit [Client Quit]
arubin has joined #ocaml
emmanuelux has quit [Ping timeout: 244 seconds]
dnolen has joined #ocaml
sebz has joined #ocaml
<everyonemines> zorun: It's easier to define ( +> ) or something as add_big_int.
<everyonemines> +|
<everyonemines> +: