mfp changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.11.2 released | Inscription for OCaml Meeting 2010 is opened http://wiki.cocan.org/events/europe/ocamlmeetingparis2010
tarbo2 has joined #ocaml
avsm has quit [Quit: Leaving.]
ikaros has quit [Quit: Leave the magic to Houdini]
derdon has quit [Quit: derdon]
tmaeda is now known as tmaedaZ
Yoric has quit [Quit: Yoric]
Drk-Sd has joined #ocaml
mutew has joined #ocaml
Smerdyakov has quit [Quit: Leaving]
yakischloba has quit [Quit: Leaving.]
_unK has quit [Remote host closed the connection]
_unK has joined #ocaml
tarbo2 has quit [Ping timeout: 246 seconds]
tarbo2 has joined #ocaml
tarbo2 has quit [Changing host]
tarbo2 has joined #ocaml
mutew has quit [Quit: leaving]
boscop_ has joined #ocaml
boscop has quit [Ping timeout: 240 seconds]
joewilliams_away is now known as joewilliams
valross has joined #ocaml
joewilliams is now known as joewilliams_away
Drk-Sd has quit [Quit: {'EXIT', Drk-Sd, "bye"}]
hiptobecubic has joined #ocaml
_unK has quit [Remote host closed the connection]
ski_ has joined #ocaml
maskd has quit [Quit: leaving]
boscop_ has quit [Quit: Gxis revido!]
jeddhaberstro has quit [Quit: jeddhaberstro]
poet has joined #ocaml
<poet> is there a built in function to apply a function to each element in a list, collect the return values in a list, and return that list?
<poet> nevermind, found it. List.map
<poet> if I define a function inside another function with a nested let, are the variables from the top function within the scope of the nested function ?
<julm> yep
<poet> julm: so that would be a closure ?
yakischloba has joined #ocaml
caligula__ has joined #ocaml
caligula_ has quit [Ping timeout: 260 seconds]
<julm> poet, I don't know
<julm> a closure is rather a function partially applied, to my mind
<poet> I've put together a minimal example: https://pastee.org/nn36e Can someone tell me why ower_name is not in scope of the method tag_possessions ?
Alpounet has quit [Ping timeout: 256 seconds]
<julm> poet: because tag_possessions is defined orthogonally with associate_owner
joewilliams_away is now known as joewilliams
<poet> julm: so I should define tag_possessions as an anonymous function in the argument list of List.map ?
<julm> poet: try this: http://vpaste.net/Xk7pJ
<poet> julm: ah, that makes sense
<poet> thanks :)
<julm> yw
djanderson has joined #ocaml
Amorphous has quit [Read error: Operation timed out]
joewilliams is now known as joewilliams_away
joewilliams_away is now known as joewilliams
Amorphous has joined #ocaml
<hiptobecubic> Does ocaml handle laziness the way haskell does? For example if you want to map a function to the first 100 elements of an infinite list?
<flux> you have explicit laziness in ocaml. however, constructs such as lazy lists need to be implemented separately. for example Batteries has a module called LazyList
<flux> it's not the best idea to have implicit laziness and side-effects in a language
<flux> (in the same language that is ;))
yakischloba has quit [Ping timeout: 258 seconds]
<hiptobecubic> flux, oh.
joewilliams is now known as joewilliams_away
joewilliams_away is now known as joewilliams
yakischloba has joined #ocaml
thrasibule has quit [Ping timeout: 256 seconds]
sshc has joined #ocaml
<poet> is there a function to print the type of a variable?
<poet> or a way to print it at compile time
<sshc> yes and no
johnnowak has joined #ocaml
<sshc> that unhelpful oxymoron is common enough for me to use to give the illusion of contributing to the discussion
<julm> :D
<poet> :-p
johnnowak has quit [Client Quit]
<julm> poet: there are the low-level Obj.is_int Obj.is_block and Obj.tag, but to have something more precise you will probably have to write your own function
<julm> also checking out Extlib, or perhaps Batteries for their dumping function may help
<julm> -precise+accurate
tarbo2 has quit [Quit: leaving]
cataska has joined #ocaml
tarbo2 has joined #ocaml
orbitz has quit [Ping timeout: 256 seconds]
hiptobecubic has quit [Quit: For a holy stint, a moth of the cloth gave up his woolens for lint.]
orbitz has joined #ocaml
Submarine_ has joined #ocaml
ttamttam has joined #ocaml
joewilliams is now known as joewilliams_away
ttamttam has quit [Quit: Leaving.]
Yoric has joined #ocaml
prigaux has quit [Quit: leaving]
poet has quit [Quit: poet]
landstalkerx has left #ocaml []
fx_ has joined #ocaml
ttamttam has joined #ocaml
_zack has joined #ocaml
yakischloba has quit [Quit: Leaving.]
infoe has quit [Ping timeout: 256 seconds]
infoe has joined #ocaml
rwmjones_lptp has joined #ocaml
rwmjones_lptp is now known as rwmjones
stmi has joined #ocaml
Alpounet has joined #ocaml
stmi has left #ocaml []
_zack has quit [Quit: Leaving.]
yakov has joined #ocaml
<yakov> hey
<Yoric> :)
<Yoric> hi
<yakov> where can I grab development version of camlp5?
<yakov> 5-5.12 does not compile with ocaml 3.11.2
<yakov> I found several patches against 3.11.1 for Debian Linux though..
<det> <Yoric[DT]> But OCaml is often able to optimize this “create a new bullet each time” to “reuse the same bullet”.
<det> I dont think this is actually true
<det> Am I wrong ?
<det> I think tuples in Ocaml always allocate, even if you are using one as an accumulator
_zack has joined #ocaml
yziquel has quit [K-Lined]
<Yoric> det: iirc, that's not necessarily the case, in presence of tail-recursion.
<Yoric> This being said, gottago.
<Yoric> Cheers.
Yoric has quit [Quit: Yoric]
valross has quit [Quit: Ex-Chat]
avsm has joined #ocaml
avsm1 has joined #ocaml
avsm has quit [Read error: Connection reset by peer]
avsm1 has left #ocaml []
rwmjones has quit [Ping timeout: 272 seconds]
_andre has joined #ocaml
kaustuv has joined #ocaml
ASpiwack has joined #ocaml
yakov has quit [Ping timeout: 245 seconds]
ikaros has joined #ocaml
_zack has quit [Quit: Leaving.]
rwmjones_lptp has joined #ocaml
rwmjones_lptp is now known as rwmjones
maskd has joined #ocaml
pimmhogeling has joined #ocaml
maskd has quit [Ping timeout: 260 seconds]
maskd has joined #ocaml
_zack has joined #ocaml
rwmjones has quit [Ping timeout: 252 seconds]
rwmjones_lptp has joined #ocaml
rwmjones_lptp is now known as rwmjones
ski_ has quit [Quit: Lost terminal]
rwmjones has quit [Read error: Operation timed out]
thrasibule has joined #ocaml
rwmjones_lptp has joined #ocaml
rwmjones_lptp is now known as rwmjones
derdon has joined #ocaml
pimmhogeling has quit [Ping timeout: 272 seconds]
pimmhogeling has joined #ocaml
_zack has quit [Quit: Leaving.]
_unK has joined #ocaml
filp has joined #ocaml
thrasibule has quit [Read error: Operation timed out]
okagawa has joined #ocaml
_zack has joined #ocaml
Submarine_ has quit [Quit: Leaving]
pimmhogeling has quit [Ping timeout: 272 seconds]
boscop has joined #ocaml
tmaedaZ is now known as tmaeda
_zack has quit [Quit: Leaving.]
_unK has quit [Remote host closed the connection]
filp has quit [Quit: Bye]
npouillard has quit [Quit: leaving]
npouillard has joined #ocaml
ulfdoz_ has joined #ocaml
* thelema is releasing batteries 1.0.1
ulfdoz has quit [Ping timeout: 240 seconds]
okagawa has left #ocaml []
<flux> ooh
<flux> what's new?
<thelema> bug fixes
<thelema> not even improved documentation.
<thelema> But I wanted to get it out anyway.
<flux> release early, release often?
<thelema> very
<thelema> I realize I need to optimize the release process more - it's still a bunch of work creating the release in gforge
joewilliams_away is now known as joewilliams
<hcarty> thelema: Very nice work on the refactored Batteries btw. I've been dormant for a while, but I've been toying with 1.0 a bit and the new structure seems nice.
<thelema> hcarty: thanks. I've got some changes I want to make in the Set structure for 1.1
<thelema> Basically putting PSet into Set and PMap into Map
<hcarty> Is it possible to create a function along the lines of (open Bigarray let f ?(layout = c_layout) x = Array1.create float64 layout x) and have the argument "layout" stay as "'a layout" rather than staying fixed as "c_layout layout"?
<hcarty> thelema: That seems like a logical change
<hcarty> I think this is a FAQ somewhere, but I haven't found it...
<thelema> hcarty: thank jharrop for the idea.
<thelema> hcarty: I don't think you can do that - how would you recover the missing polymorphism?
<hcarty> thelema: Ok, thanks. I'm not sure, I was hoping there was some type system magic I missed :-)
<thelema> ah... maybe you could do it by not using the easy optional arguments...
<hcarty> Yes, I was hoping the easy optional argument way would work. But it looks like I need to stick with normal arguments.
<thelema> do f ?layout x = let layout = match layout with None -> c_layout | Some l -> l in Array1.create float64 layout x
<thelema> s/do/let/
<hcarty> thelema: Same result, sadly
<thelema> :(
<hcarty> Making the entire module a functor should work as well I think, though I'm not sure if that is less work than making the layout a required argument for the appropriate functions
<thelema> I guess the type of layout unifies with c_layout... hmm
itewsh has joined #ocaml
pimmhogeling has joined #ocaml
* rwmjones grumbles
<rwmjones> how to hoist this non-tail-rec loop case to use an accumulator?
<rwmjones> | x :: (y :: _ as ys) when x = y ->
<rwmjones> let (nr, _), ys =
<rwmjones> match loop ys with [] -> assert false | a :: b -> a, b in
<rwmjones> (nr+1, x) :: ys
<thelema> rwmjones: loop is your main function?
* thelema stops thinking about it and does semi-real work
<rwmjones> ok I think I've done it now
<rwmjones> yeah that works ... here's the answer :-)
<rwmjones> let chars = String.explode str in
<rwmjones> - let rec loop = function
<rwmjones> - | [] -> []
<rwmjones> - | x :: (y :: _ as ys) when x = y ->
<rwmjones> - let (nr, _), ys =
<rwmjones> - match loop ys with [] -> assert false | a :: b -> a, b in
<rwmjones> - (nr+1, x) :: ys
<rwmjones> - | x :: ys -> (1, x) :: loop ys
<rwmjones> + let rec loop acc = function
<rwmjones> + | [] -> List.rev acc
<rwmjones> + | x :: xs ->
<rwmjones> + let rec loop2 i = function
<rwmjones> + | y :: ys when x = y -> loop2 (i+1) ys
<rwmjones> + | ys -> i, ys
<rwmjones> + in
<rwmjones> + let count, ys = loop2 1 xs in
<rwmjones> + let acc = (count, x) :: acc in
<rwmjones> + loop acc ys
<rwmjones> in
<rwmjones> - let frags = loop chars in
<rwmjones> + let frags = loop [] chars in
<orbitz> rwmjones: a pastebin would be a nicer place to put yoru code
<det> am I the only person who dislikes "function" ?
<flux> yes
<orbitz> 'function' is terribly named
boscop has quit [Read error: Connection reset by peer]
<det> besides the name, I always feel like it makes code harder to read
bzzbzz has quit [Quit: leaving]
<orbitz> det: I only really use it on a real unary function
<orbitz> let foo = function ...
<det> That's more readable, I agree
<orbitz> det: I think let foo x = function is just nonsense
<orbitz> Coming from Erlang, when I first started to learn ocaml I was annoyed that i could only usefully pattern match on function/match, but I must say only being able to match on those really simplifies a lot of things
boscop has joined #ocaml
<orbitz> I've been in a bi tof a friendly debate with someone in #erlang over matchin in Erlang and I'ave decided I'm not a huge fan of how it's done
ASpiwack has left #ocaml []
ASpiwack has joined #ocaml
<det> Does erlang offer more Haskell-like matching ?
<det> ie:
<det> f [] = 1
<det> f (x :: xs) = 2
<orbitz> det: Yes
<orbitz> foo([]) -> 1; foo([X|Xs]) -> 2.
<orbitz> det: And you can do: foo(X) -> [] = X. and if X is not [] it throws a badmatch exception
<det> Yeah, I dont like that either, makes it hard to follow the program
<orbitz> My specific complaint is
<orbitz> the pattern you match in a 'case', any variables become bound outside the case
<orbitz> so. foo(X) -> case X of Bar -> foo end, Bar. % Bar is visible outside the case
<det> I dont know how to parse that
<orbitz> det: match X with Bar -> foo
okagawa has joined #ocaml
<orbitz> , is like semicolon in Java/C/etc in Erlang
<det> In Ocaml, "Bar" wouldnt be a variable
<orbitz> I know, I'm tryign to bridge a language gap here, ideas aren't going to transalte 100%
<det> you mean: "match list with [] -> 0 | x :: xs -> 1" x and xs are bound outside the match ?
<orbitz> yes
<det> that is terrible
<orbitz> I agree
<orbitz> Another annoying thing: foo(X) -> case foo(X) of [X|Rest] -> % X is matched agaisnt teh parameter X above, so this will only succeed if teh 2 X's match
<orbitz> I *think* Erlang has some for of exhaustive pattern matching warning i can turn on to find that though
<det> what is %
<orbitz> comment
okagawa has left #ocaml []
<det> Is Foo calling itself in your example ?
ikaros has quit [Quit: Leave the magic to Houdini]
<orbitz> oh, sorry make one of those bar
<det> ah
<orbitz> det: the rpoblem is I have a habit of naming stuff I don't necesiarly care about 'Rest', so if i have a 'Rest' already defind, case mtches against that and in a language like Erlang you don't have a pretty compiler telling you that you forgot to have an exhaustic case
yakischloba has joined #ocaml
pimmhogeling has quit [Ping timeout: 245 seconds]
<det> Ohh
<det> Is this like how SML does patterm matching
<orbitz> does Ocaml do pattern matching like this or is 'match' like a 'let' where you can shadow variables?
<det> In Ocaml, any lower case identifier in a patter is a catch-all, and shadows old definitions
<orbitz> that's the behavior i'd like
<det> Erlang sounds more like what SML does
<orbitz> det: another Erlangism. foo(Bar) -> X = 2, {X, Y} = Bar. This will match on X and bind Y
<det> in SML, you cant tell if a pattern match is against a constructor or a catch-all by looking at it
<det> I have a hard time reading your Erland examples
<det> Erlang*
<orbitz> det: so Bar has to be {2, _} where _ is 'anything', or else a badmatch is thrown
<det> I expect upper case identifiers to be constructors :-)
<orbitz> det: {} is tuple constructor
<orbitz> hah
<orbitz> det: my personal opinion is I don't like mixing matching and binding.
<det> Well
<det> Ocaml doesnt do equality comparisons against variables in pattern matching
<det> it is always a constructor or a bind
<det> and it is syntactically apparent what it is
<orbitz> right
fx_ has quit [Ping timeout: 260 seconds]
<orbitz> i like that
<det> SML is the same except ...
<det> You dont know if something is a bind or a constructor
<det> it depends on the lexical environment
<det> really annoying
<orbitz> ah
<det> Oh
<det> but my point was that I dont think mixing matching and binding is the problem
<det> but mixing equality
itewsh has quit [Quit: There are only 10 kinds of people: those who understand binary and those who don't]
rwmjones has quit [Ping timeout: 272 seconds]
bzzbzz has joined #ocaml
_zack has joined #ocaml
_unK has joined #ocaml
rwmjones_lptp has joined #ocaml
rwmjones_lptp is now known as rwmjones
smimou has joined #ocaml
ttamttam has quit [Quit: Leaving.]
kaustuv has left #ocaml []
__marius__ has quit [Ping timeout: 260 seconds]
__marius__ has joined #ocaml
rwmjones has quit [Ping timeout: 260 seconds]
rwmjones_lptp has joined #ocaml
rwmjones has joined #ocaml
<derdon> rwmjones: hi
ASpiwack has quit [Quit: Leaving]
<derdon> rwmjones: I found a little bug in the tutorial
<derdon> rwmjones: the HTML tag dfn (and probably all others as well) is not rendered, e.g. on this page: http://ocaml-tutorial.org/if_statements,_loops_and_recursion
<derdon> (search for dfn on this site and you'll understand what I mean)
rwmjones_lptp has quit [Quit: Terminated with extreme prejudice - dircproxy 1.2.0]
rwmjones_lptp has joined #ocaml
rwmjones has left #ocaml []
rwmjones_lptp has left #ocaml []
rwmjones_lptp_ has joined #ocaml
rwmjones_lptp_ has left #ocaml []
rwmjones has joined #ocaml
Yoric has joined #ocaml
ttamttam has joined #ocaml
pimmhogeling has joined #ocaml
yziquel has joined #ocaml
<yziquel> say i have a private type. if there any way for a function to be typed as accepting any argument that can be subtyped to the private type?
<yziquel> is there any way....
CcSsNET has quit [Quit: User disconnected]
<thelema> your type isn't an object - is it a polymorphic variant?
<yziquel> something like "type 'a ptr = 'a = private pointer"
<yziquel> or something like "type 'a ptr = private pointer" and "type mytype = mytype ptr"
<yziquel> first one doesn't work. second one requires rectypes.
<yziquel> this way in the .ml ,you define a function that takes a 'a ptr and subtypes it to a pointer. in the .mli, you use the declaration of mytype instead of mytype ptr. (you do not have ptr in the mli).
jeddhaberstro has joined #ocaml
<yziquel> thelema: no. it's a simple type.
<thelema> how do you subtype a simple type?
<yziquel> wait...
smimou has quit [Quit: bli]
<yziquel> you subtype a simple type by declaring it private.
<yziquel> but this requires rectypes...
<yziquel> and that's clearly overkill.
spicey has joined #ocaml
<spicey> i believe there's some basic magic idea underneath, but still: why does 1/0 throws Division_by_zero, but 1. /. 0. returns float = infinity?
<yziquel> spicey: basically because as 0. is a float, you can never be sure that it is exactly 0...
<spicey> sure, but the calculations anyway have already went down the slope with (I guess pain to backtrack) infinity
<spicey> to me, it's just like returning some magic code on failure
<yziquel> spicey: int_of_float (1. /. 0.) is indeed curious.
<spicey> same with nans and int_of_float(sqrt( -1. ))
ikaros has joined #ocaml
Submarine has joined #ocaml
<spicey> i find it curious that there's an official operator "not", a syntactic sugar operator "or", but no "and"
<thelema> spicey: and is used in compound declarations... let foo = bar and bax = bar2
<spicey> bah, obviously
<spicey> now that you point it out, the lack of it is perfectly clear :)
ulfdoz_ has quit [Quit: Reconnecting]
_andre has quit [Quit: *puff*]
ulfdoz has joined #ocaml
Yoric has quit [Ping timeout: 260 seconds]
Alpounet has quit [Ping timeout: 265 seconds]
Yoric has joined #ocaml
djanderson has quit [Ping timeout: 272 seconds]
djanderson has joined #ocaml
<emias> .oO( Though it doesn't explain the existence of "or" ... )
<det> maybe or, & and lazy and ||, && are strict ?
<det> erm
<det> maybe or, & are lazy but ||, && are strict ?
mal`` has quit [Quit: Coyote finally caught me]
mal`` has joined #ocaml
mal`` has quit [Client Quit]
mal`` has joined #ocaml
yziquel has quit [Ping timeout: 248 seconds]
ofaurax has joined #ocaml
ttamttam has quit [Quit: Leaving.]
yziquel has joined #ocaml
yziquel has quit [Changing host]
yziquel has joined #ocaml
Narrenschiff has joined #ocaml
tmaeda is now known as tmaedaZ
<thelema> det: the logical operators are lazy - (true || assert false = true)
<det> ahh, k
<thelema> shouldn't be used.
<thelema> single character &
<thelema> [or] is the same as ||
<thelema> but again, deprecated
<thelema> http://caml.inria.fr/pub/docs/manual-ocaml/libref/Pervasives.html <- read here, in the section "boolean operations"
_zack has quit [Quit: Leaving.]
pad has joined #ocaml
ulfdoz has quit [Ping timeout: 272 seconds]
jeddhaberstro has quit [Quit: jeddhaberstro]
pimmhogeling has quit [Ping timeout: 245 seconds]
jorgenpt has joined #ocaml
Submarine has quit [Ping timeout: 264 seconds]
jeddhaberstro has joined #ocaml
<jorgenpt> I'm trying to make a function like pipe1, but that returns a function that takes "base", instead of passing it as an argument to the function.
<jorgenpt> This is actually homework - so the "form" of the function is static, only the expressions bound to base and f is supposed to be modified.
M| has quit [Read error: Connection reset by peer]
<jorgenpt> (fs is a list of functions that're supposed to be applied, [f1; f2; ...], in the order fn ( .. (f2 (f1 base) ) ))
M| has joined #ocaml
<jorgenpt> I'll gladly accept pointers on what to read up on, :-)
slash_ has joined #ocaml
smimou has joined #ocaml
avsm has joined #ocaml
Narrenschiff has quit [Quit: Narrenschiff]
jeddhaberstro has quit [Read error: Connection reset by peer]
jeddhaberstro has joined #ocaml
ofaurax has quit [Quit: Leaving]
Yoric has quit [Quit: Yoric]
<orbitz> jorgenpt: what are you asking?
<jorgenpt> orbitz: Nevermind, I can probably figure it out on my own, I just neeed to sit down with pen and paper.
<jorgenpt> :)
<orbitz> jorgenpt: base is whatever the base should be...
<jorgenpt> I just need to construct an f and a b so the returned value is a ('a -> 'a) function. :-)
Drk-Sd has joined #ocaml
Leonidas has quit [Changing host]
Leonidas has joined #ocaml
Yoric has joined #ocaml
mal`` has quit [Quit: Coyote finally caught me]
mal`` has joined #ocaml
Leonidas has quit [Quit: Reconnecting]
Leonidas has joined #ocaml
Leonidas has quit [Changing host]
Leonidas has joined #ocaml
Leonidas has quit [Client Quit]
jeddhaberstro has quit [*.net *.split]
djanderson has quit [*.net *.split]
Alpounet has joined #ocaml
jeddhaberstro has joined #ocaml
djanderson has joined #ocaml
Yoric has quit [Quit: Yoric]
avsm has quit [Quit: Leaving.]
ikaros has quit [Quit: Leave the magic to Houdini]