kaustuv changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.1 out now! Get yours from http://caml.inria.fr/ocaml/release.html
seafood has joined #ocaml
julm has joined #ocaml
slash_ has quit [Client Quit]
coopf has quit ["ERC Version 5.3 (IRC client for Emacs)"]
Lomono has joined #ocaml
Ched has quit [Read error: 60 (Operation timed out)]
alexyk has joined #ocaml
Ched has joined #ocaml
thelema has quit [Read error: 104 (Connection reset by peer)]
thelema has joined #ocaml
matt__ is now known as sfmatt
<thelema> has anyone had batteries (or probably camlp4) mess up dependencies between .mli files?
<thelema> I have an old project I'm converting to batteries, and I'm using ocamlbuild to make it
<Alpounet> hmm, ocamlfind batteries/ocaml{c|opt} is just fine for my personal use.
<Alpounet> never got such problem IIRC.
<thelema> when I compile w/o batteries, it gets to the main.ml file, and fails with unbound value |>
<thelema> but when I compile with batteries, it can't find a type from my global.mli file in another mli file
<Alpounet> hmm
<Alpounet> weird
<thelema> yes, that's what I thought.
<thelema> the dependencies seem generated properly...
<thelema> but it's as if it can't see the global.cmx
mpwd_ has quit [Read error: 60 (Operation timed out)]
<julm> thelema: is there a Global module in Batteries? If so it could be a namespace clash.
<thelema> hmm, that's a good idea...
* thelema checks
<thelema> grr... Global : Mutable global variable
<thelema> what do others use for common values? common.ml? types.ml?
<Alpounet> common, base
mpwd has joined #ocaml
willb has joined #ocaml
<palomer> urgh, seems ":" is somehow part of the ctyp grammar
<mattam> type foo = { bar : int };;
<mattam> let r = ref 0 in {bar=!r};;
<mattam> Syntax error :)
<julm> add a space before "!"
<mattam> Yeah I know.
<mattam> I just find it strange.
<mattam> One can write [let r =f x in r] fine.
<thelema> yes, but = can't start an identifier
<thelema> it can start an operator
<thelema> let (==>) x f = f x
<palomer> hrmph...what can I use to delimit a ctyp...
<julm> palomer: parenthesis?
ulfdoz_ has joined #ocaml
<palomer> the ctyp will just gobble it up, no?
<julm> no idea
<palomer> ah no, it won't!
<mattam> But there's no way [let r => = ...] would parse is there?
mpwd has quit []
<kattla> mattam: the lexer doesn't know that
<thelema> kattla: actually, it's the parser that raises syntax errors
<thelema> and the lexer just does its job dumbly, turning any sequence of a certain group of symbols into a single token
<thelema> which the parser reports is an inappropriate token to put there.
<kattla> thelema: that's what I was referring to, for "=>" to get lexed as "=" and ">" the lexer needs more information
<thelema> kattla: ok, you're right.
<thelema> or the parser needs to look at the token more, and try to break it into '=' + some other token
<palomer> err
<palomer> what part of the grammar handles constructors and qualified constructors
<palomer> like Plus, Foo.plus, Foo.Bar.plus ...
ulfdoz has quit [Read error: 101 (Network is unreachable)]
ulfdoz_ is now known as ulfdoz
willb has quit [Read error: 110 (Connection timed out)]
<thelema> Is there an ocamlbuild tag to link in Graphics?
<julm> palomer: [val_longident]?
<thelema> i.e. the equivalent of [-libs graphics]
<palomer> julm, cool!
alexyk has quit []
<Alpounet> g'night guys
<julm> bn \o_
<thelema> cheers
<palomer> and how do you take the string of an ident?
Alpounet has quit ["Quitte"]
<julm> but by using #ident instead of #expr
<palomer> whoa
<palomer> that's pretty cool
* palomer bookmarks it
alexyk has joined #ocaml
mpwd has joined #ocaml
* kattla just got polymorphic print (via type classes) in her toy language
* kattla is very happy :)
<palomer> kattla, does your toy language have a parser?
<kattla> yes
islon_s has joined #ocaml
<islon_s> is there any f# programmer here?
<thelema> islon_s: mostly ocaml, but some F#
<palomer> whoa, the emacs sidebar isn't as trivial as I thought
<islon_s> i want to load a script (fsx) file from inside my f# code (non script)
<mrvn> islon_s: Do you also look for hot single wimen in (male)gay bars?
<julm> mrvn: islon_s first asked on #fsharp but had no answer
<islon_s> yes
islon_s has quit ["#quit"]
<mrvn> .oO(No wimen in the singles bar. They must all be in the gay one. :)
<palomer> is there any danger to doing let a = <:expr< () >> in <:expr< ( $a$,$a$) >> ?
<julm> palomer: what danger are you thinking about?
<palomer> well... for example...
<palomer> erm
<palomer> locations are kept for everything, right?
<palomer> but a appears in 2 locations
<mrvn> the two a will be the same
<palomer> so there's no problem in using the same value many times?
<palomer> camlp4 doesn't do any hash voodoo magic?
Camarade_Tux has joined #ocaml
Camarade_Tux has quit [Read error: 104 (Connection reset by peer)]
<julm> palomer: I've looked into Camlp4/Struct/Loc.ml[i] and found no comment warning about such way of doing things; so I presume it's safe. :'°)
<mrvn> What else would you want to do? let a = ... in let b = a in <:expr< ( $a$,$b$) >> ?
Camarade_Tux has joined #ocaml
Camarade_Tux has quit ["Leaving"]
r0bby has quit [Connection timed out]
<palomer> mrvn, yeah
<mrvn> let b = a is a total nop.
<palomer> oh, sorry
<palomer> let a = .. in let b = ... in <:expr< ($a$,$b$) >>
<palomer> where the ... are equivalent but not equal
alexyk has quit []
<palomer> (ie a == b but not (a = b))
<mrvn> the opposite
<mrvn> ... could have side effects
<palomer> let a = ... in let b = a in <:expr< ($a$,$b$) >> certainly does not satisfy not (a = b)
<mrvn> # let a = 1 in let b = 1 in a = b;;
<mrvn> - : bool = true
<mrvn> # let a = 1 in let b = 1 in a == b;;
<mrvn> - : bool = true
<mrvn> oeh, stupid optimizer
<julm> mrvn: (==) is the same as (=) for ints
<mrvn> # let a = 1::[] in let b = 1::[] in a = b;;
<mrvn> - : bool = true
<mrvn> # let a = 1::[] in let b = 1::[] in a == b;;
<mrvn> - : bool = false
<palomer> ah, woops
<palomer> I meant the opposite
<mrvn> as I said. :)
<palomer> :P
thelema has quit [Read error: 104 (Connection reset by peer)]
ikaros has joined #ocaml
<palomer> the opposite would never be true
Associat0r has quit []
hkBst has joined #ocaml
Yoric[DT] has joined #ocaml
eevar2 has joined #ocaml
travisbrady_ has joined #ocaml
travisbrady has quit [Read error: 104 (Connection reset by peer)]
Yoric[DT] has quit ["Ex-Chat"]
Yoric[DT] has joined #ocaml
ikaros_ has joined #ocaml
ikaros has quit [Read error: 104 (Connection reset by peer)]
jeff_s_1 has quit [Read error: 54 (Connection reset by peer)]
Yoric[DT] has quit [Read error: 113 (No route to host)]
Yoric[DT] has joined #ocaml
bartiosze has left #ocaml []
seafood has quit []
ikaros_ has quit ["Leave the magic to Houdini"]
hkBst has quit [Remote closed the connection]
thelema has joined #ocaml
<flux> btw, huhu means, translated from finnish, rumor
<julm> huhu: in french it just means I am laughing :P
Associat0r has joined #ocaml
<Associat0r> guys at what level do you guys type annotate?
<Associat0r> if at all?
<gildor> Associat0r: you mean "let x (i: int)" ?
<mrvn> only when hunting bugs
<mrvn> or when neccessary to compile
<gildor> there is at least 3 case,
<gildor> 1st: hunting bug
<Associat0r> gildor : yes
<flux> if I've planned the interface ahead (and written it in the .mli) I will likely copy those annotations to the implementation file
<flux> and keep maintaining them for exported bindings
<gildor> 2nd: when you ignore result : ignore(x 1) is not good, I always write let _i : int = x 1 in ()
<Associat0r> in haskell they seem to annotate every top-level function
<gildor> 3rd: when you explicity want a type, typically when processing array of float
<Associat0r> I think it's to constrain the type classes in the haskell case right?
<gildor> array of float is unboxed, so you get a speedup if you specialize your type
<gildor> Associat0r: I am not sure why they do this in Haskell, ask #haskell, they will probably have better answer than I ;-)
<julm> gildor: sometimes [ignore] may be appropriate, because it keeps the warning for partial applications whereas [let _ =] does not (unless you specify a type I mean)
<mrvn> julm: it does?
<mrvn> Who hardcoded that into the grammar?
<gildor> julm: are you sure ignore keep the warning ? I think ";" keep the warning about partial application
<julm> # ignore ((fun _ _ -> ()) ());;
<julm> Warning F: this function application is partial,
<julm> maybe some arguments are missing.
<gildor> julm: ignore apply even to partially applied function (which are values just as anything else)
<julm> # let _ = (fun _ _ -> ()) ();;
<julm> - : '_a -> unit = <fun>
<gildor> ok
<flux> indeed sometimes you want to ignore that warning even in partial evaluation, if your function happens to return a function which you want to ignore
<gildor> but anyway, i was not proposing "let _ = "
<gildor> but "let _i : int = " which is not the same thing
<gildor> this form help you ensure that you don't have partial application and that the result is what you except
<julm> sure :) that was just to notify people about this feature of [ignore]
<Associat0r> guys thanks for your answers
<kattla> gildor: why not "ignore (... : int)" ?
<gildor> kattla: I do that also
<gildor> (more let ignore_int : int -> unit = ignore in fact)
Snark_ has joined #ocaml
munga has joined #ocaml
Lomono has quit [Read error: 60 (Operation timed out)]
Lomono_ has joined #ocaml
mpwd has quit []
Associat0r has quit []
Lomono_ has quit [Read error: 104 (Connection reset by peer)]
LeCamarade|Away is now known as LeCamarade
jeanbon has joined #ocaml
jeanbon has quit [Client Quit]
Alpounet has joined #ocaml
Lomono____ has joined #ocaml
_andre has joined #ocaml
Lomono____ has quit [Connection timed out]
ikaros has joined #ocaml
rwmjones_ has joined #ocaml
<kaustuv> Ooh, next ocaml meeting in Tokyo. I wonder if I can use it as an excuse to visit Japan.
<Alpounet> heh
<Yoric[DT]> :)
<julm> Tokyo OMG :O
barismetin has joined #ocaml
<gildor> kaustuv: there will be probably a meeting in France next february
<julm> nice, +1 for France and +2 for Grenoble :'°)
<gildor> julm: not in Grenoble this year
<gildor> julm: probably in Paris
<julm> too bad :(
<Alpounet> Paris... always Paris ... :-(
youscef has joined #ocaml
Camarade_Tux has joined #ocaml
<kaustuv> What's the matter with Paris?
<Alpounet> Too far from here :-p
<Alpounet> and interesting things always happen in Paris !
<Alpounet> E.g, I can't think about creating a FP User Group here in Marseille, I'd be nearly alone.
<kaustuv> Oh, I think there are a lot of functional programmers in u-mrs
<Alpounet> But most of French OCaml hackers are in Paris.
<Alpounet> kaustuv, yeah there are. Maybe you know "Grégory Lafitte" ?
<kaustuv> No, sorry, never met him.
<Alpounet> There are one or two other researchers using FP that I know of, that's all...
<Camarade_Tux> it would only take about three hours in train ;p
<Alpounet> Camarade_Tux, and too much in Euros :p
<Camarade_Tux> 40 to 50€ ? :D
<julm> 70
<Camarade_Tux> *2
<kaustuv> air france will have cheaper flights, I think
<Camarade_Tux> but as far as I can say, there are several ocaml people in the south of France too
<Camarade_Tux> kaustuv, yeah, probably
<Alpounet> Camarade_Tux, oh, where ?
<Alpounet> well, at least 100€ for flights, then <I don't know how much> for hotel
<Alpounet> far too much for a student
<Camarade_Tux> Alpounet, I can't say precisely but according the the domains in mails and even on irc (yes, I spy you all :D ), I can count several people and then, there should be more who don't take part in the mailing-list or on irc
<Alpounet> 'kay !
<julm> far too much for a student <- mutualizing is the key
<Camarade_Tux> have to go, headdache :)
* Camarade_Tux doesn't stand hot temperatures
<Alpounet> julm, first have to find someone to mutualize with heh !
<Camarade_Tux> could be nice to make a map of people using ocaml, like those on ohloh
<Alpounet> yay
<Camarade_Tux> (which means we could use ohloh directly...)
<Alpounet> you should start this and then advertize it on the ML
<julm> that would be nice indeed
<Camarade_Tux> I know a few people can already be found on the ohloh map but yeah, should be more known (maybe with something else than ohloh)
<Camarade_Tux> I'll probably do that by the end of the week, now really have to go
Camarade_Tux has quit ["Leaving"]
<Alpounet> and then I would be able to study whether it would be feasible (= worth) to start some IRL activity in Marseille about OCaml
<gildor> Alpounet: you mean some kind of local user group ?
dileep has joined #ocaml
alexyk has joined #ocaml
<Alpounet> gildor, yeah.
willb has joined #ocaml
<gildor> Alpounet: just do it (TM), it is by starting that you can see if it is worth
<Alpounet> there's nobody I know in here who uses OCaml
<Alpounet> that'd be ... weird to start a user group with nobody in it at the beginning except me !
<Alpounet> brb
Alpounet has quit ["Quitte"]
bombshelter13_ has joined #ocaml
sporkmonger has joined #ocaml
Lomono__ has joined #ocaml
elehack has joined #ocaml
maxote has quit [Read error: 60 (Operation timed out)]
Snark_ has quit ["Ex-Chat"]
willb has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
mpwd has joined #ocaml
alexyk has quit []
animist has quit [Read error: 110 (Connection timed out)]
travisbrady_ has quit []
dileep has quit ["Leaving"]
sfmatt has quit [Remote closed the connection]
alexyk has joined #ocaml
eevar2 has quit ["This computer has gone to sleep"]
animist has joined #ocaml
stan_ has joined #ocaml
stan_ has quit [Client Quit]
willb has joined #ocaml
alexyk has quit []
seafood has quit []
Alpounet has joined #ocaml
animist has quit [Read error: 113 (No route to host)]
__marius__ has quit [Remote closed the connection]
Associat0r has joined #ocaml
travisbrady has joined #ocaml
<hcarty> Does Batteries work on 3.10.2?
<Alpounet> If the current version doesn't, the previous should
travisbrady has quit []
<Alpounet> but it should, yeah
<hcarty> I got an off-list email from someone saying that they are having trouble compiling the GODI Batteries package under 3.10.2.
<Alpounet> did they quote some errors ?
<hcarty> Alpounet: It was extLexing.ml not matching interface extLexing.cmi
<Alpounet> hmm
travisbrady has joined #ocaml
<hcarty> I think I've seen questions from others about this same issue. IIRC it had to do with a 3.10.x -> 3.11.x change.
<hcarty> It may be handled properly in a later git revision though. GODI has the beta release.
mpwd has quit []
<Yoric[DT]> By default, we're targetting 3.11.
<Yoric[DT]> Although it *should* work with 3.10.2
<hcarty> Yoric[DT]: Ok, thanks. That's what I thought.
<hcarty> This person is using 3.10.2 and the Batteries beta package from GODI
<rwmjones_> Yoric[DT], I had some problems building batteries for fedora the other day ... I'll have to dig them out for you
<Yoric[DT]> that would be great
alexyk has joined #ocaml
Lomono__ has quit ["Don't even think about saying Candlejack or else you wi"]
Snark has joined #ocaml
alexyk has quit []
alexyk has joined #ocaml
Lomono__ has joined #ocaml
r0bby has joined #ocaml
det has quit [Remote closed the connection]
r0bby has quit [Read error: 104 (Connection reset by peer)]
r0bby has joined #ocaml
det has joined #ocaml
r0bby has quit [Read error: 54 (Connection reset by peer)]
r0bby has joined #ocaml
alexyk has quit []
barismetin has left #ocaml []
alexyk has joined #ocaml
rwmjones_ has quit ["Leaving"]
alexyk has quit [Read error: 104 (Connection reset by peer)]
alexyk has joined #ocaml
psnively has joined #ocaml
psnively has left #ocaml []
alexyk_ has joined #ocaml
alexyk has quit [Read error: 104 (Connection reset by peer)]
aij has quit ["trying to fix openafs"]
aij has joined #ocaml
alexyk_ has quit [Read error: 104 (Connection reset by peer)]
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
Snark has quit ["Ex-Chat"]
maxote has joined #ocaml
alexyk has joined #ocaml
alexyk has quit [Read error: 104 (Connection reset by peer)]
alexyk has joined #ocaml
alexyk_ has joined #ocaml
alexyk has quit [Read error: 104 (Connection reset by peer)]
alexyk_ has quit [Client Quit]
_andre has quit ["Lost terminal"]
sgnb has quit [Remote closed the connection]
sgnb has joined #ocaml
alexyk has joined #ocaml
komar__ has joined #ocaml
alexyk has quit []
rAphael has joined #ocaml
komar__ has quit [No route to host]
alexyk has joined #ocaml
rAphael has quit ["leaving"]
bombshelter13_ has quit []
julm has quit [Read error: 110 (Connection timed out)]
elehack has quit ["Leaving"]
hkBst has joined #ocaml
<palomer> http://pastebin.com/mbcdbae5 <--what's this error about??
<palomer> http://pastebin.com/m21f6dd5e <--slightly simpler
<Yoric[DT]> You need a cast.
<palomer> where?
<Yoric[DT]> IIrc, [foo () :> foo] or something such.
<palomer> err, foo isn't a type
<Yoric[DT]> Erf, it isn't a class, my bad :)
* Yoric[DT] hasn't used objects in some time.
<palomer> http://pastebin.com/m1efa3380 <--same error
<palomer> (using classes)
<palomer> the problem is the ?
<kattla> # let f g = g ~x:1;;
<kattla> val f : (x:int -> 'a) -> 'a = <fun>
<kattla> # f (fun ?(x=0) -> ());;
<kattla> Error: This function should have type x:int -> 'a but its first argument is labeled ~?x
<kattla> related?
<palomer> kattla, probably!
<palomer> is this a bug?
<kattla> I think it is more a limitation of the type checker
youscef has quit ["KVIrc 3.4.0 Virgo http://www.kvirc.net/"]
<kattla> palomer: have you tried using class types to work around it?
<palomer> yeah, you have to cast using a class type
<palomer> still kind of a bummer
<kattla> yes, it is definitely an inconvenience
slash_ has joined #ocaml
ikaros has quit ["Leave the magic to Houdini"]
<mrvn> Can methods have optional arguments?
<palomer> well, technically, a method can return a function which has optional arguments
<palomer> so method ?(foo=bar) = baz is the same as method = fun ?(foo=bar) -> baz
<mrvn> # let rec foo _ = object (self) method bar ?(baz = "moo") () = self#bar ~baz:baz () end;;
<mrvn> val foo : 'a -> < bar : ?baz:string -> unit -> 'b > = <fun>
<mrvn> That works. But s/self/foo ()/ gives the old error.
<palomer> yeah
<palomer> it's pretty screwy
Camarade_Tux has joined #ocaml
jeanbon has joined #ocaml
Camarade_Tux has quit ["Leaving"]
jeanbon has quit [Client Quit]
mpwd has joined #ocaml
hkBst has quit [Remote closed the connection]
mpwd_ has joined #ocaml
slash_ has quit [Client Quit]
mpwd has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has quit ["Ex-Chat"]
Ppjet6 has quit [Read error: 104 (Connection reset by peer)]