<Kakadu>
and is says that Package `bitstring' not found
<Kakadu>
searching bitstring in aptitude gives only i386 versions of libbitstring-ocaml(-dev)
<Kakadu>
pffff
<Kakadu>
fixed
<Kakadu>
after `aptitude update` I can see needed versions
<ansx_>
is there any plan to make ocaml support multi-threading, ever?
<Kakadu>
ansx_: yeah
<flux>
well, there is ocaml4multicore, but for some reason these kind of projects don't seem to have a lot of staying power.
paolooo has joined #ocaml
<ansx_>
Kakadu: "yeah" ? which means?
<ansx_>
because it seems that most code in ocaml is not reentrant
<rixed>
ansx_: OCaml already support multithreading. But not concurrent threads.
<Kakadu>
ansx_: ocp have mentioned that they work on it
<rixed>
ansx_: or more exactly, there can be only one OCaml GC concurrently. you can have concurrent threads in C along with a thread in Ocaml.
<ansx_>
yeah so Ocaml doesn't support threading...
<jbrown__>
ansx_: why do you want threading? :-)
<jbrown__>
programming's hard enough as it is!
<jbrown__>
heh
<ker2x>
^^
<ansx_>
saying that a langage supports threading as long as you don't use it but a C extension instead is pretty much a religious preach
<ansx_>
jbrown__: because I we have many cores available in any recent computer
<ansx_>
-I
<ker2x>
well, erlang, fortran, have super-easy multithreading capabilities
<ker2x>
almost seamless
<ansx_>
so doing stuff on only one core at a given time is like bleeding money
<ansx_>
at least F# does support threads
mjonsson has joined #ocaml
<ker2x>
i tought there was jocaml or something like that ?
<ker2x>
JoCaml is Objective Caml plus (&) the join calculus, that is, OCaml extended for concurrent and distributed programming.
<companion_cube>
ansx_: you can do multi-process if you really need
<rixed>
ansx_: no there are several purpose of threading: having several threads to simplify a program (OCaml support this) and having two simultaneous code path (Ocaml does not support this)
<rixed>
ansx_: you can do multiprograming with OCaml on your many cores, just use different processes (ie. different GC).
<rixed>
ansx_: look for msg passing or distributed map for a hint
joewilliams has quit [Remote host closed the connection]
lopex has quit [Read error: Connection reset by peer]
bobry has quit [Remote host closed the connection]
lopex has joined #ocaml
OCamlGuy has joined #ocaml
joewilliams has joined #ocaml
mjonsson has quit [Remote host closed the connection]
bddn has quit [Ping timeout: 244 seconds]
<ansx_>
how are you supposed to interface OCaml with syscalls that may return values greater than max_int?
<adrien>
Int64?
<ansx_>
but then you can't use any of the "readable" arithmetics like "a + b" right?
<ansx_>
you would need to use Int64.add a b
<f[x]>
yes
<adrien>
you can still do local redefining
smondet has joined #ocaml
<ker2x>
can someone tell me (basically) what it means ? i don't understand this syntax : let binop_precedence:(char, int) Hashtbl.t = Hashtbl.create 10
<ker2x>
it create a hastable of char/int ?
<thizanne>
no
<thizanne>
I guess it creates a hashtable with char keys and int values
<thizanne>
do you use batteries ?
<rixed>
is it the ":" that troubles you ?
<ker2x>
yup
<jbrown__>
it's just like "let x:int = 5"
<rixed>
binop_precedence:type is a type indication : binop_precedence is going to be of type "type".
<rixed>
type inference makes these indication mostly useless, except to find out why the compiler doesn't infer the same types as you do :)
<rixed>
"(char, int) Hashtbl.t" is the type of hashtables from char to int (char keys, int values)
<ker2x>
ok "Hashtbl.t" is a type. so "binop_precedence" is a variable of type "Hashtbl.t"
<rixed>
in general, hashtables have type ('a, 'b) Hashtbl.t
<rixed>
"Hashtbl.t" is a type with two parameters, here char and int.
<rixed>
If you know C++ it's like template parameters.
<ker2x>
i think i understood it enough to keep reading the code. thank you :))
OCamlGuy has quit [Quit: OCamlGuy]
Neros has joined #ocaml
Neros has quit [Read error: Operation timed out]
<ker2x>
agh
bobry has joined #ocaml
<ker2x>
the type indication is "(char, int) Hashtbl.t", not just "(char, int)"
<ker2x>
it like "int list" (for a list of int)
<ker2x>
correct ?
Neros has joined #ocaml
Vinnipeg has joined #ocaml
Yoric has quit [Remote host closed the connection]
Yoric has joined #ocaml
<rixed>
ker2x: correct
<Qrntz>
ker2x, the general type for a list of values, «'a list», has one type parameter «'a»
<Qrntz>
the general type for a hash table, «('a, 'b) Hashtbl.t», has two type parameters «'a» and «'b»
<ker2x>
got it, thank you. it was mostly a syntax problem. 1) i forgot that "a:b" is to tell that a is of type b. 2) i was used to see ( ) around type indication like a:(b). 3) i forgot that a type could be not just "b" but "b something".
<ker2x>
like int list :)
<ker2x>
not that hard actually, using some help :)
<ker2x>
thank you again
<Qrntz>
also, remember that there's a difference between e. g. «('a, b')» and «'a * 'b» in type declarations
<Qrntz>
the former is a 2-tuple of type parameters which are 'a and 'b, the latter is the actual type of a 2-tuple value of types 'a and 'b
<thizanne>
(and this definitely sucks)
* Qrntz
shrugs
<ker2x>
nope, i don't understand :(
<ker2x>
i didn't finished all tutorial yet. i'll see that later, hopefully.
bddn has joined #ocaml
andreypopp has quit [Quit: sleep]
<thizanne>
ker2x: ('a, 'b) Hashtbl.t means hash table from 'a to 'b
<thizanne>
('a * 'b) list means list of tuples, these tuples being couples of 'a and 'b
<thizanne>
in haskell, ('a, 'b) t would be something like T a b
<thizanne>
and ('a * 'b) t would be T (a, b)
andreypopp has joined #ocaml
andreypopp has quit [Client Quit]
<thelema_>
beginner42: I don't think zarith is a bit-vector library, but the integer 0 may suffice for your purposes.
Neros has quit [Ping timeout: 268 seconds]
hkBst has quit [Ping timeout: 272 seconds]
maufred has quit [Ping timeout: 245 seconds]
maufred has joined #ocaml
hkBst has joined #ocaml
hkBst has quit [Changing host]
hkBst has joined #ocaml
Neros has joined #ocaml
Neros_ has joined #ocaml
Neros has quit [Ping timeout: 276 seconds]
jamii has joined #ocaml
tac has joined #ocaml
OCamlGuy has joined #ocaml
avsm has joined #ocaml
Vinnipeg has quit [Quit: Leaving.]
tufisi has joined #ocaml
Neros_ has quit [Ping timeout: 268 seconds]
jbrown__ is now known as |jbrown|
<Ptivalien>
python has lambdas
<Ptivalien>
oh well
<Ptivalien>
should have scrolled down
<companion_cube>
python has poor lambdas
<companion_cube>
I think it's been said :)
ftrvxmtrx has quit [Quit: Leaving]
<_habnabit>
nah, its lambdas are fine
<_habnabit>
if you want to complain about something, complain that python has a separation between expressions and statements
<_habnabit>
lambdas are orthogonal to that
<companion_cube>
it's not orthogonal, since lambdqas are limited to expressions and most python code is statements
<companion_cube>
that's this distiction that makes lambdas so useless
<companion_cube>
distinction*
<_habnabit>
you're looking at it the wrong way
<companion_cube>
(this and the scoping by reference)
<_habnabit>
if python only had expressions, you could fit as many 'statements' in a lambda as you wanted
<_habnabit>
'scoping by reference' what
<companion_cube>
closures in python capture references to values rather than values
<_habnabit>
that's called 'late-binding'
<companion_cube>
ok, I thought late binding was used for virtual method resolution
<companion_cube>
so anyway, that is an ugly semantic
tac has quit [Ping timeout: 245 seconds]
<_habnabit>
fwiw you can define a function anywhere in python; using a named function instead doesn't really cause issues and python has different idioms where other languages usually have inline anonymous functions or whatever
<companion_cube>
yep; that just does not fix the scoping issue, but i agree, that's better than nothing
<_habnabit>
no, i'm just saying that people who yell about "python's lambdas are crippled!!" just don't realize that python has idioms that make that irrelevant
mcclurmc_away has joined #ocaml
<companion_cube>
it doesn't change anything about lambda themselves
andreypopp has joined #ocaml
<_habnabit>
okay??
Kakadu has quit [Quit: Konversation terminated!]
<companion_cube>
you're just saying "anonymous functions suck, but you can use named functions instead" in reply to "python lacks good anonymous functions"
<_habnabit>
i'm not saying they suck; i'm saying that in places where people typically reach for 'anonymous functions' in other languages, python has different idioms which don't require anonymous functions
andreypopp has quit [Client Quit]
<companion_cube>
yes, idioms that are not very functional :)
hkBst has quit [Quit: Konversation terminated!]
<_habnabit>
you know 'functional programming' doesn't mean 'you write a lot of functions', right?
<companion_cube>
it more of an implication to me...
OCamlGuy has quit [Quit: OCamlGuy]
<companion_cube>
what kind of idioms are you thinking about, actually?
andreypopp has joined #ocaml
tufisi has quit [Read error: Operation timed out]
<_habnabit>
decorator syntax on named functions mainly
tufisi has joined #ocaml
<companion_cube>
that's more like aspect-oriented...
avsm has quit [Quit: Leaving.]
<pippijn>
how can I find out whether ocaml found a function to be tail recursive?
<thelema_>
_habnabit: c-- is an intermediate representation in native compilation of OCaml
<thelema_>
_habnabit: thus -dcmm
<_habnabit>
oh, I see
mcclurmc_away is now known as mcclurmc
Yoric has quit [Remote host closed the connection]
Yoric has joined #ocaml
Kakadu has joined #ocaml
Submarine has joined #ocaml
ftrvxmtrx has joined #ocaml
cdidd has quit [*.net *.split]
cdidd has joined #ocaml
Vinnipeg has quit [Quit: Leaving.]
GnomeStoleMyBike has quit [Ping timeout: 256 seconds]
djcoin has quit [Quit: WeeChat 0.3.9]
tizoc has quit [Ping timeout: 246 seconds]
tizoc has joined #ocaml
djcoin has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.9]
paolooo has quit [Quit: Page closed]
mcclurmc is now known as mcclurmc_away
cdidd has quit [Read error: Operation timed out]
<madroach>
hi, I have a problem with typing mutually recursive classes: http://pastebin.com/RZ7TQLyV This fails with "universal type variable 'a cannot be generalized: it escapes its scope".
<madroach>
But when defining the classes without "and", but with two separate "class" statements it compiles fine. Why?
tac has joined #ocaml
<thelema_>
interesting question... foo is a method that takes a value of type #a and calls #id on it.
<thelema_>
is there a good reason to have the type annotation? why not just "method foo s = s#id"?
<madroach>
thelema_: this doesn't work either: The method foo has type (< id : 'a; .. > as 'b) -> 'a where 'b is unbound.
<thelema_>
ah, yes.
sepp2k1 has joined #ocaml
<thelema_>
you do need the 'a. to force polymorphism. hmm, I'm not sure why typing is going a bit weird in the recursive case.
<thelema_>
I imagine there's some obscure way to break type-safety through this, but I can't think of what it would be.