adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 4.00.1 http://bit.ly/UHeZyT | http://www.ocaml-lang.org | Public logs at http://tunes.org/~nef/logs/ocaml/
cdidd has quit [Remote host closed the connection]
avsm has quit [Quit: Leaving.]
jamii has quit [Ping timeout: 244 seconds]
sgnb has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
sgnb has joined #ocaml
sgnb has quit [Ping timeout: 244 seconds]
travisbrady has joined #ocaml
sgnb has joined #ocaml
bobry has joined #ocaml
vaati has joined #ocaml
sgnb has quit [Ping timeout: 248 seconds]
lolcathost has joined #ocaml
vaati has quit [Ping timeout: 244 seconds]
vaati has joined #ocaml
sgnb has joined #ocaml
sgnb has quit [Ping timeout: 264 seconds]
sgnb has joined #ocaml
lolcathost has left #ocaml []
sgnb has quit [Read error: Connection reset by peer]
sgnb has joined #ocaml
vaati_ has joined #ocaml
vaati has quit [Ping timeout: 260 seconds]
vaati__ has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
vaati_ has quit [Ping timeout: 252 seconds]
sgnb has joined #ocaml
sgnb has quit [Ping timeout: 265 seconds]
madroach has quit [Ping timeout: 244 seconds]
madroach has joined #ocaml
sgnb has joined #ocaml
sgnb has quit [Ping timeout: 264 seconds]
Yoric has joined #ocaml
Submarine has joined #ocaml
lolcathost has joined #ocaml
mjonsson has quit [Read error: Connection reset by peer]
sgnb has joined #ocaml
mjonsson has joined #ocaml
sgnb has quit [Ping timeout: 244 seconds]
travisbrady has quit [Quit: travisbrady]
astertronistic has joined #ocaml
sgnb has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
Progster has joined #ocaml
sgnb has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
Yoric has quit [Ping timeout: 252 seconds]
tac has joined #ocaml
tac has quit [Client Quit]
sgnb has joined #ocaml
ulfdoz has joined #ocaml
xavierm02 has quit [Quit: Leaving]
lolcathost has quit [Ping timeout: 244 seconds]
lolcathost has joined #ocaml
sgnb has quit [Ping timeout: 246 seconds]
ulfdoz has quit [Ping timeout: 260 seconds]
sgnb has joined #ocaml
sgnb has quit [Ping timeout: 246 seconds]
Submarine has quit [Ping timeout: 240 seconds]
Progster has quit [Read error: Operation timed out]
coldpizza72i has joined #ocaml
<coldpizza72i> do rb-trees in functional languages work the same way as in imperative… do they use rotations and stuff to balance etc?
astertronistic has quit [Ping timeout: 245 seconds]
sgnb has joined #ocaml
<coldpizza72i> basically I'm interested in knowing if they follow the same idea for inserting elements into a red black tree for example or if it does something completely different
sgnb has quit [Ping timeout: 265 seconds]
vaati__ has left #ocaml []
mjonsson has quit [Ping timeout: 244 seconds]
lolcathost has quit [Ping timeout: 256 seconds]
sgnb has joined #ocaml
lolcathost has joined #ocaml
<Ptival> coldpizza72i: I believe the concepts are similar, but the implementation is slightly different due to the paradigm
<Ptival> for instance, the "rotation" might elaborate into some pointers-shifting in an imperative setting, while on the functional side it's just shapeshifting your ADT
lolcathost has quit [Quit: test]
lolcathost has joined #ocaml
Yoric has joined #ocaml
adrien is now known as adrien_pasla
adrien_pasla is now known as adrien
shajen has quit [Read error: Connection reset by peer]
shajen has joined #ocaml
astertronistic has joined #ocaml
answer_42 has joined #ocaml
andreypopp has joined #ocaml
astertronistic has quit [Ping timeout: 252 seconds]
ankit9 has joined #ocaml
pango is now known as pangoafk
coldpizza72i has quit [Quit: coldpizza72i]
Cyanure has joined #ocaml
Neros_ has quit [Ping timeout: 244 seconds]
answer_42 has quit [Ping timeout: 276 seconds]
hkBst has joined #ocaml
hkBst has quit [Changing host]
hkBst has joined #ocaml
astertronistic has joined #ocaml
Cyanure has quit [Remote host closed the connection]
astertronistic has quit [Ping timeout: 255 seconds]
astertronistic has joined #ocaml
andreypopp has quit [Quit: sleep]
testcocoon has quit [Quit: Coyote finally caught me]
testcocoon has joined #ocaml
Cyanure has joined #ocaml
lolcathost has quit [Ping timeout: 248 seconds]
ftrvxmtrx has quit [Quit: Leaving]
lolcathost has joined #ocaml
lolcathost has quit [Client Quit]
lolcathost has joined #ocaml
ankit9 has quit [Ping timeout: 244 seconds]
ontologiae has joined #ocaml
ankit9 has joined #ocaml
avsm has joined #ocaml
andreypopp has joined #ocaml
Yoric has quit [Ping timeout: 255 seconds]
srcerer_ has joined #ocaml
srcerer has quit [Ping timeout: 244 seconds]
brendan has quit [Ping timeout: 272 seconds]
Yoric has joined #ocaml
brendan has joined #ocaml
Kakadu has joined #ocaml
mcclurmc_away is now known as mcclurmc
thomasga has joined #ocaml
avsm has quit [Quit: Leaving.]
astertronistic has quit [Ping timeout: 264 seconds]
_andre has joined #ocaml
<yezariaely> Is there some work for automating parallelism in OCaml? e.g. similar to data parallel haskell?
avsm has joined #ocaml
avsm1 has joined #ocaml
avsm has quit [Ping timeout: 252 seconds]
<pippijn> can I use non-core modules in myocamlbuild?
<pippijn> I want ocamlbuild, when building myocamlbuild, to do this: /usr/bin/ocamlopt.opt -I /usr/lib/ocaml/ocamlbuild -I /usr/local/lib/ocaml/3.12.1/pbuild unix.cmxa /usr/lib/ocaml/ocamlbuild/ocamlbuildlib.cmxa /usr/local/lib/ocaml/3.12.1/pbuild/pbuild.cmxa myocamlbuild.ml /usr/lib/ocaml/ocamlbuild/ocamlbuild.cmx -o myocamlbuild
<pippijn> I want to use the package "pbuild"
<pippijn> I tried this: <myocamlbuild.*>: pkg_pbuild, use_pbuild
<pippijn> oh
<pippijn> There is no direct support to link external modules with your plugin. For now the only way to achieve this is to invoke ocamlbuild as follows (the example uses the Str module) :
<pippijn> ocamlbuild -ocamlc 'ocamlc str.cma' -ocamlopt 'ocamlopt str.cmxa'
<pippijn> how can I make oasis do this?
<pippijn> ok, ocamlbuildflags
<Kakadu> pippijn: fix findlib.conf, oasis -setup, fix findlib.conf again :)
Yoric has quit [Ping timeout: 246 seconds]
<pippijn> oasis doesn't use ocamlbuildflags
<pippijn> oh wait
<pippijn> pbuild uses ocamlbuild_plugin
<pippijn> oh this sucks
avsm1 has quit [Quit: Leaving.]
cdidd has joined #ocaml
<pippijn> got it
lolcathost has quit [Quit: test]
leoncamel has joined #ocaml
lolcathost has joined #ocaml
avsm has joined #ocaml
larhat has joined #ocaml
fusillia has joined #ocaml
avsm has quit [Ping timeout: 260 seconds]
xavierm02 has joined #ocaml
leoncamel has quit [Remote host closed the connection]
Yoric has joined #ocaml
Neros has joined #ocaml
avsm has joined #ocaml
sepp2k has joined #ocaml
answer_42 has joined #ocaml
avsm1 has joined #ocaml
avsm has quit [Ping timeout: 248 seconds]
lolcathost has quit [Ping timeout: 248 seconds]
<kba> List.for_all2 (function a b -> true) lista listb
<kba> What's wrong with that statement? I just get a Syntax error
<kba> "true" is obviously dummy just to see if that could compile
lolcathost has joined #ocaml
<Kakadu> try fun instead of function
<kba> Hm, that seems to work... Odd since List.map wants "function"
<Kakadu> kba: function is a keyword
<Kakadu> shortcut for (fun x -> match x with ....)
<kba> oh.. thanks
lolcathost has quit [Client Quit]
lolcathost has joined #ocaml
gnuvince has quit [Ping timeout: 252 seconds]
paolooo has joined #ocaml
ftrvxmtrx has joined #ocaml
avsm1 has quit [Quit: Leaving.]
paolooo has quit [Quit: Page closed]
mjonsson has joined #ocaml
avsm1 has joined #ocaml
lolcathost has quit [Ping timeout: 252 seconds]
lolcathost has joined #ocaml
lolcathost has quit [Client Quit]
lolcathost has joined #ocaml
paolooo has joined #ocaml
paolooo has quit [Client Quit]
hkBst has quit [Ping timeout: 244 seconds]
hkBst has joined #ocaml
hkBst has quit [Changing host]
hkBst has joined #ocaml
lolcathost is now known as Catnaroek
rixed_ has quit [Ping timeout: 240 seconds]
mjonsson has quit [Ping timeout: 248 seconds]
avsm1 has quit [Quit: Leaving.]
rixed has joined #ocaml
avsm has joined #ocaml
Neros has quit [Ping timeout: 245 seconds]
avsm has quit [Ping timeout: 246 seconds]
Neros has joined #ocaml
Catnaroek has quit [Ping timeout: 240 seconds]
smondet has joined #ocaml
Catnaroek has joined #ocaml
avsm has joined #ocaml
coldpizza72i has joined #ocaml
<xavierm02> is it possible to do a function
Kakadu has quit [Ping timeout: 252 seconds]
<xavierm02> that could take (a_1, a_2, ..., a_n) as argument for any n?
<xavierm02> and i yes, how do you read those?
<xavierm02> I know I could use a list
<xavierm02> but is it possible?
<xavierm02> could and should*
<Qrntz> yes, it's possible if the function takes a list
<Qrntz> what is your aim for that function though?
travisbrady has joined #ocaml
<hcarty> xavierm02: It is not possible for tuples
<Qrntz> ah, whoops, misread question
ontologiae has quit [Ping timeout: 260 seconds]
ontologiae has joined #ocaml
avsm1 has joined #ocaml
Catnaroek is now known as lolcathost
avsm has quit [Ping timeout: 252 seconds]
ontologiae has quit [Ping timeout: 252 seconds]
Arsenik has joined #ocaml
coldpizza72i has quit [Quit: coldpizza72i]
tane has joined #ocaml
BiDOrD has quit [Read error: Operation timed out]
BiDOrD has joined #ocaml
mcclurmc is now known as mcclurmc_away
tane has quit [Quit: Verlassend]
jpdeplaix has quit [Ping timeout: 240 seconds]
jpdeplaix has joined #ocaml
ansx has left #ocaml []
<xavierm02> ok ty
<xavierm02> I now have two other questions
<xavierm02> 1) Are there times when you actually need the fun or function keyword? Because from what I saw you can pour the arguments on the left of the = and not need it...
<xavierm02> 2) If I have a tuple of more than 2 elements, is there some way to access the items?
<orbitz> I use fun and function all the time
<Qrntz> me too
<hcarty> xavierm02: (1) You never need function, but it can be useful
<hcarty> xavierm02: (1) fun is commonly used for anonymous functions
<orbitz> conveneint shorthand
<xavierm02> yeah function = fun + match
travisbrady has quit [Quit: travisbrady]
<hcarty> xavierm02: (2) You can pattern match - let (a, b, c) = tuple_with_three
<Qrntz> my style involves using «let f x = function …» instead of «let f x y = match y with…»
<xavierm02> oh right
<Qrntz> it's more concise and isn't really less readable
<hcarty> xavierm02: If you only want one then let (_, b, _) = tuple_with_three
<xavierm02> ok ty :)
<orbitz> I do function a lot with Core Async. do_something () >>= function | .... ...
<hcarty> Qrntz: That can make it harder to read the function though
ankit9 has quit [Ping timeout: 240 seconds]
<hcarty> Qrntz: It's not as obvious at a glance how many arguments the function takes
<Qrntz> hcarty, didn't experience that — it looks very fit for recursive functions matching lists, for example
<Qrntz> but yes, your concern is true
<iZsh> also not using function forces you to give the variable a name, which can help understand what the function is expecting
<hcarty> iZsh: That too
<iZsh> i never use "function" for that last reason actually
TDJACR has quit [Remote host closed the connection]
travisbrady has joined #ocaml
<Qrntz> I wouldn't call that a valid reason for _never_ using it
<Qrntz> e. g. it can help remove excessive verbosity in anonymous functions that need to perform matching without losing said benefit (it is clear from the iterating code itself what the function expects as input)
ftrvxmtrx has quit [Quit: Leaving]
Neros has quit [Ping timeout: 260 seconds]
<Qrntz> compare «List.iter (fun x -> match x with …», «List.iter (function …»
<xavierm02> is there a way to say "this function takes two lists *of same length* as arguments"?
<Qrntz> xavierm02, that'd require dependent types, the most you can do at the moment is check for the length equality in the algorithm itself
Damien___ has joined #ocaml
<xavierm02> why "at the moment"?
<Qrntz> well, I have hopes for dependent types support in the future
<Qrntz> they're not backed up by much but a man can dream
<xavierm02> ok, ty :)
ankit9 has joined #ocaml
Damien___ has quit [Client Quit]
<xavierm02> let inferieur_lexico a b = match ( a, b ) with
<xavierm02> | ( [ ], _ ) -> true
<xavierm02> | ( _, [ ] ) -> false
<xavierm02> | ( _, _ ) -> false (* gona change *);;
mcclurmc_away is now known as mcclurmc
Damien___ has joined #ocaml
<xavierm02> why do I get a syntax error T.T
jamii has joined #ocaml
Damien___ has quit [Client Quit]
<xavierm02> wait
<Qrntz> xavierm02, compiles just fine here
<xavierm02> I get a syntax error at those lines
<xavierm02> but if i isolate them it works T.T
<xavierm02> okay never mind
<xavierm02> I just forgot ;; to end the previous phrase -.-
<nicoo> xavierm02: Are you sure the ;; isn't closing an earlier top-level let binding ?
<nicoo> Ok
<xavierm02> how did you guess O_O
<nicoo> Experience, I guess
fusillia has quit [Ping timeout: 260 seconds]
hkBst has quit [Quit: Konversation terminated!]
Damien_Guichard has joined #ocaml
<Damien_Guichard> salut, de SpiceGuid à Ptival.
f[x] has joined #ocaml
astertronistic has joined #ocaml
tac has joined #ocaml
avsm1 has quit [Quit: Leaving.]
|jbrown| has joined #ocaml
jbrown__ has quit [Ping timeout: 248 seconds]
Neros has joined #ocaml
<xavierm02> let f1 x = let f2 x = 2 * x in f2 x;;
<xavierm02> I'm quite sure I read something somewhere about a way to right it like this
andreypopp has quit [Quit: sleep]
<xavierm02> let f1 x = f2 x where f2 x = 2 * x;;
<xavierm02> is there something like that?
<Qrntz> OCaml does not support «where» syntax
<xavierm02> and in the first way of doing it, isn't f2 "created" everytime you call f1?
<Qrntz> IIRC, some version of Caml Light had it but I'm not too sure
<xavierm02> oh
<xavierm02> my book speaks of caml light
<Qrntz> perhaps you've read from a really old source
<xavierm02> that must be why
<xavierm02> yeah
<xavierm02> the book looks old :D
<Qrntz> that's it, then
<Qrntz> this syntax hasn't been supported in any version of OCaml
Yoric has quit [Ping timeout: 252 seconds]
<xavierm02> it says 1998 :o
<xavierm02> is caml light
<xavierm02> still used
<xavierm02> ?
<Qrntz> no, at least not in public
<Qrntz> some companies might have legacy code in it
<Qrntz> but it has been fully obsoleted by OCaml
<xavierm02> so now
<xavierm02> ocaml is the only alternative
<xavierm02> ?
<xavierm02> there aren't any other language
<xavierm02> kind of similar but not exactly?
<Qrntz> there are other ML-like languages, it's just so INRIA developed Caml Light before they started work on OCaml
<Qrntz> there are plenty of them, in fact, but most are obscure
<Qrntz> the widest-known might be ATS, at least I don't recall anything more popular with ML syntax
<Qrntz> oh, and of course Standard ML
avsm has joined #ocaml
<xavierm02> ok
avsm1 has joined #ocaml
<xavierm02> ty :)
<Qrntz> you're welcome
tac has quit [Ping timeout: 245 seconds]
avsm has quit [Ping timeout: 252 seconds]
<nicoo> xavierm02: The where syntax can be implemented using either camlp4 or camlp5
<nicoo> But it isn't in the core language
<nicoo> Qrntz: I wouldn't call ATS mainstream ;) (but it is fun)
<Qrntz> nicoo, did I? :-p
<nicoo> No
tac has joined #ocaml
larhat has quit [Read error: Connection reset by peer]
larhat has joined #ocaml
astertronistic has quit [Ping timeout: 240 seconds]
ankit9 has quit [Ping timeout: 276 seconds]
travisbrady has quit [Read error: Connection reset by peer]
travisbrady has joined #ocaml
benja has joined #ocaml
srcerer_ is now known as srcerer
ankit9 has joined #ocaml
<benja> hello everyone. just a simple question, i've never figured out (or can't remember of) how to combine multiple camlp4 syntax extension, is it possible at all ?
hcarty has quit [Ping timeout: 265 seconds]
avsm1 has quit [Read error: Connection reset by peer]
avsm has joined #ocaml
<orbitz> benja: just multiple -pp's i think
<xavierm02> let rec list_of_int n =
<xavierm02> if n < 10 then
<xavierm02> [ n ]
<xavierm02> else
<xavierm02> ( list_of_int ( n / 10 ) ) @ [ ( n mod 10 ) ]
<xavierm02> this is highly inefficient right?
<xavierm02> is it possible - without doing it iteratively - to improve it?
srcerer has quit [Quit: ChatZilla 0.9.88.2 [Firefox 15.0/20120824154833]]
<flux> xavierm02, the common trick: construct list backwards and then, in the last phase, reverse it
<benja> orbitz: ok thanks i'll try that. do you know if it should work with multiple ocamlfind -syntag argument too ? (or ocamlfind -package xxx.syntax)
<flux> that way you don't need to do @ many times, which makes this function O(n^2)
<flux> it's fast to do this: x::somelist
emias has quit [Ping timeout: 276 seconds]
<xavierm02> ok
<xavierm02> but if I had to implement reverse
<xavierm02> I would do this
<xavierm02> let rec reverse_list l = match l with
<xavierm02> | [ ] -> [ ]
<xavierm02> | head :: tail -> ( reverse_list tail ) @ [ head ]
<xavierm02> so i get the same problem :o
emias has joined #ocaml
<orbitz> that would be a terrible idea
<orbitz> Why wouldn't you do let rec rev = function
<xavierm02> i prefer having explicit arguments
<xavierm02> but is it possible to get a recursive reverse
<xavierm02> function that takes O(n)?
<orbitz> function or match doens't matter, but I hit the wrong key
jbrown__ has joined #ocaml
hcarty has joined #ocaml
<flux> xavierm02, if you needed to write a function that appended a list to another, but in reverse, how would you write that?
|jbrown| has quit [Ping timeout: 276 seconds]
<orbitz> let rev = List.fold_left ~f:(fun acc x -> x::acc) ~init:[]
<orbitz> one way
pangoafk is now known as pango
ankit9 has quit [Quit: Leaving]
<xavierm02> flux: i dont know >_<
<xavierm02> i would reverse one and then append it :/
<orbitz> xavierm02: look up a line?
avsm has quit [Quit: Leaving.]
<xavierm02> orbitz: but you use List.fold_left and I don't know how it is implemented :/
<xavierm02> I want to fully understand what's going on
<xavierm02> hm
<orbitz> impelemtngin fold is pretty trivial
<orbitz> let fold f init = function | [] -> acc | x::xs -> fold f (f init x) xs
sepp2k1 has joined #ocaml
<xavierm02> found it
sepp2k has quit [Ping timeout: 244 seconds]
tac is now known as tac-lunch
<Qrntz> xavierm02, you could probably consult your local stdlib sources, they're installed in /usr/lib/ocaml on most distros I've been using OCaml on
<xavierm02> ok so the trick is to keep the list you're building as an argument too
<orbitz> accumulators are a pretty standard pattern
<xavierm02> I'm kind of new here :)
mrm has joined #ocaml
tane has joined #ocaml
Xizor has joined #ocaml
avsm has joined #ocaml
travisbrady has quit [Quit: travisbrady]
elixey has joined #ocaml
f[x] has quit [Ping timeout: 255 seconds]
<xavierm02> Is there some way to get the arrows of the keyboard to work in the ocaml loop?
<xavierm02> I get ^[[A -.-
<xavierm02> or things like that
<Qrntz> rlwrap
<orbitz> rlwrap ocaml
avsm has quit [Quit: Leaving.]
lolcathost has quit [Quit: leaving]
f[x] has joined #ocaml
travisbrady has joined #ocaml
Cyanure has quit [Remote host closed the connection]
mrm has quit [Ping timeout: 276 seconds]
fraggle_ has quit [Read error: Connection reset by peer]
fraggle_ has joined #ocaml
avsm has joined #ocaml
andreypopp has joined #ocaml
lolcathost has joined #ocaml
emmanuelux has joined #ocaml
Kakadu has joined #ocaml
ocp has quit [Quit: Leaving.]
avsm1 has joined #ocaml
<xavierm02> ty :)
avsm has quit [Ping timeout: 252 seconds]
_andre has quit [Quit: leaving]
tac-lunch is now known as tac
jbrown__ is now known as |jbrown|
beckerb has quit [Quit: Konversation terminated!]
Yoric has joined #ocaml
larhat has quit [Quit: Leaving.]
<xavierm02> I need to represent cards
mcclurmc is now known as mcclurmc_away
<xavierm02> how can I define a type
<xavierm02> type card = Card of int
<xavierm02> while telling him I don't want to allow all ints?
<thizanne> you cannot
<xavierm02> O_O
<xavierm02> So I just get to do
<xavierm02> type card = c1 | c2 | ...
<xavierm02> ?
<xavierm02> Or can I throw an exception somewhere if I get an unexpected int?
<_habnabit> xavierm02, sure, you can throw an exception
tac_ has joined #ocaml
<_habnabit> xavierm02, but there's nothing to describe the range of possible values of a type something has
tac has quit [Ping timeout: 245 seconds]
netrino has joined #ocaml
ftrvxmtrx has joined #ocaml
travisbrady has quit [Quit: travisbrady]
tac_ is now known as tac-tics
tac-tics is now known as tac-nap
travisbrady has joined #ocaml
srcerer has joined #ocaml
<xavierm02> Is there really no way to get a finite number of ints?
<xavierm02> something like type int_of_range = 1 | 2 | 3 | 4 | 5 | 6 | 7;;
<xavierm02> anything
<xavierm02> just
<xavierm02> not having to have a type
<xavierm02> type int_of_range = i1 | i2 | i3;;
<xavierm02> and then a function that takes those and give a value
<flux> sorry, not possible
<|jbrown|> fake it with an object?
<flux> I mean, how would it work?
<_habnabit> xavierm02, i'm curious; what language's type system allows this?
<flux> should it statically reject this? (read_int () : int_of_range)
<flux> or should it raise an exception?
<flux> if the latter, then you can do it with private types
<xavierm02> hm
<xavierm02> I'm not familiar with types systems
<xavierm02> not good ones anyway
<flux> I suppose ATS might be able to do that
<xavierm02> I've done a lot of JavaScript and a bit of Java
<Kakadu> It looks like dependent types
<_habnabit> I was thinking ATS, yeah
<xavierm02> :/
<flux> you would need to prove the compiler that the integer is within the desired range
<_habnabit> xavierm02, neither of those can represent this with the type system alone
<flux> for example (not real ATS, I don't know ATS): let a = random () in assert (a >= 0 && a < 10); (a : int_of_range) (* would succeed *)
<flux> it would be nice to have, but it would also probably be quite complicated
<xavierm02> ok
<xavierm02> so I need to just take an int
<flux> one would need to prove that to the compiler after every arithmetic operation one does with the value..
<xavierm02> and filter ints I don't want in every function I make that uses this type
<_habnabit> xavierm02, your card_of_int function can verify the range
<xavierm02> can we do "local" types?
<xavierm02> so that the only way to get an object of type card is to use a function card_of_int?
<_habnabit> sure
<xavierm02> how do you do that?
<flux> with ocaml module system you can do this: module Card : sig type t = private Card of int val card_of_int : int -> t end = struct type t = Card of int let card_of_int x = assert (x >= 0 ...); Card x end
<_habnabit> type card = int;; exception Invalid_card of int;; let card_of_int n = if n > 13 || n < 1 then raise Invalid_card n; n
<_habnabit> er, raise (Invalid_card n)
<flux> _habnabit, well, you would need to hide the card-type somehow
<_habnabit> flux, i'm talking about in the .ml, not the .mli
<flux> so my example gives one way of doing that
<flux> _habnabit, that code works in .ml :)
<_habnabit> yeah yeah
ontologiae has joined #ocaml
<xavierm02> you just lost me
<xavierm02> >_<
<flux> xavierm02, usually this kind of data hiding (only part part of code can see what's inside it or only one part of code can create it) is done only when you have multiple modules, ie. multiple files
<Damien_Guichard> bonsoir ontologiae,
chturne has joined #ocaml
<Damien_Guichard> c'est toi qui m'avais posé des questions sur ERic ?
travisbrady has quit [Quit: travisbrady]
travisbrady has joined #ocaml
<Damien_Guichard> tu as trouvé ton bonheur avec RACE ?
lolcathost has quit [Ping timeout: 260 seconds]
lolcathost has joined #ocaml
<thelema> Damien_Guichard: #ocaml_fr
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
chturne has quit [Ping timeout: 260 seconds]
larhat has joined #ocaml
answer_42 has quit [Quit: WeeChat 0.3.9]
hto has quit [Read error: Connection reset by peer]
hto has joined #ocaml
f[x] has quit [Quit: Leaving]
<Ptival> #ocaml-fr actually :p
Submarine has quit [Quit: Leaving]
<Damien_Guichard> Hello Ptival :)
<Ptival> hello
<Ptival> SpiceGuid, amirite?
<Damien_Guichard> SpiceGuid = Damien_Guichard
<Damien_Guichard> Ptival, what do you think about my caml-list subjet proposal ? https://groups.google.com/forum/?fromgroups=#!topic/fa.caml/1_XLpgIht_8
<Damien_Guichard> You can answer there if preferred http://progmod.org/forum/sujet/268/idees-de-tipe/?page=3
<Ptival> yeah I saw both the message and the forum post already
<Ptival> didn't take the time to read it though
mcclurmc_away is now known as mcclurmc
<Damien_Guichard> Thanks anyway.
lolcathost has quit [Ping timeout: 264 seconds]
lolcathost has joined #ocaml
Arsenik has quit [Ping timeout: 268 seconds]
Yoric has quit [Ping timeout: 252 seconds]
Yoric has joined #ocaml
tane has quit [Quit: Verlassend]
Arsenik has joined #ocaml
thomasga has quit [Ping timeout: 248 seconds]
thomasga has joined #ocaml
Yoric has quit [Ping timeout: 246 seconds]
<pippijn> I think lwt might be overkill: http://paste.xinu.at/wEwgx/
Kakadu has quit [Quit: Konversation terminated!]
Yoric has joined #ocaml
<thelema> pippijn: only .13% of cpu time itself
<pippijn> oh
<pippijn> thelema: how can I find timings?
<pippijn> ah
<pippijn> the "self" part
<thelema> 13% is <cycle 1>, whatever that is, 15% is mark_slice, 13.5% is caml_page_table_lookup, 5.26% is caml_modify, so GC is significant
<thelema> looks like most of your work is being done in the GC - maybe enlarge your minor heap?
<thelema> <cycle 1> I'm guessing is a collection of functions that call each other; that's only using <10% of CPU
<thelema> I bet that's your main program.
avsm1 has quit [Quit: Leaving.]
avsm has joined #ocaml
<pippijn> thelema: I guess so..
<pippijn> thelema: I see nothing but GC in the call graph
cdidd has quit [Remote host closed the connection]
<thelema> what are the functions in cycle 1
cdidd has joined #ocaml
<thelema> ok, just lwt
Yoric has quit [Ping timeout: 246 seconds]
<pippijn> gprof: http://paste.xinu.at/mmf/
<pippijn> gprof seems pretty useless
<pippijn> maybe I need to let it run for a longer period
<thelema> pippijn: looks like you're profiling a very short execution
<pippijn> it's running now
avsm has quit [Quit: Leaving.]
tac-nap is now known as tac-tics
ontologiae has quit [Ping timeout: 265 seconds]
tac-tics has quit [Quit: Page closed]
snarkyboojum has quit [Ping timeout: 240 seconds]
snarkyboojum has joined #ocaml
turingtest has joined #ocaml
Arsenik has quit [Remote host closed the connection]
<pippijn> thelema: http://paste.xinu.at/0F6/
<pippijn> GC time is gone
Xizor has quit [Remote host closed the connection]
zzz_ has joined #ocaml
smondet has quit [Ping timeout: 260 seconds]
sgnb has quit [Ping timeout: 244 seconds]
mjonsson has joined #ocaml
<pippijn> I disabled recording backtrace
Damien_Guichard has quit [Quit: Page closed]
emmanuelux has quit [Quit: emmanuelux]
andreypopp has quit [Quit: sleep]
travisbrady has quit [Quit: travisbrady]
emmanuelux has joined #ocaml
thomasga1 has joined #ocaml
thomasga has quit [Read error: Connection reset by peer]
xavierm02 has quit [Quit: Leaving]
lolcathost has quit [Quit: brb]
lolcathost has joined #ocaml