gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
emmanuelux has joined #ocaml
brendan has left #ocaml []
kolera has quit [Ping timeout: 265 seconds]
kolera has joined #ocaml
fasta has quit [Read error: Connection reset by peer]
fasta has joined #ocaml
oriba_ has quit [Quit: oriba_]
vazakl has joined #ocaml
cdidd has quit [Remote host closed the connection]
jaxtr has quit [Ping timeout: 256 seconds]
<taruti> How does one parse network protocols that contain e.g. 32/64 bit ints in a good way? (as ocaml ints are 31-63 bits)
<thelema_> Bitstring is good.
<thelema_> if you need a 32-bit int, you can use Int32, or similarly with Int64
<taruti> ah ok, and those are just boxed int64:s?
tmaedaZ has quit [Ping timeout: 240 seconds]
tmaedaZ has joined #ocaml
<alex-hu> /wii The_third_man
kaka222 has joined #ocaml
<kaka222> hi guys. i am learning OCaml, and have a question with this simple code: http://pastebin.com/YuLHneJG
<_habnabit> okay
<kaka222> in this function, it seems to try to match something with some code (0, 1, 2, ..)
<kaka222> but what does that match?
<kaka222> usually, i think they use "match ...", but this doesnt have any, so i am confused
<_habnabit> 'function' is the same as 'fun x -> match x with'
<kaka222> _habnabit, it seems so, but what is "x" in this case?
<kaka222> the input param of the function?
<_habnabit> that's what 'fun x ->' means, yes
<_habnabit> it's a unary function
<kaka222> _habnabit, hmm i am still confused, as sometime this eaddr16 is called with 1 param, but sometimes, it is called with 2 params
<kaka222> like this:
<kaka222> let (base, na) = eaddr16 rm, na
<kaka222> with 1 param, it is understandable, but with 2 params like above, how can i interpret the code??
<_habnabit> no, that's nonsense that's equivalent to `let base = eaddr 16`
<_habnabit> er
<_habnabit> `let base = eaddr16 rm`
<kaka222> _habnabit, so ignore "na" in this case?
<_habnabit> two parameters would be `eaddr16 rm na`
<_habnabit> commas don't delimit parameters
<kaka222> oops, i see
<_habnabit> that's building a tuple. it's equivalent to `(eaddr16 rm, na)`
<_habnabit> but, since the tuple is then immediately unpacked, it's the same as `let base = eaddr16 rm and na = na`
<kaka222> _habnabit, obviously :-)
<_habnabit> the `na = na` part is why I said it's nonsense
<kaka222> thanks a lot, i have another question. in this code:
<kaka222> Arg.String(fun e->addinput(`Binrange(!f, !s, toint64 e)))]),
<kaka222> what is that `Binrange ?
<_habnabit> it's a polymorphic variant
alxbl has quit [Changing host]
alxbl has joined #ocaml
<kaka222> i suppose ` is for something like "polimorphic", but usually i only see a single char after `, but not `Binrange like in this case
<kaka222> so more than 1 char is ok for polymorphic?
emmanuelux has quit [Remote host closed the connection]
kolera has quit [Quit: Leaving]
digcon9_ has joined #ocaml
digcon9_ has quit [Read error: Connection reset by peer]
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
Fnar has quit [Quit: Client exiting]
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
andreypopp has joined #ocaml
manu3000 has quit [Quit: manu3000]
Kakadu has joined #ocaml
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
ulfdoz has joined #ocaml
ulfdoz has quit [Ping timeout: 240 seconds]
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
<Drakken> kaka222 yes, any capitalized identifier can represent a polymorphic variant (with the backquote)
pango is now known as pangoafk
<kaka222> Drakken, thanks!
digcon9 has joined #ocaml
digcon9 has quit [Ping timeout: 240 seconds]
<kaka222> i am reading some code, and they have something like "Some" in a lot of places. is "Some" a standard keyword in Ocaml? since i cannot seem to find the definition of this "Some" anywhere
<Kakadu> type 'a option = Some of 'a | None
<Kakadu> it is built-in
<kaka222> Kakadu, how to use this "Some"? i cannot find any documentation about it
<Kakadu> kaka222: Read about algebraic datatypes
digcon9 has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
ftrvxmtrx has quit [Quit: Leaving]
<kaka222> Kakadu, thanks
digcon9 has joined #ocaml
ggherdov has quit [Quit: bye folks]
djcoin has joined #ocaml
<kaka222> so "function" is to match the input param with pattern. but if the procedure is called with more than 1 param, what happens?
<kaka222> like in this code:
<kaka222> let rec f t s r = function
<kaka222> | [] -> (t, s, List.rev r)
<kaka222> | p::ps -> f t s (p::r) ps
<kaka222> i dont understand what is matched to the pattern in this case
<kaka222> as f is defined with 3 params
<kaka222> any idea?
<Kakadu> kaka222: fun x y z = function ..... is an equevalent for fun x y z smth = match smth with ...
<Kakadu> function matches last argument
<kaka222> oh i see!
<djcoin> Yeah function take an implicit last argument
<djcoin> I have a syntax question - and I guess it is related to GADT - the use of this construct: " type a, b. a -> b " for example
andreypopp has quit [Quit: Quit]
<djcoin> Never seen the use of the dot "." before
<kaka222> Kakadu, do you have any idea why the above recursive function is called with 1 more param? p::ps -> f t s (p::r) ps
<kaka222> while let rec f t s r = ... means this recursive function has only 3 params?
Sablier has joined #ocaml
cago has joined #ocaml
<djcoin> kaka222: your f function as 4 params
mika1 has joined #ocaml
<djcoin> the use of the "function" keyword in the body of the function means your function take one extra implicit args
<kaka222> djcoin, let rec f t s r = function ....
<kaka222> so f takes only 3 params, no?
<djcoin> your "f" is take 4 params
<kaka222> djcoin, can you pls explain? i suppose that when the function is defined, it must list all params there ....
<djcoin> your "f" function take 4 params. As Kakadu says it's a shortcut of f t s r last_implicit_arg = match last_implicit_arg with
<kaka222> oops!
<djcoin> Did you get it ?
<kaka222> ocaml sounds like a terrible language :-(
<djcoin> Otherwise check the doc, I guess I could not be more clear
<djcoin> Well It's a bit weird shortcut yep
<kaka222> never see why they design language with all these stupid implicit :-(
<djcoin> Don't be sad kaka222 it happens :)
<Kakadu> kaka222: I don't understand. OCaml is beautiful
<kaka222> djcoin, not sad, but crazy
<kaka222> Kakadu, well, this is up to the taste, but i still think Python is much more beautiful
<kaka222> no offense, just my personal taste
<djcoin> Im a Python coder (and javascript too) - Python used to have no AST - this is way more ugly
<Kakadu> kaka222: When I read Ocaml tutorial I've promised don't write Java programs which doesn't fit a one screen
<djcoin> Currying is trivial in OCaml and painful in python too
<djcoin> etc.
<djcoin> May anyone enlight me on the " type a, b. a -> b " construct ?
testcocoon has quit [Quit: Coyote finally caught me]
<Kakadu> djcoin: to avoid monomorphism, AFAIR
<djcoin> I mean the "type a, b." part with the dot
<djcoin> (note: i'm far from being an ocaml expert)
<Kakadu> djcoin: oops
<Kakadu> it was mmisunderstanding
ftrvxmtrx has joined #ocaml
digcon9 has quit [Read error: Connection reset by peer]
digcon9 has joined #ocaml
<kaka222> a question: what does Some(v) returns?
<kaka222> i suppose it returns v if v !=None, and None if v==None?
<kaka222> is that correct?
digcon9 has quit [Read error: Connection reset by peer]
<Kakadu> what?
<adrien> "Some v" returns "Some v"
<Kakadu> Some is not a function, it is constructor
<kaka222> Kakadu, i have a line of code like this:
<kaka222> let asm = try Some(ToStr.to_string pref op) with Failure _ -> None
<kaka222> why they put "Some" there?
<Kakadu> val asm : string option
<Kakadu> with part returns None : 'a option
<Kakadu> hence try part should return 'a option
<Kakadu> but we want to return a string
<Kakadu> that's why we return Some "string" : string option
testcocoon has joined #ocaml
<Kakadu> kaka222: both parts should return the same type
<kaka222> Kakadu, by "val asm: string option", they means asm can be a string, or None. is that correct?
<Ptival> kaka222: the try part and the with part should have the same type, here said type being "string option"
digcon9 has joined #ocaml
<Ptival> a string option can be either the None constructor, or the Some constructor with a string parameter
<Kakadu> kaka222: they means that asm can be Some of string or None. It analogue of Java's null
<Kakadu> but a type-safe analogue :D
<Ptival> kaka222: it's not "asm can be a string or None", because a string and None don't have the same type
<kaka222> thank guys. it is getting clearer for me now
<Ptival> it's rather Some(a_string) or None, that both have the same type: string option
<Kakadu> btw, Does anybody knows how to get twits with #ocaml tag using RSS?
<Ptival> a bit verbose with the RTs though :\
<Kakadu> Ptival: very-very verbose :)
<alex-hu> mcstar, It turns out that haskell implementation of the same thing looks much more scrutable, if I want to achieve the same effectiveness. :-\
<Ptival> Kakadu: let me try some magic :)
ocp has joined #ocaml
digcon9 has quit [Ping timeout: 252 seconds]
<Ptival> that's #ocaml - RT
ocp has left #ocaml []
<Kakadu> Ptival: seriously better
<Ptival> you can fiddle with the request at the end of the URL :)
<Ptival> actually, you can drop both %22, no need for them
digcon9 has joined #ocaml
thomasga has joined #ocaml
<Ptival> (that's the same contents as the previous one)
<Ptival> Kakadu: you still have the chinese and russian messages, so you can "minus" some of their frequent characters if you want to filter that out
digcon9 has quit [Read error: Connection reset by peer]
<Kakadu> Ptival: Russian is not a problem)
<Ptival> now if you want to filter out French, that will be more complicated :)
<Ptival> actually that might be japanese
<Ptival> I'm missing symbols in my RSS reader font :(
<mrvn> Ptival: you can filter the `´vo on top of letters.
silver has joined #ocaml
<Ptival> sure
cyphase has quit [Ping timeout: 260 seconds]
Submarine has quit [Remote host closed the connection]
kaka222 has quit [Quit: Ex-Chat]
cyphase has joined #ocaml
kaka222 has joined #ocaml
<kaka222> i read some code, and they have some operator like "+*"
eikke has joined #ocaml
<kaka222> what is +* ?
<Kakadu> kaka222: I think it is defined somewhere above
<rixed> kaka222: Probably something they defined themself somewhere
<kaka222> like they define their new operator, as in C++?
<rixed> kaka222: Yes. Look for a "let ( +* ) = ..." somewhere.
<Kakadu> kaka222: let (+*) x y = x+x*y for example
<kaka222> thank guys!
<Ptival> actually, I think in C++ you can only overload a few set of operators
<Ptival> s/few/small/
fpz has quit [Read error: Connection reset by peer]
fpz has joined #ocaml
kaka222 has quit [Quit: Ex-Chat]
<mcstar> i think you can overload all of them, the problem is, you cant create new ones by putting them together
<Kakadu> http://paste.in.ua/4297/raw/ what option should I add to fix compilation?
<mrvn> Kakadu: ,unix
<mrvn> which would be a bug in cores META file
<mcstar> how come there are a lot of standard library implementations for ocaml? this comes as a surprise to me, i thought languages usually have 1 std lib
<Kakadu> mcstar: stdlib is a very small
<mrvn> Because the stdlib is verry small in ocaml so people started to write bigger ones.
<mrvn> mcstar: Use batteries, which brings most of the "std"libs together into a consistent project.
<mcstar> how about the jane street one?
<mcstar> i'd guess thats of the best quality?
silver has quit [Ping timeout: 246 seconds]
<Kakadu> mrvn: Your advice doesn't help
<Kakadu> mcstar: camlunity doesn't like JS core. I don;t know why
<Kakadu> mrvn: the same error.
<Kakadu> mrvn: maybe I should add some .a files manually?
<mrvn> Kakadu: unix,core? the order matters probably.
<mrvn> Kakadu: otherwiese I don't know. The missing functions look like unix.
<Kakadu> mrvn: order doesn't matter
<taruti> How do I fix eliomc complaining about not finding Eliom_sessions (installed with godi)?
<Kakadu> taruti: maybe is better to ask in #ocsigen
<Kakadu> taruti: maybe is better to ask in both channels...
<mcstar> Kakadu: core_unix?
<Kakadu> mcstar: don't think so. there is only core_unix.mli
<mcstar> so, is it advised to go with this Batteries, instead of the shipped std lib?
<Kakadu> mcstar: or Core
<mcstar> what you are trying to get to work?
<Kakadu> mcstar: I'm fixing compilation after new releae core
<Kakadu> release*
<Kakadu> mcstar: see lenk above
<Kakadu> link*
<mcstar> your paste? yes im looking at it
Yoric has joined #ocaml
silver has joined #ocaml
<Kakadu> man recommends to link with -lrt
<Kakadu> but with -ccopt -lrt I have the same error... TT
kaka222 has joined #ocaml
<kaka222> i am wondering what tool do you use to browse Ocaml code?
<kaka222> for C, i usually use Vim + Ctags/Cscope
<kaka222> which tool is available for Ocaml?
<mrvn> vim
<mrvn> 8-P
* mrvn uses emacs + tuareg
<kaka222> sorry but i prefer something with Vim
<rixed> kaka222: vim + grep most of the time. :-( But there's also the excelent ocaml-annot (look for it @ github) which allow to display any type from vim
<kaka222> Vim has some shortcuts, so i can jump to the definition of a particular function, then comeback
<mcstar> mrvn: i installed typerex, though a better toplevel would be nice
<mrvn> mcstar: I usualy only use the toplevel with cut&paste from emacs.
<kaka222> rixed, yes, i am using grep now, but that is a very bad solution
<mcstar> yeah that works
<mrvn> otherwise just compile
<mcstar> mrvn: supposedly typerex supports some kind of autocompletion, i haventset it up yet
<kaka222> rixed, ocaml-annot is not what i am looking for
<kaka222> if you use cscope before, you know what i mean
<kaka222> or sourcenav
Hussaind has joined #ocaml
Hussaind has left #ocaml []
Snark has joined #ocaml
vazakl has quit [Ping timeout: 256 seconds]
Hussaind has joined #ocaml
Hussaind has left #ocaml []
jaxtr has joined #ocaml
eikke has quit [Remote host closed the connection]
kaka222 has quit [Quit: Ex-Chat]
Fnar has joined #ocaml
Fnar has quit [Changing host]
Fnar has joined #ocaml
Yoric has quit [Ping timeout: 264 seconds]
Reventlovv has joined #ocaml
<Reventlovv> morning
<Reventlovv> I have a question concerning caml light (yes, it's outdated, it sucks… etc)
<Reventlovv> if I write, pop1 * pop2;; what will be the first pop executed ?
<Reventlovv> pop1 or pop2 ?
cdidd has joined #ocaml
<pippijn> why is it called pop?
<pippijn> I don't know the answer, but I'm curious why it's called pop
<pippijn> is it related to stack pop?
<taruti> Reventlovv: the answer may be "undefined"
<pippijn> what's * in caml light?
<Reventlovv> pippijn: any operator, in facts
<Reventlovv> pippijn: I'm trying to implement RPN
<pippijn> oh
<pippijn> in ocaml, it's undefined
_andre has joined #ocaml
<pippijn> in native code, it will be pop2 * pop1
<pippijn> Reventlovv: why caml light?
<Reventlovv> It's the virsion used in the french prepas
<Reventlovv> version*
<pippijn> ok
thomasga has quit [Quit: Leaving.]
Yoric has joined #ocaml
Reventlovv has quit [Quit: Page closed]
suze has quit [Quit: WeeChat 0.3.2]
BiDOrD has joined #ocaml
BiDOrD_ has quit [Ping timeout: 265 seconds]
NaCl is now known as SPanishInquisitr
SPanishInquisitr is now known as SpanishInquisitr
ski has quit [Ping timeout: 245 seconds]
ski has joined #ocaml
cago has quit [Quit: Leaving.]
gnuvince has quit [Read error: Operation timed out]
jamii has joined #ocaml
jamii has quit [Read error: Connection reset by peer]
cago has joined #ocaml
ocp has joined #ocaml
thomasga has joined #ocaml
mika1 has quit [Ping timeout: 252 seconds]
avsm has joined #ocaml
cago has quit [Quit: Leaving.]
emmanuelux has joined #ocaml
hto has quit [Read error: Connection reset by peer]
Kakadu has quit [Ping timeout: 244 seconds]
Kakadu has joined #ocaml
gnuvince has joined #ocaml
hto has joined #ocaml
Sablier has quit [Read error: Connection reset by peer]
dima_ has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
dima_ has quit [Quit: Leaving]
xaimus_ has quit [Ping timeout: 248 seconds]
Sablier has joined #ocaml
avsm has quit [Quit: Leaving.]
silver has quit [Remote host closed the connection]
<flux> hmm, batteries comes only with the Dllist implementation that requires me to handle 'empty' case separately?
<flux> if I want to have a queue that I can add/remove at both ends that is
<thelema_> flux: deque?
<flux> ah, thank you!
Yoric has quit [Ping timeout: 250 seconds]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
mcstar has quit [Quit: mcstar]
eni has joined #ocaml
eni has quit [Read error: Connection reset by peer]
ocp has quit [Ping timeout: 248 seconds]
dca has quit [Read error: Connection reset by peer]
dca has joined #ocaml
ftrvxmtrx has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.2]
<Kakadu> Have you ever tryed extract something from cmi files?
<Kakadu> tryed to extreact*
<adrien> extract what?
<Kakadu> adrien: module interface
err404 has joined #ocaml
ulfdoz has joined #ocaml
avsm has joined #ocaml
djcoin has joined #ocaml
osa1 has joined #ocaml
romildo has joined #ocaml
<adrien> Kakadu: cmigrep?
<Kakadu> adrien: Maybe. Now I'm investigating `ocamlc -where`/compiler-libs
SpanishInquisitr is now known as NaCl
Yoric has joined #ocaml
<Kynes`> /nick C5H8NNaO4
<adrien> Kakadu: view cmigrep.ml
<adrien> :P
pangoafk is now known as pango
<wmeyer``> hello
<adrien> morning
<adrien> (bye)
<wmeyer``> damn, good that I closed the window - my laptop would be soaking wet
<adrien> laptop condoms are great :P
<wmeyer``> adrien: morning
<wmeyer``> i don't need to protect myself from the laptop :P
err404 has quit [Remote host closed the connection]
<wmeyer``> Kakadu: http://search.ocaml.jp/
xaimus has joined #ocaml
<wmeyer``> if you are looking at compiler-libs then what you probably want is to look at the OCaml source code. All this stuff will be installed by default as part of upcoming release I believe. (so not as a part of the 3rd paty distro like Debian, odb or godi)
<Kakadu> wmeyer``: thanks for this link
<wmeyer``> no problem. It looks like this would be really useful if somebody put more stuff into the database
<flux> ah, the magic of self-explanatory types.. type 'a request = unit -> (t * (unit -> unit) * (('a -> unit) -> unit -> (receive_handler * receive_finish)))
<wmeyer``> and below there is a dating site advertisment at the moment, so all included ;-)
<wmeyer``> flux: oh gosh, this looks worse than the weather today here :(
<flux> "using types is like violence: if it doesn't solve your problem, you're not using enough of them"
<wmeyer``> function that returns function that returns function ... - it's a pure torture (but still don't see any recursion ;-)) - not mentioning that all this have side effects. I don't judge but in Python (no, not saying I am fan of python at all) at the same time you would never construct (even when it's useful) such signature
<wmeyer``> sorry it's the function that accepts function that returns tuple of functions
<wmeyer``> well, please ignore previous statemens as currying indeed is useful :)
<mrvn> flux: could be worse, could have not used any named types at all
pango has quit [Ping timeout: 260 seconds]
<flux> well, it couldn't, because one of the types is a recursive function, so I need a constructor somewhere..
<flux> type receive_handler = Cont of (string -> (receive_handler * receive_finish))
<flux> so at least it's not mutual recursino between two types.
<wmeyer``> gotcha ya, so I was right
<wmeyer``> well almost ...
<wmeyer``> that recursion is involved
<wmeyer``> is there any Obj.magic involved in the end, maybe it will break the chain of violence :-)
<flux> I'm trying to make type-safe program here :)
<mrvn> oh yeah, Obj.magic. That certainly always helps
pango has joined #ocaml
romildo has quit [Quit: Leaving]
<wmeyer``> got my coffee, so warming up too for today
dwmw2_gone has joined #ocaml
<dwmw2_gone> rwmjones?
<dwmw2_gone> where is this osx ppc64 back end of which you speak?
<wmeyer``> dwmw2_gone: some of the backend were removed on trunk, for sure alpha - no idea about ppc
<dwmw2_gone> and don't really understand why anyone would do a ppc64 back end that *doesn't* start with a copy of the ppc32 back end. Or why they'd rip the assembler-agnostic features out of emit.mlp if they did.
<avsm> dwmw2_gone: http://caml.inria.fr/cgi-bin/viewvc.cgi/ocaml/trunk/asmcomp/power/ has the 64-bit version too, iirc
<dwmw2_gone> ah, right
<avsm> yes, it does: let ppc64 = match Config.model with "ppc64" -> true | _ -> false
Snark has quit [Quit: Quitte]
<dwmw2_gone> so fixing that to work on linux/ppc64 seems like the best approach.
<wmeyer``> dwmw2_gone: sorry for the noise.
<dwmw2_gone> rather than using my old code from http://git.infradead.org/users/dwmw2/ocaml-ppc64.git/shortlog
<dwmw2_gone> oh, wait.
<dwmw2_gone> does darwin/ppc64 use a different ABI?
<dwmw2_gone> or, more to the point, the *same* ABI as ppc32 except 64-bit?
<dwmw2_gone> without the various changes that Linux/ppc64 has (function descriptors, etc.)
<dwmw2_gone> I think there was a *reason* I didn't try to do linux/ppc64 with conditional stuff in the existing power back end
<avsm> looks like it, but I havent ever used the ppc64 backend on darwin to even know if it works (there was only a small window on 10.5 when it was relevant, i think?)
* avsm needs to sort out a MIPS64 backend to ocamlopt sometime this summer
<wmeyer``> avsm: Out of curiosity, are you coming here: http://www.fpdays.net/fpdays2012/index.php
<avsm> wmeyer: maybe; i'm down to give a talk, but may still be on sabbatical in california then. sorting that out, then will know...
<avsm> wmeyer: but harrop is kicking off ML pub meets in camb every so often; the first one was fun!
<avsm> (if not announced widely, just on twitter i think)
<wmeyer``> avsm: Never seen harrop in CB really, i suppose it must be fun to attend the pitch. I might also give a talk there. Hope you will be there - at any rate enjoy your sabbatical if you won't be able to come
<wmeyer``> avsm: when is the pub meet happening - any link?
<avsm> wmeyer: none, but i'll forward the next one to you when it shows up...
<wmeyer``> avsm: Ok, thanks.
Sablier has quit [Read error: Connection reset by peer]
Sablier has joined #ocaml
smerz has joined #ocaml
gnuvince has quit [Ping timeout: 252 seconds]
thomasga has quit [Ping timeout: 250 seconds]
fschwidom has joined #ocaml
thomasga has joined #ocaml
wmeyer``` has joined #ocaml
wmeyer`` has quit [Ping timeout: 246 seconds]
eni has joined #ocaml
fschwidom has quit [Remote host closed the connection]
fraggle_ has quit [Remote host closed the connection]
wmeyer``` has quit [Ping timeout: 245 seconds]
thomasga has quit [Quit: Leaving.]
fschwidom has joined #ocaml
fschwidom has quit [Remote host closed the connection]
gnuvince has joined #ocaml
Submarine has quit [Remote host closed the connection]
<adrien> -and cmi_magic_number = "Caml1999I013"
<adrien> +and cmi_magic_number = "Caml1999I014"
<adrien> ...
<adrien> +and cmt_magic_number = "Caml2012T001"
<adrien> branch bin-annot, anyone remember what it does?
<adrien> (in ocaml svn)
<adrien> no ChangeLog, the only thing I can find is: + "-bin-annot", Arg.Unit f, " Save typedtree in <filename>.cmt"
<mehdid> cmt_magic_number, looks like the binary annotation files used by typerex
<adrien> that's what I had in mind too
<adrien> so, -annot and -bin-annot?
<mehdid> bin-annot has more informations than annot, aiui
<mehdid> annot has only locations and types
<mehdid> while bin-annot has the whole typedtree (as the option usage suggests)
<mehdid> the latter is useful for go-to-def type of features I guess
wmeyer` has joined #ocaml
<mehdid> but it seems that it has nasty features http://caml.inria.fr/mantis/view.php?id=5627
<adrien> arf
<adrien> but overall a good thing
<adrien> I think I'm going to his my bed very very soon =)
eni has quit [Quit: Leaving]
<wmeyer`> adrien: you said "morning" a couple of hours ago :-) time shift?
<adrien> wmeyer`: I always say "morning", no matter which time of the day it is ;-)
<wmeyer`> adrien: for me notion of morning does not exist really it can be any time during night or day ;-)
<wmeyer`> adrien: yes, exactly same here
<wmeyer`> not sure how healthy is that - perhaps bacon on eggs in the morning is less healthy
Kakadu has quit [Quit: Konversation terminated!]
<adrien> I have a pretty regular schedule, but it's always "morning" for someone on an IRC channel, so it always works =)
<wmeyer`> adrien: not here but it also works :-)
Davidbrcz has joined #ocaml
<Davidbrcz> Hi all !
<wmeyer`> Davidbrcz: Hi
<Davidbrcz> Tomorow I have a test about Ocaml. I'll have to create a little software
<Davidbrcz> and i was wondering what are the usual subjects which are given in Ocaml
<Davidbrcz> do you have any clue ?
<Davidbrcz> I thought of mathematical parser
<mehdid> a file synchronizer
<zorun> s/Ocaml/caml light/
<Davidbrcz> list manipulation
<mehdid> or an edonkey client? :)
<wmeyer`> Davidbrcz: I suppose it depends what kind of stuff your tutor is up to, could be anything - please clarify
<wmeyer`> Davidbrcz: you shall have a hint what can be
<mehdid> and how much time do you have too
<wmeyer`> Davidbrcz: of course list manipulation, but could be unix programming or unification with backtracking
<Davidbrcz> wmeyer, The course was only 20H
<wmeyer`> Davidbrcz: Then get familiar with type checker first :-)
<Davidbrcz> and tomorow we will have only 2H to do subject
<wmeyer`> Davidbrcz: could be a calculator too
Yoric has quit [Quit: Instantbird 1.2a1pre -- http://www.instantbird.com]
<Davidbrcz> such as for derivating function ?
<mfp> Davidbrcz: some kind of interpreter for a simple language
<wmeyer`> mfp: good point
<wmeyer`> Davidbrcz: any symbolic computation really
<Davidbrcz> oki oki
<Davidbrcz> thank you !
<wmeyer`> Davidbrcz: you can have symbolic derivation: http://www.cl.cam.ac.uk/teaching/Lectures/funprog-jrh-1996/
<wmeyer`> Davidbrcz: Parsing combinators
<wmeyer`> Davidbrcz: Or to show higher order functions - constructing numeric differentials
<Davidbrcz> isn't it a little bit too harsh for begininers in Ocaml ?
<Davidbrcz> beginners*
<wmeyer`> Davidbrcz: the link I sent you - contains very useful lectures - if you want some ready examples look at the examples
<wmeyer`> Davidbrcz: it's a full course - so you might skim it - the best is to just get really good at types first
<Davidbrcz> wmeyer, I'm casting a glance at it
_andre has quit [Quit: leaving]
eikke has joined #ocaml
<eikke> anyone ever looked into porting Criterion to OCaml?
<eikke> (I know about the 'benchmark' module somewhere on SF, but that's rather limited)
<hcarty> eikke: I think thelema worked on something similar
manu3000 has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.2]
<eikke> hcarty: ah, a 'bench' github repository in that account indeed :) will check it out, thanks!
err404 has joined #ocaml
<hcarty> eikke: You're welcome. I haven't used it, but I think it was designed with criterion in mind.
<hcarty> Or something similar from R
pango has quit [Ping timeout: 248 seconds]
pango has joined #ocaml
Davidbrcz has quit [Remote host closed the connection]
Davidbrcz has joined #ocaml
Davidbrcz has quit [Ping timeout: 244 seconds]
fraggle_ has joined #ocaml
smondet has quit [Remote host closed the connection]
eikke has quit [Ping timeout: 244 seconds]
<thelema_> hcarty: thanks for pointing out bench, yes it's intended to be similar to criterion
<thelema_> a lot of the internals are the same (and by the same, I mean a haskell -> ocaml translation)
osa1 has quit [Quit: Konversation terminated!]
samposm has joined #ocaml
<wmeyer`> thelema_: I am working on the fix for the oasis deps, it make take longer than I suspected Oasis is a complicated beast :-)
dsheets has quit [Quit: Leaving.]
<wmeyer`> thelema_: I think I will for additional switch for printing the dependencies onto the screen, not sure how they are dependent on the configure step however
<wmeyer`> thelema_: Being conservative means to satisfy all of them
<wmeyer`> thelema_: However it might be that just ocaml setup.ml will produce them
dsheets has joined #ocaml
<wmeyer`> thelema_: So yes, possibly adding a switch to the generated code would fix the problem with resolving dependencies
<wmeyer`> thelema_: Need to ask gildor what does he think
err404 has quit [Remote host closed the connection]
Sablier has quit [Quit: Quitte]
romildo has joined #ocaml
fraggle_ has quit [Read error: Connection reset by peer]
<romildo> It seems that OCaml does not accept the use of register type constructors in type expressions in general. For instance,
<romildo> type escEnv = {level:int; mutable escape: bool} list
<romildo> gives a syntax error.
<pippijn> right, there are no anonymous records
<romildo> So before using a record type, it has to be given name, right?
<pippijn> yes
<romildo> What is the rationale behind this?
<pippijn> probably efficiency or simplicity
<thelema_> wmeyer`: got it. no rush. I figured it would be complex; only to gildor is oasis easy
<wmeyer`> romildo: I don't know what would be a type of using level or escape tag. Of course you could limit it to the usage inside lists only, so in list constructions through :: and [] and pattern matches, maybe it would be worth to ask on the mailing list, people might give you more accurate answer
* gildor_ has been summoned from the hell of Windows
<gildor_> wmeyer`, thelema_: what is the problem ?
<wmeyer`> gildor_: there is no problem. I was thinking that processing oasis might not give the right answer about dependencies
<wmeyer`> I think the dependencies might be known after configure step
<gildor_> wmeyer`: I agree, there are some internal logic about processing conditional values that are not easy to solve
<wmeyer`> so I was thinking about armoring setup.ml with an option of showing dependencies
<wmeyer`> that would have two fold benefit - accurate dependency tracking and we wouldn't need oasis for that task