flux 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!)
tomh has quit ["http://www.mibbit.com ajax IRC Client"]
psnively has joined #ocaml
psnively has quit [Client Quit]
psnively has joined #ocaml
asmanur has quit [Remote closed the connection]
psnively has quit []
fy___ has joined #ocaml
fy___ has quit [Client Quit]
FoolOfSoul has quit [Read error: 110 (Connection timed out)]
<jeddhaberstro> Would someone mind critiquing a little bit of my code?
<jeddhaberstro> http://pasteall.org/1899/ocaml if anyone wants to take a look
<bluestorm> jeddhaberstro:
<bluestorm> your multiple "where" clause are awkward
<jeddhaberstro> i found one thing all ready :)
<jeddhaberstro> yeah, the where clauses are pointless
<bluestorm> do only one clause, and compute the function on the fly
<jeddhaberstro> oh, how do u do that?
<jeddhaberstro> do you mean somehow casting "+" to (+)?
<bluestorm> Fun ((match math with "+" -> (+) | "-" -> (-) | ...), interp_aux c1, ... )
<jeddhaberstro> ah
<bluestorm> btw
<bluestorm> why are you using a temporary "listf" layer ?
<bluestorm> you could compute in one pass only
<bluestorm> last, you could define a small DSL for your AST
<jeddhaberstro> DSL?
<bluestorm> let (!) x = Int x and op str a b = BinOp (str, a, b) in
<jeddhaberstro> let me work on doing it in one pass
<bluestorm> let (+!) = op "+" and (-!) = op "-" and ( *!) = op "*" and (/!) = op "/" in
<bluestorm> !2 *! !3 +! !5
<jeddhaberstro> This is better.. http://pasteall.org/1900/ocaml
<Associat0r> guys are there ocaml IDE's that figure out the file compilation order by themeselves?
<jeddhaberstro> what does DSL stand for by the way?
<mbishop> Domain Specific Language
<jeddhaberstro> ah
<jeddhaberstro> thanks
<Associat0r> can anyone tell me the exact reason why an F# IDE can't figure out the order of compilation itself like seen here http://lorgonblog.spaces.live.com/blog/cns!701679AD17B6D310!347.entry while Visual Haskell for example could?
<Associat0r> I guess it applies to ocaml too
<bluestorm> Associat0r:
<bluestorm> try ocamldepend
<bluestorm> or ocamlbuild
mikezackles has quit [Read error: 60 (Operation timed out)]
bzzbzz has quit ["leaving"]
<jeddhaberstro> what's the best to compile ocaml source code? Is there something like SCons?
<bluestorm> jeddhaberstro: if you have simple source, the usual tools are more than enough
<bluestorm> that is ocaml, ocamlc, ocamlopt
<jeddhaberstro> yeah
<bluestorm> if you want something more sophisticated you have ocamlfind
<bluestorm> and even more sophisticated, ocamlbuild
<bluestorm> wich is probably the more scons-like of all
<bluestorm> trying simple things first is probably a better idea, still : spending some time to get used to a powerful build system to compile two miserable files of code does not make sense
coucou747 has quit [Read error: 113 (No route to host)]
jeddhaberstro has quit []
ygrek_away has joined #ocaml
m3ga has joined #ocaml
Proteus has quit ["Leaving"]
bluestorm has quit ["Leaving"]
Proteus has joined #ocaml
ygrek_away has quit [Remote closed the connection]
m3ga has quit ["disappearing into the sunset"]
Tankado has joined #ocaml
<Tankado> If i have a rational number represented as int*int and now i want to convert the value to some real so pass to another function can i do something like Int.toReal(rat) ?
Proteus_ has joined #ocaml
<Tankado> and is "@" an append of list?
<flux> you can create a module Int with function toReal if that was your question
<flux> and yes
<Tankado> flux : i am not realy familiar with modules
<Tankado> i just have Rat(x,y) and i want to convert this to a number (real)
<flux> tankado, write file int.ml which has the function
<flux> it will create module Int
<flux> simple compiling: ocamlc -o result int.ml yourothercode.ml
<Tankado> but how the function will go
<flux> well, what should it do?
<Tankado> make a representation of rat number consist of 2 numbers into one number i can pass to a function
<flux> I was thinking more in the terms of a low-level algorithm
<Tankado> i think you confusing my request for something much more complicated or i just dont understand what you saying
<Tankado> will a function like this fn(rat) => (Rat(x,y)) => x/y work?
<Tankado> fn(Rat(x,y))=>x/y
Proteus has quit [Read error: 113 (No route to host)]
Associat0r has quit []
<Tankado> anyone know how i can convert from int to real?
Asmadeus has joined #ocaml
Tankado has quit ["Leaving"]
GustNG has joined #ocaml
filp has joined #ocaml
Amorphous has quit [Read error: 104 (Connection reset by peer)]
Amorphous has joined #ocaml
Yoric[DT] has joined #ocaml
mishok13 has joined #ocaml
vixey has joined #ocaml
ygrek has joined #ocaml
hml has joined #ocaml
<hml> anyone konw where to get a used physical print of ocaml for scientists?
guillem has joined #ocaml
<GustNG> Fat chance. Don't be cheap. >:c
<hml> ha; i'm a student, lol
<Asmadeus> Ask your school's library to get one; they usually can if there are enough people requesting (say, two or three; you can have friends asking even if they don't really want to read it :P)
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
<Proteus_> I'm in the same situation as hml - is ocaml for scientists worth the effort?
<Proteus_> I mean, I have $0
<Proteus_> I'm not sure what that converts to in pounds
<vixey> Proteus_: if you want to learn ocaml you can certainly do it by reading texts online
<Proteus_> maybe jon will be in a giving mood and give me a pdf, or something.
<Asmadeus> Well, he's making a living out of such things, I don't know if that will happen :)
<GustNG> That's bad business.
<Proteus_> yeah, I know
<Asmadeus> But I'm somewhat wondering though, I think it's supposed to be a bit more than "learning ocaml", sadly haven't read it though :(
<GustNG> For programmers who need cash though, I can say Flash web games.
<Proteus_> i'm not sure it's bad business to get one more ocaml programmer out there, espeicially one who can't possibly afford his book
<Proteus_> haha
<Asmadeus> If you're looking to learn ocaml, there are other contents online :)
<GustNG> Proteus_: But making an exception is impolite to hundreds of other people who don't want to buy it because of money.
<jynxzero> There's at least one free book: "Developing applications with Objective Caml
<jynxzero> "
<Proteus_> there's also the pre-publish pdf of the cambridge book
<Proteus_> which is quite nice
<hml> wait ... ocaml for scientists, is a physical book, not a pdf?
<hml> i just placed an order; and thought i'd get a physical book and a pdf
<hml> but ... besides that world pay site saying that they charged my credit card, i have gotten nothing so far; neither a pdf link nor a confirmation of a shipment
<Asmadeus> I think it's just a physical book
<Asmadeus> Proteus_: I've heard http://files.metaprl.org/doc/ocaml-book.pdf was good too, if you need to learn. Or you can just quickly browse through ocaml-tutorial.org
<Proteus_> yeah
<hml> i wasnt' impressed by jason hickey's book
<vixey> Proteus_: Why do you want to learn ocaml though?
<Proteus_> many reasons. I've been toying with it for quite a while and find it to be powerful, elegant, and robust
<vixey> what will you program with it ?
<hml> the one thing that tempts me about ocaml
<hml> is it's speed advanteage ove rhaskell
<Proteus_> bioinformatics apps, I'm working on a ogre3d-based game engine and game and ocaml seems like a good language for procedurally generating content
<hml> why can't those ghc guys make haskell faster?
<Proteus_> purity
<hml> purity should make things faster since the compikler can do more optimixaiont
<hml> like how coding in c beats assembly on average (since hand assembly gets tiring after a while), the ghc compiler should be beating these impure languages
<Proteus_> the difference between c and asm is relatively insignificant
<Proteus_> and has no relation to pure vs. impure languages
<hml> _purity shoudl abe a compiler writers' dream
<Proteus_> I don't follow you
<mfp> Proteus_: more than purity, I'd point at laziness and the use of combinators everywhere
<GustNG> Tiny scope.
<mfp> ah and [Char] ;-)
seafood has joined #ocaml
<hml> ls
<Proteus_> mfp, the GHC programmers are hardly stupid. If performance were such a low hanging fruit then they'd do it. But Haskell isn't the drag racer of languages, and it isn't low hanging fruit, so perhaps you should consider that you're missing something vital and do some research. ;-)
seafood has quit [Read error: 104 (Connection reset by peer)]
<mfp> GHC is comparatively much more advanced than the semi-naïve ocamlopt, but Haskell is much more demanding to being with
<vixey> #haskell
seafood has joined #ocaml
<mfp> Proteus_: when did I imply so?
* vixey thinks Proteus meant to direct that at hml
<Proteus_> oh merde, my apologies
<Proteus_> I'm very tired
<hml> i'd love to have ocaml with haskell syntax
<hml> ocaml code somehow just looks so ugly
<hml> sorry; not meant to troll
<mfp> np, maybe I'm missing something vital, my OCaml code is still faster than my Haskell :P
<mfp> hml: have you seen the pa_where extension?
<hml> isn't ocaml supposed to be faster than haskell?
<mfp> usually, yes
<Proteus_> ocaml is a pragmatic language, haskell is rather idealistic.
<mfp> GHC can beat it at some micro-benchmarks given enough manpower
<vixey> Proteus_: They are both pragmatic
<Proteus_> vixey, really? oh. Perhaps I'm just ignorant of some details of Haskell then.
<Proteus_> it was my impression
<mfp> vixey: if Haskell is pragmatic, what's an "idealistic" language then, brainfuck? :)
<hml> what's haskel pragmatic for, other than writing resea4rch pape4rs? :-)
<mfp> at any rate, things like the ability to do both imperative and functional code or the printf integrated in the type system make OCaml more pragmatic IMO
<vixey> well you can do both these things in haskell
<vixey> mfp: coq maybe
<mfp> heh
<Proteus_> I'm writing a game/game engine/engine toolset and I need to generate a lot of geometry, code, and whatnots. I plan to have bits of ocaml code in the running game. I really can't see haskell being used in this way.
seafood has quit [Read error: 104 (Connection reset by peer)]
<vixey> mfp: (sorry for being a bit off topic but this -is- cool http://www.lri.fr/perso/~sozeau/repos/coq/misc/shiftreset/GenuineShiftReset.html )
seafood has joined #ocaml
<vixey> Proteus_: You probably just have more experience with ocaml then
<Proteus_> vixey, would you recommend haskell for real time applications?
<vixey> no I wouldn't recommend anything
<mfp> vixey: similar in spirit to the classical functional unparsing, no?
<Proteus_> vixey, but you can see haskell being used in this way?
<mfp> str "The value of " ^^ fmt (T:=T) pr_str ^^ str " is " ^^ fmt (T:=T) (B:=A) pr_int
<Proteus_> sucessfully
<mfp> "The value of %s is %d"
<mfp> it's not about whether the type-safe printf is doable
<mfp> but rather the choice to integrate format strings in OCaml's type sys which makes it a pragmatic
<mfp> because it's ad-hoc, and not really needed because there's also functional unparsing
<mfp> but it's convenient
<mfp> which makes it a pragmatic design choice
<Proteus_> incidentally, when calling functions to<->from C, what sort of performance penalty does one incur?
<mfp> Proteus_: if the C function is declared as "noalloc", essentially none
<Proteus_> nice
<mfp> just the overhead of placing the params on the stack (x86) or moving to the right regs on x86_64
vixey has quit [Read error: 104 (Connection reset by peer)]
<mfp> if the C function allocates, either directly or indirectly (by calling an ocaml callback or raising an exception), there's some overhead
<mfp> I counted some 20 instructions or so IIRC, dunno about the cycles
vixey has joined #ocaml
<mfp> ah and a branch misprediction
<hml> /quit
hml has quit ["leaving"]
<Proteus_> branch misprediction?
<mfp> because there's an indirect jump in caml_c_call
<Proteus_> ah
<vixey> doesn't ocaml get compiled into native code?
<Proteus_> yes
<mfp> caml_c_call saves some context for exception management & GC and does an indirect jump
<vixey> so could it not be possible that calling a C function would just be unboxing some parameters and doing exactly what C does, then re-boxing them?
<mfp> then in the C function, you have to register extra roots (CAMLparamN, etc.)
<mfp> vixey: that's what happens when the external is declared as "noalloc"
<mfp> minus the unboxing, because the C func receives and returns value types
<mfp> Proteus_: the figure I gave before was incorrect (must have been what I measured _including_ some root registration with CAMLparamN/CAMLlocalN)
seafood has quit [Read error: 110 (Connection timed out)]
<mfp> it's actually 4 instructions + indirect jump + root registration (if needed) http://pastebin.com/m52849fed
asmanur has joined #ocaml
rwmjones has joined #ocaml
<Proteus_> that's still not too bad
<mfp> you can often avoid allocation in the C func
<mfp> e.g., when you have exceptions
<Proteus_> is all this documented somewhere? all I've found is the little chapter in the manual.
<mfp> instead of doing the equiv of let foo a b = if bad_args a b then invalid_arg "f: bad a, b"; ... in C and external foo : a -> b -> c = "mylib_foo",
<Asmadeus> What's documented is how to use it, to see that he just looked at the asm code dumped by ocamlopt
<Asmadeus> Probably :P
<mfp> external foo_unsafe : a -> b -> c = "mulib_foo" "noalloc" and let foo a b = if bad_args a b then invalid_arg "f: bad a, b"; foo_unsafe a b
<mfp> yeah, this I learned by reading the .s
<rwmjones> anyone here using coq? if so, what is /usr/bin/parser used for?
<mfp> both the code generated by ocamlopt, and ocaml/asmrun/{i386,amd64}.S in the compiler's sources
<Proteus_> mfp, thanks for the info.
<mfp> np
<Proteus_> I may need to make somewhat extensive use of the FFI
<mfp> ah there's another thing
<mfp> you can use unboxed floats in externals too
<mfp> with the "float" predicate
<mfp> there was a message on caml-list where xleroy explained this (I haven't used it myself)
<mfp> IIRC, by doing external foo : float -> float -> float = "foo" "noalloc" "float", you could use some double foo(double a, double b){ ... }
<mfp> instead of passing/returning a float boxed in a value
<mfp> it's actually used like this: pervasives.ml:external exp : float -> float = "caml_exp_float" "exp" "float"
<mfp> so caml_exp_float must be the version with boxed floats (for bytecode and native when needed), and exp the unboxed one
<Proteus_> when would you need it boxed in native?
<mfp> hmmm for instance if it's a tail call in a function returning a float that hasn't been inlined?
Jomyoot has joined #ocaml
<mfp> it might use the unboxed one if it's got the floats in a register and box after the call, dunno
Jomyoot has left #ocaml []
<mfp> duh
<mfp> there's one situation where it will use the boxed one:
<mfp> let apply f x = f x .... apply sqrt 10.
<Proteus_> on the other hand, if I'm calling a lot of big functions on one side or the the other, these little opimisations wouldn't really matter much, correct?
<mfp> right
seafood has joined #ocaml
seafood has quit [Connection reset by peer]
seafood has joined #ocaml
<Proteus_> still potentially useful though - thanks mfp.
<Proteus_> I'm headed to bed. Good night to all.
Proteus_ has quit ["Leaving"]
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit []
coucou747 has joined #ocaml
seafood has joined #ocaml
seafood has quit []
tomh has joined #ocaml
vixey has quit []
seafood has joined #ocaml
seafood has quit []
mikezackles has joined #ocaml
Associat0r has joined #ocaml
ygrek has quit [Remote closed the connection]
RobertFischer has joined #ocaml
marmotine has joined #ocaml
asmanur has quit [Read error: 104 (Connection reset by peer)]
rog1 has joined #ocaml
struk_atwork has joined #ocaml
struk_atwork has quit [Client Quit]
vixey has joined #ocaml
Linktim has joined #ocaml
GustNG has quit ["Leaving."]
GustNG has joined #ocaml
RobertFischer has quit ["Taking off -- check out http://smokejumperit.com and http://enfranchisedmind.com/blog/"]
pango_ has quit [Remote closed the connection]
<hcarty> mfp: Thanks for mentioning the "noalloc" and "float" FFI tags. I may not ever use them, but it's nice to know they are there...
vixey has quit [Read error: 113 (No route to host)]
vixey has joined #ocaml
pango_ has joined #ocaml
jlouis has joined #ocaml
Linktim_ has joined #ocaml
ygrek has joined #ocaml
Associ8or has joined #ocaml
jlouis has quit [clarke.freenode.net irc.freenode.net]
shortc|desk has quit [clarke.freenode.net irc.freenode.net]
Hadaka has quit [clarke.freenode.net irc.freenode.net]
flux has quit [clarke.freenode.net irc.freenode.net]
mishok13 has quit [clarke.freenode.net irc.freenode.net]
mikezackles has quit [clarke.freenode.net irc.freenode.net]
ido has quit [clarke.freenode.net irc.freenode.net]
munga has quit [clarke.freenode.net irc.freenode.net]
l_a_m has quit [clarke.freenode.net irc.freenode.net]
ulfdoz has quit [clarke.freenode.net irc.freenode.net]
Amorphous has quit [clarke.freenode.net irc.freenode.net]
jdev has quit [clarke.freenode.net irc.freenode.net]
mfp has quit [clarke.freenode.net irc.freenode.net]
hcarty has quit [clarke.freenode.net irc.freenode.net]
coucou747 has quit [clarke.freenode.net irc.freenode.net]
szell has quit [clarke.freenode.net irc.freenode.net]
haelix has quit [clarke.freenode.net irc.freenode.net]
jynxzero has quit [clarke.freenode.net irc.freenode.net]
Associat0r has quit [clarke.freenode.net irc.freenode.net]
tomh has quit [clarke.freenode.net irc.freenode.net]
Asmadeus has quit [clarke.freenode.net irc.freenode.net]
netx has quit [clarke.freenode.net irc.freenode.net]
Axioplase_ has quit [clarke.freenode.net irc.freenode.net]
smimou has quit [clarke.freenode.net irc.freenode.net]
tab_ has quit [clarke.freenode.net irc.freenode.net]
Lalu has quit [clarke.freenode.net irc.freenode.net]
cmeme has quit [clarke.freenode.net irc.freenode.net]
Sparkles has quit [clarke.freenode.net irc.freenode.net]
wlmttobks has quit [clarke.freenode.net irc.freenode.net]
svenl has quit [clarke.freenode.net irc.freenode.net]
Linktim_ has quit [clarke.freenode.net irc.freenode.net]
vixey has quit [clarke.freenode.net irc.freenode.net]
Linktim has quit [clarke.freenode.net irc.freenode.net]
rog1 has quit [clarke.freenode.net irc.freenode.net]
ikatz has quit [clarke.freenode.net irc.freenode.net]
jeremiah has quit [clarke.freenode.net irc.freenode.net]
Mr_Awesome has quit [clarke.freenode.net irc.freenode.net]
xevz has quit [clarke.freenode.net irc.freenode.net]
pattern has quit [clarke.freenode.net irc.freenode.net]
marmotine has quit [clarke.freenode.net irc.freenode.net]
guillem has quit [clarke.freenode.net irc.freenode.net]
jonafan has quit [clarke.freenode.net irc.freenode.net]
rogo has quit [clarke.freenode.net irc.freenode.net]
Demitar has quit [clarke.freenode.net irc.freenode.net]
bohanlon has quit [clarke.freenode.net irc.freenode.net]
petchema has quit [clarke.freenode.net irc.freenode.net]
GustNG has quit [clarke.freenode.net irc.freenode.net]
rwmjones has quit [clarke.freenode.net irc.freenode.net]
Ugarte has quit [clarke.freenode.net irc.freenode.net]
mattam has quit [clarke.freenode.net irc.freenode.net]
sbok has quit [clarke.freenode.net irc.freenode.net]
gim_ has quit [clarke.freenode.net irc.freenode.net]
r0bby has quit [clarke.freenode.net irc.freenode.net]
ppsmimou has quit [clarke.freenode.net irc.freenode.net]
bla has quit [clarke.freenode.net irc.freenode.net]
toxygen has quit [clarke.freenode.net irc.freenode.net]
ertai has quit [clarke.freenode.net irc.freenode.net]
thelema has quit [clarke.freenode.net irc.freenode.net]
TaXules has quit [clarke.freenode.net irc.freenode.net]
ygrek has quit [clarke.freenode.net irc.freenode.net]
pango_ has quit [clarke.freenode.net irc.freenode.net]
Yoric[DT] has quit [clarke.freenode.net irc.freenode.net]
fremo_ has quit [clarke.freenode.net irc.freenode.net]
Smerdyakov has quit [clarke.freenode.net irc.freenode.net]
acatout has quit [clarke.freenode.net irc.freenode.net]
tsuyoshi has quit [clarke.freenode.net irc.freenode.net]
Associ8or has quit []
petchema has joined #ocaml
bohanlon has joined #ocaml
Demitar has joined #ocaml
rogo has joined #ocaml
jonafan has joined #ocaml
guillem has joined #ocaml
marmotine has joined #ocaml
pattern has joined #ocaml
xevz has joined #ocaml
Mr_Awesome has joined #ocaml
jeremiah has joined #ocaml
ikatz has joined #ocaml
rog1 has joined #ocaml
vixey has joined #ocaml
Linktim_ has joined #ocaml
Sparkles has joined #ocaml
cmeme has joined #ocaml
tab_ has joined #ocaml
Lalu has joined #ocaml
smimou has joined #ocaml
Axioplase_ has joined #ocaml
netx has joined #ocaml
Asmadeus has joined #ocaml
tomh has joined #ocaml
Associat0r has joined #ocaml
ygrek has joined #ocaml
pango_ has joined #ocaml
Yoric[DT] has joined #ocaml
fremo_ has joined #ocaml
Smerdyakov has joined #ocaml
tsuyoshi has joined #ocaml
acatout has joined #ocaml
tsuyoshi has quit [Read error: 104 (Connection reset by peer)]
cmeme has quit [Killed by ballard.freenode.net (Nick collision)]
GustNG has joined #ocaml
rwmjones has joined #ocaml
Ugarte has joined #ocaml
mattam has joined #ocaml
sbok has joined #ocaml
gim_ has joined #ocaml
r0bby has joined #ocaml
toxygen has joined #ocaml
ppsmimou has joined #ocaml
bla has joined #ocaml
cmeme has joined #ocaml
tab has joined #ocaml
TaXules has joined #ocaml
thelema has joined #ocaml
ertai has joined #ocaml
szell has joined #ocaml
haelix has joined #ocaml
jynxzero has joined #ocaml
wlmttobks has joined #ocaml
svenl has joined #ocaml
Axioplase_ has quit [Success]
Asmadeus_ has joined #ocaml
fremo has joined #ocaml
hcarty has joined #ocaml
mfp has joined #ocaml
jdev has joined #ocaml
ulfdoz has joined #ocaml
Amorphous has joined #ocaml
Jeff_123 has joined #ocaml
shortc|desk has joined #ocaml
jlouis has joined #ocaml
Jedai has joined #ocaml
mikezackles has joined #ocaml
mishok13 has joined #ocaml
ido has joined #ocaml
Hadaka has joined #ocaml
flux has joined #ocaml
l_a_m has joined #ocaml
munga has joined #ocaml
Associat0r has quit [SendQ exceeded]
tsuyoshi has joined #ocaml
acatout has quit [Killed by ballard.freenode.net (Nick collision)]
acatout has joined #ocaml
acatout_ has joined #ocaml
Axioplase_ has joined #ocaml
middayc has joined #ocaml
tab_ has quit [Read error: 104 (Connection reset by peer)]
acatout_ has quit [Client Quit]
Asmadeus has quit [No route to host]
fremo_ has quit [Read error: 111 (Connection refused)]
rstites has joined #ocaml
ygrek_ has joined #ocaml
ygrek has quit [Remote closed the connection]
jonafan_ has joined #ocaml
filp has quit ["Bye"]
jonafan_ has quit ["Leaving"]
jonafan_ has joined #ocaml
jonafan has quit [Read error: 110 (Connection timed out)]
jonafan_ is now known as jonafan
Linktim has joined #ocaml
mishok13 has quit [Read error: 104 (Connection reset by peer)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Asmadeus_ is now known as Asmadeus
tvn1981a has joined #ocaml
filp has joined #ocaml
vpalle has joined #ocaml
<tvn1981a> so if I want to guarantee my code will never reach this line, can I use "assert false;" ? the compiler complains this statement never returns (or have unsound type) ? is there a better "assert" way ?
<Asmadeus> assert false throws an exception
<Asmadeus> I think it shows on which line, just like a match failure, but I'm not certain
<Asmadeus> You might want to use failwith if you want to check which one it is faster
<tvn1981a> I just want it to crash (or stop) if it ever reaches that line
<tvn1981a> assert (1=0) works fine but it looks ugly
<flux> (assert false : unit)?
<flux> or perhaps I don't see what the rest of the code looks like
<Asmadeus> No, it's not unit
<mfp> tvn1981a: failwith "this should never be reached because ...."
<Asmadeus> Exceptions have a weird type, it can be anything in such cases
<Asmadeus> And "assert false" works, since 1=0 evaluate as false :)
<jlouis> exceptions are pretty cheap in ocaml
<jlouis> (when you are not requesting stack traces, that is)
<Asmadeus> It's just that you might use aggressive catch (try ... with _ -> ...) which would catch the assert failure
<vixey> if you don't want an expcetion, let rec impossible () = impossible ();;
<vixey> then you can write
<vixey> impossible ()
<vixey> somewhere
<flux> and get stuck? great :)
<vixey> no you don't get stuck (at least we hope), since getting to that branch is impossible
<Asmadeus> And it'll crash stack overflow soon enough
<vixey> oh really?
<vixey> I don't thin that will ever crash
<Asmadeus> It will :P
<vixey> I'm running it now and it's not crashed yet
<Asmadeus> Oh yeah
<Asmadeus> It's tailrecursive
<Asmadeus> Have it do 1 + impossible ()
<Asmadeus> And then it will
<flux> well, it would raise an exception, eventually ;)
<Asmadeus> I don't think that's an exception
<flux> really? it may crash, at times, such as with natively compiled binaries, but the general principle should be that it throws?
<Asmadeus> Hum, don't know
<flux> hmm
<Asmadeus> Gotta try.. give me a sec :P
<flux> no exception in toplevel
<flux> Fatal error: exception Stack_overflow
<flux> on a standalone bytecode binary
<flux> also with native binary
RobertFischer has joined #ocaml
<Asmadeus> Well, it's an exception in native
<Asmadeus> tried "try impossible () with _ -> print_endline "thing"; 1" and it showed "thing"
RobertFischer has left #ocaml []
<Asmadeus> Well, that's great, although I'd have sworn that would crash :P
<flux> I think it still can at unfortunate moments
<flux> although bytecode binaries should always handle that
<flux> I suppose for example when you call c code exactly when you run out of stack?
<flux> unless it handles it with signal handlers somehow
<Asmadeus> Heh, that's not something I'd be able to try
Tankado has joined #ocaml
<Asmadeus> Well, in fact probably can. You can use a ref to get the stack size and call the function at the precise moment
<Tankado> Hello i try to compile my code in SML and i get this error : 49.33 Error: syntax error: inserting LPAREN
<Tankado> anyone know anything?
<Asmadeus> Well, I don't know SML but are you sure you've got all the parenthesises necessary at the right place ?
<vixey> I can't see you code
<Tankado> i can paste it but does 49.33 mean a line or something?
<Asmadeus> probably line.char number
<Tankado> yeah got it
<Tankado> thanks
<jlouis> Tankado, line.char indeed. The SML/NJ parser has the ability to attempt to make the parse work by inserting or deleting things from the parse (to get more than one error)
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
vixey has quit []
seafood_ has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood_ has quit [Read error: 104 (Connection reset by peer)]
coucou747 has joined #ocaml
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
marmotine has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
seafood_ has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood_ has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
Ched- has joined #ocaml
Associat0r has joined #ocaml
Tankado has quit ["Leaving"]
marmotine has joined #ocaml
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
rwmjones has quit ["Closed connection"]
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
middayc_ has joined #ocaml
seafood has quit [Client Quit]
tvn1981a has quit [Remote closed the connection]
middayc has quit [Read error: 110 (Connection timed out)]
ygrek_ has quit [Remote closed the connection]
ygrek has joined #ocaml
GustNG has quit [Read error: 104 (Connection reset by peer)]
tvn1981a has joined #ocaml
redocdam has joined #ocaml
<tvn1981a> what's the function to create a directory in ocaml ?
Anarchos has joined #ocaml
<Anarchos> i have an interface with ocaml in c++ which leads to a segfault. Can someone look my code in http://pastebin.com/me607582 ?
Ched- has quit [Read error: 104 (Connection reset by peer)]
<Anarchos> i will go back, but i am really interested in an enlightened opinion about my interface
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
filp has quit ["Bye"]
Ched- has joined #ocaml
<mfp> tvn1981a: Unix.mkdir
<tvn1981a> mfp: thanks
ofaurax has joined #ocaml
ygrek has quit [Remote closed the connection]
<tvn1981a> how do I print the Digest of a string "hello" ? I tried something like Printf.printf "%s" (Digest.string "hello");; but doesn't work --
tomh- has joined #ocaml
tomh has quit ["http://www.mibbit.com ajax IRC Client"]
tomh- is now known as tomh
<hcarty> tvn1981a: I havne't used the Digest module, but I would guess that you want to Digest.to_hex function
<tvn1981a> hcarty: yeh I'll try that
<tvn1981a> thanks
ofaurax has quit ["Leaving"]
Ched- has quit [Remote closed the connection]
ofaurax has joined #ocaml
ofaurax has quit [Read error: 104 (Connection reset by peer)]
<tvn1981a> what's the difference btw these 2 matching statments 1) match n with | 1 -> dosomething1 | 2 -> dosomething2 2) match n with 1-> dosomething1 | 2->dosomething2 ? Syntax wise the only difference is the extra "|" in 1) -- does it have any effect ?
Jedai has quit [Read error: 110 (Connection timed out)]
<Asmadeus> It's the same
Ched- has joined #ocaml
<tvn1981a> k - I thought so too - thanks
Linktim_ has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has quit ["Ex-Chat"]
asmanur has joined #ocaml
Linktim has joined #ocaml
Linktim has quit [Read error: 104 (Connection reset by peer)]
vpalle_ has joined #ocaml
Linktim_ has quit [Read error: 110 (Connection timed out)]
vpalle has quit [Read error: 110 (Connection timed out)]
mikezackles has quit [Read error: 110 (Connection timed out)]
jeddhaberstro has joined #ocaml
jlouis has quit [Remote closed the connection]
tomh has quit ["http://www.mibbit.com ajax IRC Client"]
vpalle_ has quit ["Leaving"]
Asmadeus has quit ["nightynight"]
marmotine has quit ["mv marmotine Laurie"]
xevz_ has joined #ocaml
guillem has quit [Remote closed the connection]
xevz has quit [Read error: 110 (Connection timed out)]
xevz_ is now known as xevz