mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab OCaml 3.10.2 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
jlouis has quit [Read error: 104 (Connection reset by peer)]
jlouis has joined #ocaml
RobertFischer has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
evn has quit [Read error: 113 (No route to host)]
evn has joined #ocaml
thelema has joined #ocaml
yangsx has joined #ocaml
prince has joined #ocaml
|Catch22| has quit ["To the best of my knowledge, I guess that I'm fresh"]
jlouis has quit [Remote closed the connection]
adu has joined #ocaml
shortcircuit has joined #ocaml
schme has joined #ocaml
yminsky has left #ocaml []
yminsky has joined #ocaml
prince has quit [Connection timed out]
evn has quit []
adu has quit ["Bye"]
<thelema> hc: I welcome them. how do you want to give them to me? Github is out of beta, so it should be trivial for you to get an account.
<thelema> hcarty: see above
schme has quit [Remote closed the connection]
palomer_ has quit [Remote closed the connection]
prince has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
seafood_ has joined #ocaml
prince has quit [Connection timed out]
netx has joined #ocaml
evn has joined #ocaml
travisbemann has joined #ocaml
prince has joined #ocaml
zarul has joined #ocaml
netx has quit [Remote closed the connection]
Linktim has joined #ocaml
prince has quit [Read error: 110 (Connection timed out)]
prince has joined #ocaml
seafood_ has quit [Read error: 104 (Connection reset by peer)]
seafood_ has joined #ocaml
prince has quit [Read error: 110 (Connection timed out)]
<flx> I remember reading about a problem with pcre and mod_caml, has that issue been resolved? I think there was a mention that apache 2.2 would fix the issue?
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
rwmjones has joined #ocaml
love-pingoo has joined #ocaml
prince has joined #ocaml
seafood_ has quit []
z[x] has joined #ocaml
rwmjones_ has joined #ocaml
rwmjones has quit [Read error: 113 (No route to host)]
OChameau has joined #ocaml
hkBst has joined #ocaml
prince has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has joined #ocaml
sporkmonger has quit [Read error: 110 (Connection timed out)]
yangsx has quit [Read error: 110 (Connection timed out)]
ikaros has joined #ocaml
sanxiyn has joined #ocaml
<sanxiyn> I got type-safe return working in OCaml! Yay me.
<sanxiyn> Usage example: http://pastebin.ca/985796
<Yoric[DT]> How do you define return ?
<Yoric[DT]> With an exception ?
<sanxiyn> With static catch/raise, which compiles to jump.
<sanxiyn> Yoric[DT]: Will post full patch soon.
<Yoric[DT]> Nice.
<sanxiyn> nontail-exit-v1 and return-v1. (The later depends on the former.)
<sanxiyn> If you look at return-v1, it's really just 12 lines in typer and 12 lines in core->lambda translator.
<flx> hm, I was expecting a camlp4 -based solution
<flx> but that's actually a patch to the language
<sanxiyn> yes
<flx> it seems doubtful such a patch would go in to the main stream fork :-o
<sanxiyn> flx: Why?
<flx> well, it's just a personal guess, that such constructs would not be appreciated. but there is already for/while, so perhaps it would fit in fine.
<sanxiyn> flx: if (some_exceptional_case) return ...; if (another_exceptional_case) return ...; style reduces nesting and makes code easier to read.
<flx> some might have another opinion whether such alterations of the control flow make code easier to read
<sanxiyn> flx: IMO this is better than "let return_value = ref ...; return_value := x" etc.
<sanxiyn> flx: Without return I often resort to "assign to reference and return at the end", which just clutters the code.
<flx> that kind of constructs are rarely used also :)
<sanxiyn> Anyway, typecore.ml is... very complex to say the least :)
<sanxiyn> I hope I got this one right... It seems to work fine.
<flx> btw, maybe number #1 reason why the patch wouldn't go in would be that it takes the word 'return' which is used a lot in monadic code
<flx> and in the code of the compiler also, as you have found
<sanxiyn> flx: It wasn't used at all in the compiler.
<flx> - let return v = Obj.magic v () in
<flx> + let ret v = Obj.magic v () in
<sanxiyn> flx: Scanf used it to deceive the typer though.
<flx> a bit ;)
<flx> right, I didn't remember it was in the standard library
<sanxiyn> Hm, what is "monadic code"?
<Yoric[DT]> erf...
<flx> code that operates by the monadic principles :)
<Yoric[DT]> Not a one-liner :)
<sanxiyn> flx: I guess you didn't expect me to understand that :)
<Yoric[DT]> Essentially, code that encapsulates imperative/side-effect-based features inside purely-functional style.
<flx> I would have expected someone to know what is monadic code before adding a 'return'-functionality into a compiler..
<sanxiyn> flx: Oops, I guess I have some homework to do...
<Yoric[DT]> Yep, probably.
<sanxiyn> flx: What would be the camlp4 based solution?
<flx> uh, definitely some homework to do :-)
<flx> camlp4-based solution would work as a preprocessor to the code
<flx> however, if an efficient return from a non-tail position would involve patching the compiler, that patching should be separate (something like mega-efficient exception handling under certain conditions or something)
Snark_ has joined #ocaml
<Yoric[DT]> iirc, OCaml's exception-handling *is* quite fast.
<sanxiyn> flx: I believe OCaml's exceptions are not checked, which makes removing try/with difficult.
<Yoric[DT]> So ?
<Yoric[DT]> How is that a problem ?
<sanxiyn> Well flx mentioned "mega-efficient exception handling under certain conditions or something".
<sanxiyn> Yoric[DT]: Thank you for "Exception Monads" link, btw.
<Yoric[DT]> My pleasure.
<Yoric[DT]> v2 is on my hard-drive but not posted yet
<sanxiyn> Ok, I have a question.
<sanxiyn> I got the impression that people don't expect OCaml language to change (e.g. introducing break/continue/return)
<flx> people can expect ocaml to change, but into a different direction
<sanxiyn> Am I wasting my time? (Certainly not, I enjoyed working on this, but in terms of effect to OCaml users)
<flx> definitely your time spent has been useful in learning how ocaml works
<sanxiyn> flx: Definitely!
<sanxiyn> flx: I learned a lot while tracing typecore.ml! :)
<Yoric[DT]> :)
<flx> but in the latter term.. well, perhaps you can offer it to the caml mailing list and ask how they feel about it
<sanxiyn> flx: I already did with break/continue. I will mail my return one soon.
<sanxiyn> flx: I am also thinking about introducing C#-like yield.
<flx> yield would be interesting, however a more generic mechanism call/cc even more so
<flx> and there are patches to do that around
<sanxiyn> I got the impression that call/cc would require major surgery to current compiler...
<sanxiyn> flx: Got a link?
<flx> nope, should be googleable
<flx> actually I don't think they are patches
<flx> the major limitation of one library-based solution is that it works only on byte-code
<flx> also I believe it could be more efficient, and by their own statement it's not production-quality
<sanxiyn> flx: I guess you were referring to ocaml-callcc by Xavier Leroy?
<Yoric[DT]> sanxiyn: the problem is that C#-like yield is essentially OCaml's streams.
<Yoric[DT]> Streams have existed since OCaml 1.
<sanxiyn> Yoric[DT]: Yes, I thought so.
<Yoric[DT]> The only missing thing is that they don't interact well with for and while.
<sanxiyn> Yoric[DT]: It does miss easy way to produce Stream.t, IMO.
<Yoric[DT]> Well, with the stream syntax, it's actually quite easy.
<Yoric[DT]> let rec stream_of_1 = [< 1; stream_of_1 >]
<sanxiyn> Yoric[DT]: How about stream that produces 1, 2, 3, ...?
<Yoric[DT]> let rec stream n = [< n; stream (n+1) >]
<sanxiyn> Hm.
<Yoric[DT]> Sorry, forgot a ' .
<Yoric[DT]> let rec stream n = [< 'n; stream (n+1) >]
* sanxiyn is searching for OCaml stream syntax and stream matching syntax to refresh his memory.
<zarul> among all programming channel that I have been.. this is the only channel that I feel people are speaking alien's language..
<zarul> :)
<sanxiyn> let sieve numbers = [< prime = next numbers; sieve (filter prime numbers) >] ?
<sanxiyn> (I hope I got the meaning across. What would be the proper syntax?)
<sanxiyn> let sieve stream =
<sanxiyn> let numbers = ref stream in
<sanxiyn> while true do
<sanxiyn> let prime = next !numbers in
<sanxiyn> yield prime; numbers := filter prime numbers
<sanxiyn> done
<sanxiyn> (Something like above was what I thought about example of using yield.)
jlouis has joined #ocaml
<sanxiyn> jlouis: Hello!
<Yoric[DT]> sanxiyn: looks about correct.
<Yoric[DT]> zarul: :)
<Yoric[DT]> (missing a "rec")
<Yoric[DT]> Oh, no, I missed something.
<Yoric[DT]> Let me try and rewrite that.
<zarul> anyway, I am learning about compiler/interpreter, and I was told ocaml might be a good choice to start playing with..
<Yoric[DT]> let rec sieve numbers = let prime = next numbers in [< 'prime; sieve (filter prime numbers) >] ;;
<Yoric[DT]> zarul: writing a compiler/interpreter ?
<zarul> yup
<Yoric[DT]> Yeah, OCaml is one of the best languages for this kind of things.
* Yoric[DT] suffers from having to teach that in C.
<zarul> but the sad thing is... I tried to find some books in Ocaml
<zarul> the only book I found got a very bad review
<zarul> I know I cand find some good tutorials at the ocaml website
<zarul> but I wish there is a good hardcopy out there
<zarul> :)
<sanxiyn> zarul: Which book got a bad review?
<Yoric[DT]> OCaml for scientists is quite good.
<Yoric[DT]> Just very expensive.
<zarul> "practical ocaml"
<Yoric[DT]> Other than that, Developing applications with OCaml is slightly old but good, too.
<sanxiyn> Yes I enjoyed Developing applications with Objective Caml too.
<sanxiyn> (Though it's OCaml 2.x book IIRC.)
<flx> and lately that "Introduction to Ocaml" (?) has been popping up at places
<flx> from what I saw, it seemed quite decent
<petchema> sanxiyn: it's not that old, probably more like OCaml 3.04 or so
<sanxiyn> Perhaps one on the web is an old version.
<Yoric[DT]> petchema: no, it's 2.99 :)
<Yoric[DT]> iirc
<sanxiyn> Would anyone here recommend reading F# books?
<zarul> any good new documents?
<sanxiyn> Yoric[DT]: By the way, F# seems to have implemented yield, mainly to be compatible with C#'s idea of iterators.
<Yoric[DT]> interesting
<zarul> how much is F# related to ocaml?
<sanxiyn> zarul: It is basically a superset.
<Yoric[DT]> zarul: same core, different just about everything else :)
<petchema> Yoric[DT]: maybe 2.99, yes... At least most 3.x features are mentionned (probably not polymorphic variants)
<Yoric[DT]> iirc, they mention somewhere that it's 2.99
<sanxiyn> Yoric[DT]: In my experience most OCaml code I would write worked same on F#.
<Yoric[DT]> I must admit I never managed to actually toy with F#.
<Yoric[DT]> Some time ago, I tried to get it to run under Linux and failed.
<Yoric[DT]> Since I don't have Windows, that was the end of it.
<sanxiyn> Yoric[DT]: I am playing with F# on Linux now :)
<Yoric[DT]> :)
<Yoric[DT]> I might try again soon, then.
<zarul> so, is F# is a good choice for writing compiler too?
<sanxiyn> zarul: I think so. F# compiler is written in F#, at least.
<sanxiyn> But then, writing compiler in C is not too painful IMO.
<sanxiyn> If the objective is to learn how to write a compiler...
<Yoric[DT]> zarul: I'm pretty sure F# and OCaml are similar enough that writing a compiler in either would be essentially indistinguishable.
<zarul> which mean that it's easier to port F# code to Ocaml later if I decided to do so?
<sanxiyn> zarul: Yes, if you don't use .NET libraries.
<zarul> cool
<sanxiyn> (And if you don't use F#'s "light" syntax. It's only superfically different, but it does automatically insert "in" and other stuffs which will be very annoying if you later want to port to OCaml.)
<zarul> will get the book in 2 hours time
<zarul> :)
prince has joined #ocaml
<zarul> any good?
<sanxiyn> I don't know. That's why I was asking.
<zarul> ermm..
<mfp> isn't F# quite different from OCaml once you go beyond HOFs for generic programming and modularization?
<zarul> I think I will just print out some ocaml documents
<mfp> i.e., the two mechanisms you can use for structural typing (functors, objects) differ
<zarul> any suggestion which one is good to start with?
<petchema> afaik, F# doesn't support functors
<mfp> (IIRC F# has got no functors, and the object system is essentially C#'s)
<mfp> right
<Yoric[DT]> mfp: yeah, but for writing an interpreter/compiler, you probably won't need any of this.
<zarul> Yoric[DT], so you teach subject on compiler/interpreter?
<Yoric[DT]> Among other things, yeah.
<zarul> cool
<sanxiyn> zarul: I started with OCaml user manual, but it's not really beginner-friendly in my experience.
<Yoric[DT]> Unfortunately, it's only a crash course.
<zarul> ah..
<zarul> It will be good if there is a any document that use ocaml as the language
<Yoric[DT]> (i.e. 3h on semantics, 3h on lexer/parser/ast, 3h on static analysis and 3h on code generation)
<zarul> I can find some in C and Java
<Yoric[DT]> What do you mean ?
<sanxiyn> zarul: Are you looking for compiler textbook which uses ML?
<sanxiyn> I believe there are many.
<zarul> sanxiyn, I only found the one by Appel
<jlouis> zarul, it will teach you the basics, but I don't think it is a very good book
<sanxiyn> zarul: Tiger one, yes.
* Yoric[DT] intends to write a short one whenever he finds time.
<Yoric[DT]> (only on basics)
<zarul> yeah the Modern Compiler Implementation in ML
<zarul>
<zarul> Modern Compiler Implementation in ML
<sanxiyn> Yoric[DT]: Compiler is a huge topic, so I guess courses are necessarily crash.
<mfp> Yoric[DT]: take ocamlopt for instance, it uses objects for code generation; what should one use instead for OCaml/F# compatibility, selective compilation?
<jlouis> sanxiyn, nope :)
<mfp> that is, defunctorizing manually and using a preprocessor/(o)make magic
<sanxiyn> mfp: F# does understand (*IF-FSHARP ... ENDIF-FSHARP*) and (*IF-OCAML*) ... (*ENDIF-OCAML), but yes, it sucks.
<mfp> does it also have something like -pp?
<sanxiyn> mfp: I don't think so. It has limited expression quoting IIRC.
<sanxiyn> <@ 1 + 1 @>
<sanxiyn> val - : Expr<int>
<sanxiyn> etc.
<mfp> :-| OCaml doesn't know about (*IF-OCAML*), so being able to do ocamlopt -pp "cpp -DOCAML" and fsc -whatever -DFSHARP would help
<mfp> was that taken from MetaOCaml?
<sanxiyn> mfp: Ah, (*IF-OCAML*) ... (*ENDIF-OCAML) is ignored by F#. OCaml, of course, just compiles not-commented codes.
<sanxiyn> mfp: So there's no problem.
<mfp> ah, it's not (*IF-FSHARP*)...(*ENDIF-FSHARP*), I misread
<sanxiyn> F# license sucks a bit. It's almost open, except that it forbids commercial use. You can distribute, modify, and distribute modifications, but only non-commercially.
<sanxiyn> Otherwise, I guess someone could integrate camlp4 to F#.
<mfp> no limitations on its output, I hope?
<sanxiyn> Yes, none. (Also you can redistribute runtime.)
<sanxiyn> I mean, if you *only* redistribute runtime, commercial purpose is ok, etc.
<Yoric[DT]> mfp: I must admit I haven't thought about that.
sporkmonger has joined #ocaml
ygr has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
z[x] has quit [Remote closed the connection]
sanxiyn has quit ["전 이만 갑니다."]
Linktim has quit [Remote closed the connection]
Linktim has joined #ocaml
RobertFischer has joined #ocaml
Linktim_ has joined #ocaml
jlouis has quit [Read error: 104 (Connection reset by peer)]
schme has joined #ocaml
Linktim_ has quit [Remote closed the connection]
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
jlouis has joined #ocaml
travisbemann has quit ["leaving"]
r0bby has quit [Client Quit]
r0bby has joined #ocaml
zarul has quit [Connection timed out]
netx has joined #ocaml
Linktim_ has joined #ocaml
Linktim- has joined #ocaml
jlouis has quit [Remote closed the connection]
RobertFischer has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
bebui_ has joined #ocaml
linktim` has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim_ has joined #ocaml
pango_ has quit [Remote closed the connection]
bebui has quit [Read error: 110 (Connection timed out)]
Linktim- has quit [Read error: 110 (Connection timed out)]
pango_ has joined #ocaml
linktim` has quit [Read error: 110 (Connection timed out)]
schme has quit [Remote closed the connection]
schme has joined #ocaml
schme has quit [Remote closed the connection]
schme has joined #ocaml
RobertFischer has joined #ocaml
RobertFischer has left #ocaml []
RobertFischer has joined #ocaml
ygr has quit [Remote closed the connection]
Amorphous has joined #ocaml
Linktim- has joined #ocaml
RobertFischer_ has joined #ocaml
Morphous has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Demitar has joined #ocaml
<jonafan> i have finally looked into the object oriented bits of ocaml
postalchris has joined #ocaml
<orbitz> wha tdo you think of htem?
<jonafan> i have concluded that even though i think object oriented is overrated and ocaml prefers functional solutions, ocaml does objects better than most other languages
<jonafan> you can pretend you're in some dynamically typed language and skip all the interface business, but ocaml will go ahead and statically check everything for you as if you had
<jonafan> as if you had done all your interfaces with perfect granularity
RobertFischer has quit [Read error: 110 (Connection timed out)]
<hcarty> Yes, being able to write a function that takes any_class with #foo_method and have it type checked for you is quite nice
<orbitz> i haven't done much with classes in ocaml yet
<jonafan> i kind of wonder why people don't use this language for... everything
<orbitz> hah
<orbitz> Ocaml and Erlang are probably my top 2 langauges right now, i just don't get to use them in the real world:(
<jonafan> i basically only use ocaml as an awesome scripting language
<orbitz> yeah it rocks like that
<Smerdyakov> Use Coq and you'll have trouble going back to OCaml. ;)
<orbitz> but if it becomes my faovrite language i won't be able to stop giggling
<jonafan> haha
<jonafan> Smerdyakov likes coq
<hcarty> Smerdyakov: Do you think Coq will develop enough real-world support to become a reasonable language to develop general purpose programs in?
<Smerdyakov> hcarty, it already is a reasonable language to develop general purpose programs in.
<hcarty> It is written in OCaml, so perhaps OCaml libraries could be used with some effort
<Smerdyakov> Yes, OCaml libraries are easy to use.
<Smerdyakov> So are Haskell libraries.
<hcarty> As you mentioned, there is little to no documentation for general purpose programming. Do you think that will change?
RobertFischer_ has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
RobertFischer has joined #ocaml
* RobertFischer shakes off his stupid _.
<Smerdyakov> hcarty, yes. I plan to write a textbook on implementing certified compilers with Coq, at least.
<RobertFischer> Smerdyakov: Does everyone over at Jane St have their own language? I know Brian is cranking away on one in his free time, too.
<Smerdyakov> Coq isn't my own language, though I do have my own languages. :)
<Smerdyakov> An additional factoid is that I decided to leave Jane Street and do various PL researchy things again, so you might not want to include me in your data.
<orbitz> i do too
<orbitz> people confuse it with types though
LordMetroid has joined #ocaml
<RobertFischer> Smerdyakov: WTF? You're leaving Jane St?
<Smerdyakov> RobertFischer, already left.
<Smerdyakov> RobertFischer, that's why I'm on IRC at 12:42 PM on a Tuesday. :)
<orbitz> ah you worked at Jane st?
<orbitz> how was it
<RobertFischer> Heh.
<RobertFischer> I was wondering about that.
<RobertFischer> Are you at grad school, or just doing your own thing, or what?
<Smerdyakov> orbitz, awesome place to do traditional software development taken as far as you can go without writing your own languages.... but I like writing my own languages. :)
<Smerdyakov> RobertFischer, I finished my PhD before I went to Jane Street, so it wouldn't make much sense to be "at grad school."
<orbitz> so a sweet place for someone who likes to think but perhaps not interested in doing research?
<Smerdyakov> orbitz, a sweet place for most FP fans, I imagine.
<orbitz> cool
<RobertFischer> Smerdyakov: Just because you have one PhD doesn't mean you can't have more. And you could always be faculty/research staff/whatever. :)
<orbitz> i worked at a wall st firm who was the exact opposite and longely looked at jane st adverts
<Smerdyakov> RobertFischer, the second case wouldn't be "at grad school."
<Smerdyakov> RobertFischer, I'm maneuvering towards doing the second case part-time, while working on founding a language-oriented start-up.
<RobertFischer> orbitz: I hung out with the Jane St. people once upon a time. +1 from here, as long as you're into high-level math, PL theory, and New York City.
Yoric[DT] has joined #ocaml
<orbitz> i don't think i have what it atkes to make it to jane st, i recently left NYC to go back to grad school
<orbitz> i worked in a horrible java shop trying to fix horrible programmers errors
<RobertFischer> Smerdyakov: Keep me informed as to that start-up. Always curious.
<RobertFischer> orbitz: Story of my life.
<orbitz> which is probably why the company i worked for sold at such a discount to JPM:)
<Yoric[DT]> hi again
<Smerdyakov> orbitz, where are you at grad school? You seem to be making fewer typos now, so maybe they're teaching you something. ;)
<orbitz> hah i haven't started yet!
<orbitz> I'm going to Johns Hopkins for a masters in bioinformatics
<Smerdyakov> How trendy. ;P
<orbitz> heh
<orbitz> because it rocks :)
<Smerdyakov> I don't know, these biological systems, they aren't as purdy as programming languages designed right.
Linktim- has quit [Read error: 104 (Connection reset by peer)]
|Catch22| has joined #ocaml
<orbitz> Smerdyakov: how short sighted, considering we can create chromosomes from scratch in a lab now, we'll need genetic programming langauges and DNA compilers
<orbitz> :)
<orbitz> my version of gcc makes a bacteria! (or will!)
<Yoric[DT]> Gnu Chromosome Compiler ?
<orbitz> hehe
<orbitz> gdna
Linktim has joined #ocaml
<Smerdyakov> That's fine, but we still don't know yet how to do traditional computing right, and I'll stick around there until we do.
<RobertFischer> If I could debug my hypothetical children, I may consider actually making them. :)
* RobertFischer digging on this idea of gcc'ing up children.
<Yoric[DT]> Well, are you willing to spend 21+ years debugging your children ?
<RobertFischer> I don't know: the fun part is pulling them together in the first place.
seafood_ has joined #ocaml
<RobertFischer> And I tend to be bad with debugging environmental problems, which I think there'd probably be a lot of.
<Yoric[DT]> Well, if they're purely functional you can just #trace them.
<Yoric[DT]> Of course, children tend to have side-effects.
<RobertFischer> Yeah. And I thought undefined behavior in Ruby was scary.
<orbitz> i did use Ocaml for my personnal projects when i worekd on wall st thouhg, which was cool
* RobertFischer thanks orbitz for pulling us back on topic.
<RobertFischer> Anyone know what linux package "dc" is in?
<orbitz> i think it's like bc
<orbitz> Dc is a reverse-polish desk calculator which supports unlimited preci-
<orbitz> sion arithmetic.
<orbitz> i had a series of ocaml tools that i would use to extract data out of Azul system dumps i was taking
<orbitz> it was super easy and quick
seafood_ has quit []
<Yoric[DT]> RobertFischer: for me, it's in a package called "dc" (Ubuntu).
<orbitz> RobertFischer: sorry
<orbitz> i can't read
<RobertFischer> Yoric[DT]: WTF? It told me it wasn't there when I tried that before.
<RobertFischer> Thanks. My computer is out to get me.
<Yoric[DT]> You're welcome.
ikaros has quit [Read error: 110 (Connection timed out)]
Linktim_ has joined #ocaml
rwmjones_ is now known as rwmjones
Linktim has quit [Read error: 110 (Connection timed out)]
<rwmjones> what should my lexer return to indicate end of file?
<rwmjones> I'm raising End_of_file
<rwmjones> but that escapes from the parser & causes the program to exit ...
<Yoric[DT]> Usually, I define a special token EOF.
<rwmjones> and match on that in the parser? or not?
<Yoric[DT]> Yes.
<mfp> yay type-safe marshalling on top of Marshal http://pastebin.be/10522
<Yoric[DT]> cool :)
<mfp> only probabilistically, though
RobertFischer_ has joined #ocaml
<mfp> at least 50% collision chance if you declare 54500 different types, since I use a 31 bit type id
<mfp> and assuming my hash function : ctyp -> int is not stupid
RobertFischer has quit [Read error: 110 (Connection timed out)]
evn has quit [Read error: 110 (Connection timed out)]
RobertFischer_ has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
RobertFischer has joined #ocaml
ikaros_ has joined #ocaml
thelema has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
schme has quit [Remote closed the connection]
schme has joined #ocaml
bla has quit [Read error: 110 (Connection timed out)]
Linktim_ has joined #ocaml
kotarak has joined #ocaml
OChameau has quit ["Leaving"]
schme has quit [Remote closed the connection]
ikaros has joined #ocaml
schme has joined #ocaml
bla has joined #ocaml
ikaros_ has quit [Read error: 110 (Connection timed out)]
<flx> has someone implemented dimensional types for ocaml?
<flx> like val multiply : 'a -> 'a -> 'a^2 :)
<flx> but with the trick Vesa Karvonen used for type-level adding
<Yoric[DT]> How would you define 'a^2 ?
* RobertFischer didn't get his OSP proposal accepted. :(
<hcarty> Wow, those look like some ambitious projects this year
<orbitz> are there any plan sot give ocaml generators? that' dbe nice
<RobertFischer> Yeah. Given the calibre of the projects this year, it's not a surprise.
<orbitz> or iterator or somethign
<RobertFischer> The multicore runtime would be sweet -- it'd resurrect adlib.
<hcarty> Hopefully most of them will work out well and be maintained. Most of the projects from last year seem to have been unmaintained since the OSP ended.
<RobertFischer> Yeah, which sucks.
<RobertFischer> I would have liked to see more out of the Erlang message passing project -- some middle ground between JoCaml and Ocaml would be nice.
<hcarty> coThreads and ocamlp3l both seem promising. Sadly, the process/parallel ocamlp3l runtime has not worked in my limited testing.
<hcarty> And they both seem like they are unmaintained
<RobertFischer> The trick is just getting past "promising".
ofaurax has joined #ocaml
schme has quit [Remote closed the connection]
vfdfdfvd has joined #ocaml
Snark_ has quit ["Ex-Chat"]
kAworu has joined #ocaml
<kAworu> hi
<orbitz> hi
<kAworu> i have a problem with the graphics module of ocaml. i hope someone caan help :)
<kAworu> The external function `caml_gr_moveto' is not available
<kAworu> here is the code http://rafb.net/p/YFokay26.html
thelema has joined #ocaml
evn has joined #ocaml
<RobertFischer> I'm not sure, but I think the old Postgres driver is out of date with libpq, and Ocaml DBI is out of date with the new Postgres driver.
<RobertFischer> I'm trying to install all three of them from scratch and I'm getting compile errors.
<RobertFischer> > ocamlc -g -I /usr/local/godi/lib/ocaml/pkg-lib/pcre -I /usr/local/godi/lib/oc
<RobertFischer> aml/pkg-lib/postgresql -c dbi_postgresql.ml
<RobertFischer> > File "dbi_postgresql.ml", line 142, characters 23-38:
<RobertFischer> > Unbound value Pg.escape_bytea
<RobertFischer> > make: *** [dbi_postgresql.cmo] Error 2
<RobertFischer> > *** Error code 2
<hcarty> kAworu: It sounds like you are not linking in graphics.cm(x)a
<flx> I suppose other encodings could be possible
* Yoric[DT] takes a look.
* Yoric[DT] will take a look tomorrow.
* Yoric[DT] is too tired for now.
<RobertFischer> Although I'm seeing "escape_bytea" as a method as a subset of connection. Not finding it connected to anything named "Pg....
* RobertFischer is getting really tired of compile errors.
postalchris has quit [Success]
rwmjones_ has joined #ocaml
jlouis has joined #ocaml
<kAworu> hcarty> thx. could you give me the ocamlc option that i need i read the man ocamlc but didn't found it.
Smerdy has joined #ocaml
znutar has quit [brown.freenode.net irc.freenode.net]
TaXules has quit [brown.freenode.net irc.freenode.net]
orbitz has quit [brown.freenode.net irc.freenode.net]
ikatz has quit [brown.freenode.net irc.freenode.net]
neale has quit [brown.freenode.net irc.freenode.net]
Smerdyakov has quit [brown.freenode.net irc.freenode.net]
pattern has quit [brown.freenode.net irc.freenode.net]
orbitz has joined #ocaml
znutar has joined #ocaml
TaXules has joined #ocaml
Smerdy is now known as Smerdyakov
<flx> yoric[dt], now that I think of it, wouldn't simply val mul : ('a, 'b) t -> ('a, 'b) t -> ('a, 'b * 'b) t work.. it would make m^2*m and m*m^2 incompatible, though.
<flx> so the real trick would be making somehow those types compatible
pattern has joined #ocaml
postalchris has joined #ocaml
<hcarty> kAworu: ocamlc graphics.cma foo.ml
<kAworu> hcarty> yup i just found it in the ocaml-doc thanks .)
sporkmonger has quit []
ofaurax has quit ["Leaving"]
Linktim_ has quit [Remote closed the connection]
ygrek has joined #ocaml
bluestorm has joined #ocaml
<orbitz> does extlib come with ocaml?
<bluestorm> no it doesn't
palomer has joined #ocaml
<orbitz> does it add much in teh way of string functions?
<bluestorm> you have to install it yourself, eg. with godi, and then you'll be able to use it (with ocamlfind it's easy to use)
<palomer> I remember reading somewhere that it's possible to update a single row of a record
<orbitz> like trimming, joining, etc?
<palomer> how do you do this?
<bluestorm> palomer: { foo with field = new_value }
<orbitz> or make it mutable
<orbitz> if you really wan tot 'update'
<palomer> and {foo with somefild = foo.somefield @ [1]} has the expected semantics?
<bluestorm> palomer: yes
<palomer> cool!
<bluestorm> but list @ [1] is _ugly_
<bluestorm> you should not add something at the end of a list
<bluestorm> you're very likely to do something wrong there
LordMetroid has quit ["Leaving"]
<palomer> err, that was just an example
<palomer> (I'm not actually doing it)
<palomer> is it possible to update many fields?
<orbitz> sure
<orbitz> put a ; between them
<palomer> cool!
<pango_> 'updating' is not very accurate in this context, however
<palomer> what verb should I use?
<orbitz> you reallyg et a new record with this
<orbitz> an update would rquire making a meber o fit mutable and using -> to set it
<palomer> yeah
<orbitz> what does ocaml call its version of 'keyword parameters'?
<orbitz> labels?
RobertFischer has left #ocaml []
<orbitz> i need a better chair
<palomer> is it possible to call an inherited method from the overriding method?
<bluestorm> yeah, super#yourmethod
<bluestorm> provided you've done "inherit motherclass as super"
<orbitz> what about in multiple inheritence
<bluestorm> inerhit motherclass1 as mc1 inherit motherclass2 as mc2
<bluestorm> mc1#foo, mc2#bar
<orbitz> heh, ocamls object system seems so traight forward and sensicle
<palomer> yeah, I really dig it
smimou has quit ["bli"]
love-pingoo has quit ["Connection reset by pear"]
smimou has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
smimou has quit [Client Quit]
smimou has joined #ocaml
ofaurax has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
kotarak has quit ["Xaide, leka nosht."]
<orbitz> is not being able to have records be considered diferent types but have the same attribute names considered a problem that needs fixing?
rwmjones_ has quit ["Closed connection"]
ikaros has quit ["segfault"]
<palomer> yes! I successfully defined the head function in my programming language
<palomer> success!
olleolleolle has joined #ocaml
vfdfdfvd has quit [Remote closed the connection]
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
ofaurax has quit ["Leaving"]
ikatz has joined #ocaml
olleolleolle has left #ocaml []
ygrek has quit [Remote closed the connection]
RobertFischer has joined #ocaml
RobertFischer has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
RobertFischer has joined #ocaml
hkBst has quit ["Konversation terminated!"]
RobertFischer has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
RobertFischer has joined #ocaml
<orbitz> has anyone fied ocaml-mode for emacs so it can handle multi line comments
<jlouis> tuareg mode?
<jlouis> is there any other mode?
RobertFischer has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
dlomsak has joined #ocaml
yangsx has joined #ocaml