flux changed the topic of #ocaml to: Yes, inria.fr is back up! | Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0beta1 available from http://caml.inria.fr/pub/distrib/ocaml-3.11/ | Or grab OCaml 3.10.2 from http://caml.inria.fr/ocaml/release.html
willb has joined #ocaml
struktured has joined #ocaml
Associat0r has quit []
Jedai has joined #ocaml
code17 has quit [Remote closed the connection]
hkBst has quit [Remote closed the connection]
tomh- has quit ["http://www.mibbit.com ajax IRC Client"]
|Jedai| has quit [Read error: 110 (Connection timed out)]
jlouis has quit [Remote closed the connection]
Kerris4 has quit ["Leaving."]
dabd has quit [Client Quit]
BSWolf has joined #ocaml
mfp has quit [Read error: 104 (Connection reset by peer)]
<BSWolf> Anyone have tips on how to print values in ocaml for debugging purposes?
<mbacarella> why can't i write: let y f = f f ;; ?
<mbacarella> BSWolf, Printf.printf ?
<BSWolf> but doesn't that return an unit?
<mbacarella> yes
<BSWolf> But wouldn't that mean the types will be off?
<BSWolf> Well, let me state what my problem is. I am getting a stack overflow, clearly from recursion, but even when its not suppose to recurse it will still do so
<mbacarella> normal: if true then x else y with-debugging: if true then (Printf.printf "true!\n"; x) else (Printf.printf "false!\n"; y)
<mbacarella> you can introduce a block of statements with () and ocaml will simply the whole block evaluates to the value of the last statement in the block
<mbacarella> simply say the
mfp has joined #ocaml
<BSWolf> thank you.
<mbacarella> np
jeddhaberstro has quit []
ulfdoz has quit ["deprecated"]
psnively has quit []
threeve has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
bynari has joined #ocaml
struktured has quit [Read error: 60 (Operation timed out)]
struktured has joined #ocaml
jeddhaberstro has joined #ocaml
Palace_Chan has joined #ocaml
jeddhaberstro has quit []
Palace_Chan has quit [Client Quit]
apples` has quit ["Leaving"]
struktured has quit [Read error: 110 (Connection timed out)]
struktured has joined #ocaml
Camarade_Tux has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
<Camarade_Tux> hi Yoric[DT]
<Camarade_Tux> deadline mode ?
<Yoric[DT]> Yep.
<Yoric[DT]> But also lecture in about 1h.
* Camarade_Tux should dress up
<Camarade_Tux> see you
Camarade_Tux has quit ["Leaving"]
threeve has quit []
Yoric[DT] has quit ["Ex-Chat"]
jknick has joined #ocaml
<kattla> mbacarella: why can't i write: let y f = f f ;; ?
<kattla> you would need Rank-2 Polymorphism for that
mishok13 has joined #ocaml
<kattla> Actually, using -rectypes, it is possible to type in ocaml
<kattla> # let y f = f f;;
<kattla> val y : ('a -> 'b as 'a) -> 'b = <fun>
<kattla> But that is probably not the type you would want.
_zack has joined #ocaml
snhmib has joined #ocaml
filp has joined #ocaml
_zack has quit ["Leaving."]
Kerris4 has joined #ocaml
rwmjones has joined #ocaml
_zack has joined #ocaml
r0bby has quit [Read error: 60 (Operation timed out)]
tomh has joined #ocaml
tvn1981_0 has joined #ocaml
tvn1981_0 has quit ["Leaving"]
ulfdoz has joined #ocaml
Snark_ has joined #ocaml
jdev has quit ["Lost terminal"]
Kerris0 has joined #ocaml
mattam has quit [kornbluth.freenode.net irc.freenode.net]
vbmithr has quit [kornbluth.freenode.net irc.freenode.net]
Asmadeus has quit [kornbluth.freenode.net irc.freenode.net]
fremo has quit [kornbluth.freenode.net irc.freenode.net]
mattam has joined #ocaml
vbmithr has joined #ocaml
Asmadeus has joined #ocaml
fremo has joined #ocaml
Kerris01 has joined #ocaml
Kerris01 has quit [Client Quit]
Yoric[DT] has joined #ocaml
Kerris0 has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
asabil has joined #ocaml
Kerris01 has joined #ocaml
Spiwack has joined #ocaml
Kerris0 has joined #ocaml
Anna` has joined #ocaml
Anna` is now known as ASpiwack
<det> I just ported an application that used camlzip/extlib to batteries
<flux> was it a pain? a breeze?
<det> breeze, but, there were some pitfalls
<det> Problem is that the dependent modules are still in your environment
<Yoric[DT]> Could you post/blog about your experience somwhere?
<det> It is a really simple couple applications
<det> I'll post about it on batteries list after I use batteries a bit more
<det> and form some more solid observations
Spiwack has quit [Read error: 113 (No route to host)]
<det> I know, maybe I'll blog about it, and have that syndicated to Planet OCaml, and then link them to a pay-to-read journal entry on how to port to Batteries :p
Kerris01 has quit [Read error: 110 (Connection timed out)]
<Yoric[DT]> :)
Yoric[DT] has quit ["Ex-Chat"]
<det> It would be nice if Ocaml had the equivalent of polymorphic variants for exceptions, so you didn't have to "open "System.IO" or write "try ... with "System.IO.No_more_input ->", but instead write "try ... with `No_more_input -> ..."
<det> This is another reason to prefer option-style, but thankfully, batteries provides nice enough abstractions that I can convert my input loops to use lines_of enums or read_all
<det> Am i crazy, or did Batteries reverse the order of the accumulator argument to fold ?
munga_ has quit [Read error: 60 (Operation timed out)]
munga_ has joined #ocaml
Kerris01 has joined #ocaml
<olegfink> can someone, in the interests of pure science, provide a Batteries solution to http://www.spoj.pl/problems/SIZECON/? My non-Batteries version is over 100 chars.
<olegfink> that's I'd like to see how such a solution would look like.
Snark_ has quit [Remote closed the connection]
Kerris0 has quit [Read error: 113 (No route to host)]
<det> My quick solution, didn't put a lot of effort into being short
<det> 300 chars :p
<olegfink> okay, 98 bytes
<olegfink> (still without batteries)
<det> Can you post your non-batteries solution somewhere (like pastey.net)
<olegfink> you soultion seems to be shorter (with elimination of all good programming style)
<det> Is your solution correct? It looks like it was adding the abs value, when I interpreted the specification to ignore negative integers.
<olegfink> (x + abs(x))/2 = x, when x>0 and 0 otherwise
<det> ahh
<olegfink> it's just a size hack.
<det> what is abs for
<olegfink> sorry?
<olegfink> Batteries solutions seems shorter, as it doesn't need read_int()s
<olegfink> (and it has |>)
Snark_ has joined #ocaml
<olegfink> mneh, I don't have a Batteries install anywhere near me, so can't check.
Kerris01 has quit [Read error: 113 (No route to host)]
<det> Batteries solution looks longer to me, even with elimination of good style
<det> Also, batteries doesn't have a "pop an element, raise an exception if empty" function, so you have to waste chars on pattern matching
<olegfink> "that can't be"
<olegfink> batteries should, by its design, allow for shorter code.
<olegfink> it has fold instead of fold_left, |>, streaming input, etc.
<olegfink> as my solution will be #5 in ocaml, I think I'll submit it.
<olegfink> haha, wrong answer
<det> 152 lines with bad style
<det> I mean, chars :-)
<olegfink> wow, I really screwed the last version up.
<olegfink> that's because I either need fold_right (+1 char) or to flip arguments (oh.)
<olegfink> 94!
<olegfink> (it doesn't counts line ends)
<olegfink> but I wonder how the 77 version was done.
threeve has joined #ocaml
<olegfink> det: can you show me your destyled version?
<olegfink> Data.Mutable.Enum is the bottleneck.
<det> yes
<det> But this is kind of silliness, Batteries isn't intended to win 1-liner contests :p
<det> hmm, apparently I can just use "Enum:
<olegfink> you can use ((<)0) instead of (fun x -> x>0)
<det> I didnt know you could do that in Ocaml
<det> 124 chars now
<det> counting all chars
<olegfink> nice.
<det> Doubt I can shorten that much
<olegfink> I'd use filter ((<)0), but Array doesn't have filter, and List doesn't have init
<flux> det, replace ;;\nlet with and?
<flux> ah, never mind
<flux> strip whitespace ;)
<olegfink> no
<det> those chars dont count towards the contest
<flux> oh, ok
<det> I dont think
<olegfink> (and silly me)
<olegfink> space is 32, right?
<olegfink> so it doesn't count
<olegfink> and parens are 40 and 41, so whitespace is preferable
<olegfink> heh, I can't drop any parens from my solution
<flux> in any case, the solution is still readable
<flux> infact it doesn't even look obfuscated :-o (does it?)
Snark_ has quit ["Ex-Chat"]
<olegfink> det's? sure.
<olegfink> mine is pretty much unreadable
snhmib has quit ["Good riddance!"]
<det> System.IO.lines_of stdin|>map Int.of_string|>fun l->Enum.take(get l|>Option.get)l//((<)0)|>fold(+)0|>print_int
<det> So is mine :p
<det> still longer than yours too
velco has joined #ocaml
Smerdyakov has quit ["Leaving"]
willb has quit [Connection timed out]
<det> Enum.from read_int|>fun l->Enum.take(get l|>Option.get)l//((<)0)|>fold(+)0|>print_int
<det> OK, now I beat you :-)
<flux> victory :)
<det> btw, take appears broken:
<det> # Enum.range 0 |> Enum.take 2 |> List.of_enum;;
<det> - : int list = [1; 2; 3]
Associat0r has joined #ocaml
<flux> if it's the same bug as 1 -- 2 resulting in [2; 3] then it's fixed
<flux> (but if I understand correcly (iiuc?), not in a relase-form)
willb has joined #ocaml
<det> (Enum.from read_int|>Enum.take(read_int ()))//((<)0)|>fold(+)0|>print_int
<det> there we go, 74 total, 71 ignoring spaces
jdev has joined #ocaml
Axle has joined #ocaml
willb has quit [Connection reset by peer]
willb has joined #ocaml
Smerdyakov has joined #ocaml
Smerdyakov has quit ["Leaving"]
kg4qxk` has quit [Read error: 60 (Operation timed out)]
<olegfink> det: cool! :-)
<olegfink> by the way, doesn't Batteries have sum = fold (+) 0?
<olegfink> ah, brainlessly copying haskell doesn't make sense
<det> Batteries doesn't define sum
<kattla> sum in haskell is probably more useful than the ocaml version because of type classes
<olegfink> yep.
pango has quit [Remote closed the connection]
sporkmonger has joined #ocaml
pango has joined #ocaml
jlouis has joined #ocaml
Amorphous has quit [kornbluth.freenode.net irc.freenode.net]
rogo has quit [kornbluth.freenode.net irc.freenode.net]
ppsmimou has quit [kornbluth.freenode.net irc.freenode.net]
Amorphous has joined #ocaml
rogo has joined #ocaml
ppsmimou has joined #ocaml
Camarade_Tux has joined #ocaml
mishok13 has quit [Read error: 110 (Connection timed out)]
code17 has joined #ocaml
threeve has quit ["Leaving"]
threeve has joined #ocaml
r0bby has joined #ocaml
sscj has joined #ocaml
velco has quit ["Went wasting time elsewhere ..."]
Snark has joined #ocaml
asabil has quit ["Ex-Chat"]
Axle has left #ocaml []
filp has quit ["Bye"]
<mbishop> oh god
<mbishop> I sure hope we don't end up with Ocamlgolf
<Camarade_Tux> mbishop, ocamlgolf ?
<mbishop> Yeah, like perl golf, "I can make this program unreadable in 35 bytes!"
<mbishop> <det> (Enum.from read_int|>Enum.take(read_int ()))//((<)0)|>fold(+)0|>print_int
<mbishop> is what got me thinking :P
<Camarade_Tux> didn't see that, nicely unreadable :p
* Camarade_Tux goes
snhmib has joined #ocaml
_zack has quit [Read error: 60 (Operation timed out)]
snhmib has quit [Client Quit]
marmotine has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
Yoric[DT] has joined #ocaml
Nafai has left #ocaml []
vixey has joined #ocaml
struktured_ has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
struktured has quit [Read error: 110 (Connection timed out)]
velco has joined #ocaml
munga_ has quit ["Leaving"]
ASpiwack has quit ["Leaving"]
psnively has joined #ocaml
psnively has quit [Remote closed the connection]
psnively has joined #ocaml
<sscj> I'm having trouble building Batteries 20081112 with 3.10.2. I get the following error message:
<sscj> + ocamlfind ocamlc -c -g -package zip -I src/libs/camlzip -I src -I src/main -I src/core -I src/libs -I src/core/extlib -I src/core/extlib_threads -I src/core/baselib_threads -I src/core/toolchain -I src/core/baselib -I src/libs/common -o src/libs/camlzip/gZip.cmo src/libs/camlzip/gZip.ml
<sscj> File "src/libs/camlzip/gZip.ml", line 41, characters 9-21:
<sscj> Unbound constructor Zlib.Error
<sscj> I got camlzip 1.03 installed
mbacarella has quit [Remote closed the connection]
jdev has quit [Remote closed the connection]
mbacarella has joined #ocaml
marmotine has quit [Read error: 60 (Operation timed out)]
<det> sscj, You might have the zip package installed as "camlzip"
<det> sscj, ocamlfind list | grep -i zip
<det> what does that say
marmotine has joined #ocaml
<olegfink> det, showed that problem to my friend, he set new haskell record, 55 chars
<olegfink> and I got to 88 in my solution, but you beat me by infinity
<det> olegfink, This problem is highly dependent on the standard library
mbacarella has quit [Remote closed the connection]
mbacarella has joined #ocaml
<olegfink> yes, and to the short function names in it.
<olegfink> s/to/on/
<flux> I wonder how concepts such as mccabe's cyclomatic complexity work in functional languages
<det> olegfink, for instance, if "take" and "from" were in Standard and there was a function to pop the first element of an enum, raising an exception for empty, then it could be 55 in ocaml
<det> olegfink, I am curious about your friends solution, can you paste it here ?
Camarade_Tux has quit [Remote closed the connection]
<det> also, things like "show" shave 5 characters off of "print_int"
<mbacarella> is there something unusual about sscanf?
<det> mbacarella, unusual in what way
Camarade_Tux has joined #ocaml
<mbacarella> if i call (sscanf foo fmt f) it works fine but if i do (printf "%s\n" fmt; sscanf foo fmt f) i get the strangest compiler error
<olegfink> det, yeah, but show makes no sense without type classes, and I'm afraid ocaml doesn't make much sense with type classes (and whatever else I like in haskell), because it isn't haskell.
<mbacarella> This expression has type string but is here used with type ('a, Scanf.Scanning.scanbuf, 'b, 'c -> 'd, 'a -> 'e, 'e) format6
<mbacarella> buh?
<flux> mbacarella, the format string of sscanf isn't a string at all
<mbacarella> so why am i allowed to specify a string?
<mbacarella> sometimes
<flux> mbacarella, complier magic
<flux> mbacarella, you may use string_of_format to get a string
<mbacarella> so there IS something unusual about sscanf
<olegfink> well, all scanfs are a bit magic
<flux> well, yes, or perhaps more accurately about scanf6
<flux> uh, format6
<det> Yes, printf/scanf are language features
<flux> I don't know if printf/scanf themselves need special magic, but their types doe
<mbacarella> hrumphh
<flux> although I think I recall seeing Obj.magic there..
<det> printf is generating a function which depends on the format string
<flux> actually I'm not quite sure that's true
<flux> the functional unparsing whitepaper produces results that are strikingly similar to printf and friends
<olegfink> printf/scanf can be implemented in camlp4, right?
<flux> escpecially scanf's type
<flux> olegfink, what do you mean by that?
<sscj> det: it's installed as 'zip'
<flux> looking that pgocaml is implemented in camlp4 then I suppose yes, you could have printf-like capabilities with it
psnively has quit []
<flux> but printf/scanf as they are implemented now have nothing to do with camlp4
<det> sscj, ocamlfind query zip
<olegfink> sure, I mean more of format
<mbacarella> ok followup question
<mbacarella> Scanf.sscanf "18446744073709551615" "%Lu" (fun x -> x) ;;
<mbacarella> Scanf.Scan_failure "scanf: bad input at char number 20: int_of_string".
<mbacarella> shouldn't %Lu make it call int64_of_string?
<sscj> det: /usr/lib/ocaml/site-lib/zip
<det> mbacarella, Probably can only be 63 bits large ?
<flux> mbacarella, well, Int64.of_string gives the same results
<det> also
<flux> I guess the intxx_of_string-functions all claim to be int_of_string
<det> it is signed
<det> so half the space is reserved for negatives
<mbacarella> yeah.
<olegfink> det, hmm, he's got offline now, and I don't know if I am permitted to give his solution away, open source rulez, but who wants to spoil the competition?
snhmib has joined #ocaml
<det> Is this an active competition going on now ?
<mbishop> Is there (or will there be) some kind of "check" for Batteries? so I can do "if BATTERIES then dothis () else dothat ()" ?
<olegfink> det: it is always going? just submit a better result.
<det> oh ok
<det> 9223372036854775807 is the largest int64 you can represent, I think
<olegfink> so I'll post it whenever I get a permission from him.
<det> olegfink, no worries
<olegfink> det: to make the ocaml land less sad, it largely relies on [a..b] syntax
<det> what is that syntax
<det> I dont know Haskell very well
<olegfink> [a..b] is [a,a+1,...,b]
<olegfink> I think it's the same as Batteries' a--b
<det> o_O
<det> He uses that in his solution ?
<olegfink> yep.
<det> I dont understand how that could be of any use
<olegfink> you get a 'functional' loop this way
<olegfink> read n, generate [1..n], apply read_int to each element, filter, sum up, print
<det> ahh
<olegfink> (the 'apply' part is what's tricky)
<olegfink> I don't think that rewriting it in Batteries will beat your result
mbacarella has quit [Read error: 104 (Connection reset by peer)]
<det> like "Enum.from read_int" gives you a enum of the inputs in mine
<det> like I say, this is too much dependent on the stdlib
<olegfink> you're not checking for the number of elements, right?
<det> yes I am
<olegfink> ah
<olegfink> sorry
<det> I read 1 int, then read that many ints from stdin
<olegfink> then yes, your solution is the same
<det> if I just ignored the first element and read until EOF, I could shorten it a bit
<olegfink> it's even more elegant because it makes the enumeration explicit
<olegfink> this task seems to insist on not relying on EOF
<olegfink> (gives wrong answer otherwise)
<det> ahh
<det> mine is actually readable if you add back the whitespace
<olegfink> Batteries are really impressive, I should sit back and read the manual.
<det> / seems to have the wrong associativity, though
<det> (//), I mean
<olegfink> (you know the secret plot to add functional languages to ACM ICPC?)
<olegfink> / is filter, right?
<det> yes
<olegfink> er, //
<det> hehe, xchat did it to you too ?
<olegfink> weechat, but yes, exactly this reason
<olegfink> hmm, can't find the source for //
<olegfink> ah, src/core/extlib/enum.ml
<olegfink> enum//p1//p2 -> (filter p1 enum)//p2 -> filter p2 (filter p1 enum)
<olegfink> seems right to me
<olegfink> or my idea of associativity in ocaml is totally screwed up
marmotine has quit [Read error: 60 (Operation timed out)]
Snark has quit ["Ex-Chat"]
<det> you can't write: (1 -- 10) |> map ((+) 2) // (fun x -> x mod 2 = 0)
<det> You have to write: ((1 -- 10) |> map ((+) 2)) // (fun x -> x mod 2 = 0)
<olegfink> is there any associativity difference between |> and //
<olegfink> I saw a discussion that operators differ in associativity depending on thei first character, but I have no idea where is such a behaviour documented.
<hcarty> olegfink: Yes - the specific documentation is in the manual. Though I don't remember where
<hcarty> The OCaml associativity in this case allows for (1 + 2 > 2 - 3) to work "as expected"
<hcarty> Or rather, a > b || b > c
<olegfink> but I think the case with |> and // is more associativity than precedence
<olegfink> aha, // has more precedence and is left-associative, while |> isn't in the table.
<olegfink> ah, it's in "all other"
<olegfink> so it's also left-associative, but has lower precedence
<olegfink> so |> should probably be given more precedence? something like %>?
<hcarty> olegfink: I have found |>'s low precedence to be a good thing in general, if not for this particular example
<mbishop> I found a bug in Batteries...
* mbishop finds where to send reports
<hcarty> mbishop: I think they use the forge bugtracker
<olegfink> hcarty, so the 'fix' here would be to lower the priority of //?
<hcarty> olegfink: I suppose so
<hcarty> I'm not sure if that can be done here without reverting to camlp4
<olegfink> I mean, by changing // to something else
<hcarty> I don't know if there is a suitable operator. There may be though.
<olegfink> I can't think of anything better than >>
<olegfink> the math suggests ':', but it's a syntactic construct
<hcarty> As-is, though, some of the () can be removed for the example: "1 -- 10 |> map ((
<hcarty> +) 2)" will work as expected
marmotine has joined #ocaml
<olegfink> yes, so the problem is //'s high precedence
<hcarty> Something ugly like |/ would also work
<olegfink> it looks like a paper filter
<hcarty> I'm not sure of the specific reasons why, but use of $ >> and a few other operators are frowned on. Something to do with camlp4 issues.
<hcarty> But I think they only cause problems when used in the syntax extension code
<hcarty> |: works as well, and is perhaps less ugly
<hcarty> mbishop:
<hcarty> That's an OCaml bug
<hcarty> It's a problem with the 3.10.x camlp4
<mbishop> Oh?
<hcarty> It is fixed in 3.11, and the relevant patch applies cleanly to 3.10.2 as well
<hcarty> mbishop: Bugs #4495 and #4593, if you are at all interested
<mbishop> Hmm, well looks like ubuntu doesn't have 3.11 even in their experimental branch ("jaunty")
<mbishop> gonna grab the deb from debian experimental for 3.11
Associat0r has quit []
<hcarty> It's too bad this wasn't fixed sooner, since several fairly major distributions are releasing/have released with 3.10.x and they all have this bug
<hcarty> Which makes using camlp4 from the toplevel a royal pain
<hcarty> s/from/with/
<mbishop> Yep, can't get the debian packages without screwing my system heh...guess I can build fresh
<hcarty> You could probably patch the Ubuntu deb sources and build it that way
<hcarty> Or use godi
<mbishop> couldn't get godi to even install
<hcarty> Missing packages?
<mbishop> No, it wanted to install ocamlnet, and then complained that a bunch of godi packages would need to be removed
<mbishop> like godi-rpc and stuff that ocamlnet provides
<mbishop> but there was no way to remove them
<mbishop> the docs claim there is a "godi_delete" but it didn't exist, and "godi_console" told me it was only a bootstrap version
<mbishop> this was while I was doing bootstrap2
<hcarty> Oh yes, I remember
<hcarty> It sounds like it was picking up another installation, but I could be wrong
<mbishop> Not that I know of
* mbishop shrugs
<mbishop> anyway, I can see why most distros use 3.10...there is no 3.11 release, even on the caml site
<hcarty> Oh, definitely. 3.11 is still in beta I think.
<hcarty> The camlp4+toplevel bug has been there since 3.10.0
palomer has joined #ocaml
Asmadeus has quit [Read error: 104 (Connection reset by peer)]
Asmadeus has joined #ocaml
hkBst has quit [Remote closed the connection]
jdev has joined #ocaml
psnively has joined #ocaml
<sscj> damnit. can't get the git version of batteries to build either:
<sscj> + ocamlfind ocamlc -c -package threads -thread -I src/core -I src -I src/main -I src/libs -I src/core/extlib -I src/core/extlib_threads -I src/core/baselib_threads -I src/core/toolchain -I src/core/baselib -I src/libs/common -I src/libs/camlzip -o src/core/batteries_core_threads.cmo src/core/batteries_core_threads.ml
<sscj> File "src/core/batteries_core_threads.ml", line 35, characters 25-54:
<sscj> Unbound module Extlib_threads.ExtMutex.Mutex
<Yoric[DT]> er...
* Yoric[DT] checks whether he has pushed all his changes or forgotten something...
<Yoric[DT]> Give me 5 minutes :)
<sscj> sure :)
<Yoric[DT]> Any better?
|Jedai| has joined #ocaml
velco has quit ["Ex-Chat"]
<sscj> better, but now it's another error:
<sscj> + ocamlfind ocamlc -c -g -package zip -I src/libs/camlzip -I src -I src/main -I src/core -I src/libs -I src/core/extlib -I src/core/extlib_threads -I src/core/baselib_threads -I src/core/toolchain -I src/core/baselib -I src/libs/common -o src/libs/camlzip/gZip.cmo src/libs/camlzip/gZip.ml
<sscj> File "src/libs/camlzip/gZip.ml", line 41, characters 9-21:
<sscj> Unbound constructor Zlib.Error
<sscj> same problem I had with building 20081112
<Yoric[DT]> How did you install camlzip?
<sscj> I adapted the gentoo makefile patch
<Yoric[DT]> mmmhhhh
<Yoric[DT]> does ocamlfind find it?
<sscj> hang on, I've probably done something stupid
<Yoric[DT]> That'll have to continue tomorrow.
<Yoric[DT]> Time to call it a night.
mbac has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
Jedai has quit [Read error: 110 (Connection timed out)]
apples` has joined #ocaml
<sscj> heh, turns out it was my fault
snhmib has quit ["Good riddance!"]
threeve has quit ["Leaving"]
marmotine has quit ["mv marmotine Laurie"]
willb has quit [Read error: 60 (Operation timed out)]
dabd has joined #ocaml
vixey has quit ["Ex-Chat"]