<mfp>
the graphical illustrations are very telling
vpalle has joined #ocaml
sporkmonger has quit []
itouch has joined #ocaml
<Asmadeus>
They explain how the basics work on their homepage here, http://www.astree.ens.fr - seems like a really good work
<Asmadeus>
I wonder if they've proven that a program ASTRÉE accepts really won't have any runtime error
Eridius has joined #ocaml
<Eridius>
hey guys, why won't this work: let rec f a b () = (a, f (a+b) (succ b))
<Eridius>
I'm trying to get a function that returns a tuple, of which the second element is a function that returns a tuple, of which the second element...
<Eridius>
basically, I'm trying to make a stream
<Eridius>
(without using camlp4's stream syntax)
<Asmadeus>
That's because the type f return never terminates
<Eridius>
is there any way to solve this without introducing a new record type to replace the tuple?
bluestorm has joined #ocaml
seafood has quit [Read error: 54 (Connection reset by peer)]
seafood has joined #ocaml
<Asmadeus>
I don't think so. I'd use a type that look alot like a list Thing (int * next) or End
<Eridius>
end? this is an infinite list
<flux>
I believe you can compile it with -rectypes and it compiles, but it's not really a good solution
<Eridius>
playing around a bit, type stream = { elt : int; f : unit -> stream }; works, I'm just annoyed that I can't generalize this so elt can be 'a
<bluestorm>
hm
<flux>
otherwise you can just do type t = T of (int * (unit -> t))
<Asmadeus>
Well, the thing is 'a is a type that'd be infinite if it's expanded (sorry, didn't read the stream part correctly :P)
<flux>
isn't the type he wants analoguous to type t = int * (unit -> t) ?
<bluestorm>
well type 'a stream = { elt : 'a; f : unit -> 'a stream } works, doesn't it ?
<Eridius>
ooh, I didn't realize you could parameterize records
<flux>
you can parametrize all kinds of types
<bluestorm>
type 'a stream = Stream of 'a * unit -> 'a stream should also work
<Eridius>
is there a reason you guys are suggesting variants instead of records? is it a stylistic thing, or what?
<bluestorm>
(and as flux said, you could remove the variant tag with -rectypes if you really want to)
<bluestorm>
hm
<bluestorm>
in that case i don't think there is an obvious decision between variant and records
<bluestorm>
Eridius: it is good practice to use records when you have lot of fields and/or you need meaningful names
<Eridius>
and yet you both reached for variant first. Is it more idiomatic to use variants?
<Eridius>
ah
<bluestorm>
in that case however, records are not a bad choice because they highlight the "product" nature of your infinite type
<Eridius>
also, I can make the record mutable and then make a 'next' function that pulls the element out and then mutates the record to contain the next element
<bluestorm>
hm
<bluestorm>
why don't you use Streams ?
<bluestorm>
there is a decent basis library, decent syntaxic sugar and a more sophisticated third-party library compatible with caml streams
<Eridius>
mostly because at the time I wanted this I was still executing my code with `ocaml foo.ml` and didn't want to have to bother with setting up the Makefile to properly compile stuff with all the right options
<bluestorm>
if you want something destructive it's a good choice
<Eridius>
of course since that point I've already converted over to using a Makefile and compiling stuff with ocamlopt
<bluestorm>
Eridius: you can use streams without the sugar if you want
<Eridius>
hrm, Stream.from only hands the stream count to the function. So if I need to keep extra state (like in my example where I need access to the previous value) I need to have a ref in my closure? ugh
<bluestorm>
you
<bluestorm>
you want an unfold ?
<Eridius>
huh?
<bluestorm>
unfold : ('a -> 'a * 'b option) -> 'a -> 'a * 'b list
<bluestorm>
hmm
<bluestorm>
failed
<Eridius>
I'm not sure I follow
<bluestorm>
the haskell list unfold is ('b -> ('a * 'b) option) -> 'b -> 'a list
<bluestorm>
it's a general operation to build data structures by iterations an operation on a value
<Eridius>
so what, unfold passes 'b to the function, then as long as it returns a Some ('a * 'b) back, it pulls the 'a off and passes the 'b back in?
<bluestorm>
yes
<Eridius>
ah
<bluestorm>
Sdlflow has a val seq : 'a -> ('a -> 'a) -> ('a -> bool) -> 'a flow wich is quite similar
<Eridius>
in my problem I wanted to generate an infinite list of so-called "triangle numbers"
* Eridius
is solving the projecteuler.net problems in OCaml
<Eridius>
problem 12 defines a "triangle number" then asks what's the first triangle number to have over 500 divisors
<bluestorm>
are triangle numbers the n(n+1)/2 folks ?
<Eridius>
so I needed to be able to processes each triangle number, then if it didn't have enough divisors move on to the next
<bluestorm>
(and how is the last number you checked useful for the next one ?)
<Eridius>
err, probably. It defined them slightly differently, and I didn't care to do the math to resolve it to a simple expression :P
Chaide has joined #ocaml
<bluestorm>
(what's your definition ?)
<Eridius>
it defined them as the 7th number is 1 + 2 + 3 + 4 + 5 + 6 + 7, etc
<bluestorm>
ok
<Eridius>
so my definition was to take the previous triangle number and add the current index
<bluestorm>
so it's 7*8/2
<bluestorm>
(classic and quite basic calculus formula, i guess)
Ched- has quit [Read error: 104 (Connection reset by peer)]
<Eridius>
anyway, I ended up just creating each new number and checking divisors in the same loop, instead of what I wanted which was to separate the definition of triangle numbers from the processing of them
<bluestorm>
well seq seems adequate
<Eridius>
well, the step function for seq would have to keep state
<bluestorm>
seq (1, 1) (fun (i, n) -> let i' = i + 1 in (i', n + i')) (fun _ -> false)
<bluestorm>
yes, you have an additional index
<bluestorm>
but is that a problem ?
<Eridius>
I suppose not
<bluestorm>
hm
Chaide has quit [Remote closed the connection]
<bluestorm>
there might be something even more accurate in Extlib
<Eridius>
I suppose I probably should install some of these standard third-party libraries..
<bluestorm>
hum
<bluestorm>
isn't :p
<bluestorm>
Eridius: well you could also define your unfold
* Eridius
was rather surprised to find ocaml doesn't seem to expose any way to pretty-print values the way the top-level interpreter does
<Eridius>
well, unfold as you described it produces a finite list out of a function and an initial value
<bluestorm>
yeah, that's a shame
<Eridius>
I wanted an infinite list
<bluestorm>
let rec unfold next a = [< a; unfold next (f a) >]
<bluestorm>
if you have a map (Sdlflow does), you can even (map snd) to ditch the index out
<bluestorm>
however, keeping it might even be a good idea on the long run for, say, debugging purposes
<bluestorm>
Eridius: are they considering prime divisors, or any divisors ?
<Eridius>
any divisors
* Eridius
has a function that generates divisors by taking the prime factors and then combining them
<bluestorm>
overkill
sporkmonger has joined #ocaml
<Eridius>
why? I need divisors in several other problems that use really large numbers
<bluestorm>
ah
<Eridius>
I started out with the brain-dead approach to finding divisors and switched to this when the first way was too slow
<bluestorm>
well with the n(n+1)/2 formula you could maybe do clever things (compute n divisors, n+1 divisors, and mix them)
<bluestorm>
wich can be interesting because then you're working on the square root of the number
<Eridius>
ya know, I'm happy with my approach. Including compilation, running the whole thing takes only 7.8 seconds to spit out 76576500
besiria has joined #ocaml
seafood has quit []
Ched- has joined #ocaml
Ched- has quit [Remote closed the connection]
Ched- has joined #ocaml
bluestorm has quit ["Leaving"]
Kerjean has joined #ocaml
<Kerjean>
why is there no posix semaphore used instead of caml_{enter/leave}_blocking section, which use a volatile int ?
<flux>
I suspect speed is one concern
<Kerjean>
flux ok. I added one because i have a program with parts in ocaml and parts in C which are heavily multithreaded and access to ocaml. So two threads in C are able to access the ocaml interpreter at the same time, even if i use the enter/leave_blocking_section()
besiria has quit [Read error: 104 (Connection reset by peer)]
<Kerjean>
anyway i still find a pity that the concurrent GC formally verified of caml is not used anymore in ocaml
<Kerjean>
if not for performance, it is a good toy for research !
<Toonto_del_alma>
Kerjean, the GC is not ready for a multithreaded environment
<Kerjean>
Toonto_del_alma one guy did a PhD on a multithreaded GC, formally verified . Leslie Lamport was member of the jury....
<Toonto_del_alma>
by example, the Boehm's GC use parallel processing in the mark stage and non-parallel in the sweep stage, it's still a stop-world class.
<Kerjean>
i know you can not parallelize all tasks of a gc
<flux>
toonto_del_alma, but it's better than non-concurrent, as it can scale betetr
<Toonto_del_alma>
its scalability is partial, only for mark phase
<flux>
I suppose trees are better for concurrent gc than lists, for example?
munga__ has joined #ocaml
munga__ has quit [Remote closed the connection]
<Toonto_del_alma>
the current problems of GCs of nowadays are we're fighting with bigger heaps of the order of gibibytes, multithreading and parallelism on multicores processors.
<Kerjean>
Damien Doligez is the guy whom i spoke about
<Toonto_del_alma>
many GCs are inefficient for this magnitude
vpalle has quit [Read error: 110 (Connection timed out)]
marmotine has joined #ocaml
asmanur has quit [Remote closed the connection]
asmanur has joined #ocaml
coucou747 has joined #ocaml
bzzbzz has joined #ocaml
<Camarade_Tux>
I've profiled an application (which has a function defined in a C file) and compare_val ranks high in the time-eaters, anyone knows when it is called (instead of caml_compare) ?
<gildor>
Camarade_Tux: what are you comparing?
Myoma has joined #ocaml
<gildor>
Camarade_Tux: have you some snippets of your program around
<Camarade_Tux>
I was writing a description but yes, just give me a minute
<mfp>
Camarade_Tux: caml_compare (Pervasives.compare) calls compare_val; so do (<), (<=), etc.
<mfp>
Camarade_Tux: iow. you have many "indirect" structural comparisons via (>) and friends
<Camarade_Tux>
mfp, both compare_val and caml_compare take a lot of time, what I wonder is why _both_, the C part only uses '=='
<Camarade_Tux>
(NB : I'm aware the C part is not really well written but I've just written it)
filp has quit ["Bye"]
<mfp>
I can't see a single polymorphic comparison there
<mfp>
is it somewhere else in your code?
<gildor>
Camarade_Tux: List.assoc
<mfp>
it's commented out
<gildor>
Camarade_Tux: line 33, it doesn't seem to be in comment
<tsuyoshi>
line 4 uses =, doesn't it?
<mfp>
ah, missed that one (just saw l22)
<mfp>
tsuyoshi: monomorphically, over chars
<Camarade_Tux>
substring_matches ss and ss_m_s_rc j ss i s are in fact not called, they're only called for find which I was not profiling
<mfp>
ah match_length_loop
<tsuyoshi>
does the compiler optimize monomorphic comparisons?
<mfp>
nope not even that, since i + 1 implies i : int
asmanur has quit [Read error: 110 (Connection timed out)]
<Camarade_Tux>
gildor, thanks for the answer, using an association list is clearly not the best solution but it was the quickest to implement ;)
<mfp>
tsuyoshi: yup
<tsuyoshi>
hrm that assoc is not going to be optimized for sure though
<Camarade_Tux>
btw, if you're wondering why I defined match_length_loop outside of match_length, it's because it gave a performance improvement (a few percents)
<tsuyoshi>
that must be it
<mfp>
for some basic types, that is
<gildor>
Camarade_Tux: I recommend: SetChar = Set.Make(struct type t = char let compare a b = (Char.code a) - (Char.code b) end);;
<gildor>
or MapChar depending on what you want
authentic has joined #ocaml
<gildor>
you won't inline compare function but you will save a lot of time over List.assoc
<mfp>
ocamlopt is not smart enough to monomorphize let set = Array.unsafe_set :-|
<Camarade_Tux>
well, right now I'm doing in-place modifications ; I have another version that is purely functionnal though, it's already using Map also
<mfp>
I realized that when I did module Array = struct include Array let set = Array.unsafe_set let get = Array.unsafe_get end to turn .( ) into unsafe ops within some scope (without -unsafe), à la pa_do
<tsuyoshi>
what if you use the external syntax instead of let
<tsuyoshi>
it should be able to figure that out, no?
<mfp>
hmm let's see
<tsuyoshi>
gah.. I have to get up early tomorrow
<tsuyoshi>
somehow I let this girl talk me into doing something other than programming
* tsuyoshi
heads for bed
<Eridius>
bed? it's 8:45am! :P
<mfp>
tsuyoshi: yeah external works
<Camarade_Tux>
hum, 5:45pm ? ;)
<mfp>
given that array.mli declares external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set", I think the compiler should be able to monomorphize let set = Array.unsafe_set, though :-/
<Eridius>
haha, if I take my non-terminating type example from before and explicitly declare the type to be what it claims the expression is, it expands the type one step further and complains again
bluestorm has joined #ocaml
<Camarade_Tux>
btw, if anyone has suggestions on how to reduce the memory usage of my code (the caml part), I'll be really happy to hear them ;)
<bluestorm>
(code ?)
<Camarade_Tux>
that one : http://ocaml.nopaste.syscp.org/283 (don't pay attention to the association list, I'll change it ;) ), I posted it before you connect
<bluestorm>
hm
<bluestorm>
patricia tree ?
<bluestorm>
(i'm not sure of the name, those things with the suffixes and the like)
<Camarade_Tux>
yup, some call it radix tree or crit-something tree, that version is in-place but I also have another one that is functionnal
coucou747 has quit ["bye ca veut dire tchao en anglais"]
<bluestorm>
how heavy is your indexed data in memory ?
<bluestorm>
(i mean the 'a type)
<bluestorm>
(i suppose you want it memory-efficient *and* cpu-efficient ?)
<Camarade_Tux>
currently I'm storing a string, the same as the one that indexes, it provides some checks wrt correctness
<Camarade_Tux>
and not necessarily cpu-efficient but not too cpu-inefficient ;)
<gildor>
Camarade_Tux: your List.assoc is not sorted...
<bluestorm>
gildor: he said he would use another data structure
<gildor>
Camarade_Tux: I think that he does a lot of compare due to the 'unsorted' nature of the list
<gildor>
he -> it (i mean the code does a lot of compare)
<Camarade_Tux>
I'm also operating over big sets of data (the only way to benchmark), lists should be small (I don't currently have stats unfortunately)
<gildor>
list should be less than 256 elements indeed ;-)
<gildor>
but even at this scale, you could win time with sorted datastructure
<Camarade_Tux>
but would sorting a list really help ?
<gildor>
(lst_add seems to compare every element of the list)
<bluestorm>
the problem with sorting the list is that your insertion is still O(n)
<gildor>
nope, sorting a caml list would not help
<gildor>
but you have 2 solutions:
asmanur has joined #ocaml
<gildor>
either use Set/Map as recommended above
<gildor>
or if you use C part, use a bit field
<Camarade_Tux>
lst_add should return as soon as it finds a corresponding index
<bluestorm>
(do you plan to use insertion or read most ?)
<gildor>
for 256 values you will need 4 or 8 integers
<gildor>
(with bitfields you will earn A LOT of time)
<gildor>
bluestorm: why not ;-)
<bluestorm>
Camarade_Tux: do you have a restricted alphabet ?
<gildor>
Camarade_Tux: i think alphabet = char
<bluestorm>
i mean if you only sort a-z letters, it can be a big win
<bluestorm>
s/sort/use/
<Camarade_Tux>
my test currently use ascii but it should handle unicode/latin* too
<bluestorm>
ewww
<bluestorm>
unicode ?
<Camarade_Tux>
it should work ;)
<gildor>
Camarade_Tux: with unicode you cannot use BitSet, you should directly go to Map/SEt
<bluestorm>
gildor: i think, if there is a few child per node, a Map/Set would be memory costy and not so interesting for the performances wrt. assoc lists
<Camarade_Tux>
I'll probably head to an unbalanced binary search tree
<bluestorm>
(when n = 5, log n is not _that_ better)
<gildor>
bluestorm: indeed
<flux>
how about a b-tree for the characters?
<bluestorm>
about memory efficiency, i was thinking about sharing considerations
<bluestorm>
it seems that in the present code (String.sub) and all, new strings are allocated for each node
<bluestorm>
while a lot of them should be structurally equal
<bluestorm>
(because the common case will be to have one-char string per node, right ?)
<flux>
one could try how the rope library would work with that
<bluestorm>
so it should be possible to improve sharing, maybe by storing a table of unique common strings
<bluestorm>
(say you can have a hashtabl table of all the length-1 and length-2 strings you've used so far, it could be interesting if you share them a lot)
<Camarade_Tux>
in fact no : it's several chars per node, the reason I index with chars is because of performance (memory and cpu), I haven't proven it but I think it is better (I know, it's a bit weird)
<bluestorm>
hm
<Camarade_Tux>
also, I've tried a rope library, performance was worse (but the real one which suffered is Map, 700% slower)
<bluestorm>
well for example if you have the words, say, "moo", "moody" and "moods"
<bluestorm>
moody and moods will be on a "d"-node, right ?
<bluestorm>
(or you store the whole prefix ?)
<Camarade_Tux>
no, only the added part, so yes moody and moods will be as you say
<Camarade_Tux>
(sorry, I'm slow to type, I don't have my glasses on ;) )
Kerjean has quit ["Vision[0.8.5-0418]: i've been blurred!"]
<Camarade_Tux>
ok, be back in 20 minutes
<bluestorm>
Camarade_Tux: i assume those 1-length shared strings might be the common case
<Camarade_Tux>
usually you share more, 1-length mostly happen at the end
<bluestorm>
well
<bluestorm>
if you have say 40K words and 10K nodes with a 1-length prefix
<bluestorm>
you can still save 10K / alphabet-length by sharing
<bluestorm>
even in the longer prefix, it is likely that some of them (syllables) occur quite frequently
<Camarade_Tux>
sharing is really important, for instance, on 27MB of string, the patricia tree takes about 30MB
<Camarade_Tux>
and there is all the tree overhead to take into account
<bluestorm>
(what's the plural for "prefix" ? prefixs, prefixes ?)
<Camarade_Tux>
prefixes ;)
<bluestorm>
why is it so dead on the "Ocaml Summer Project" side ?
<bluestorm>
there should be 6 different projects doing exciting things all summer, and we don't have *one* blog post or annoucement of any kind
<bluestorm>
is sucking at communication a requirement for OSP selection ?
filp has joined #ocaml
<hcarty>
bluestorm: The pa-do folks seem reasonably communicative. It is too bad that everyone else seems silent though.
<hcarty>
At least the qtcaml folks have their Subversion repository open for others to look through
coucou747 has joined #ocaml
filp has quit ["Bye"]
rwmjones has joined #ocaml
rwmjones has quit [Remote closed the connection]
rwmjones has joined #ocaml
maattd has joined #ocaml
Kopophex has joined #ocaml
Yoric[DT] has joined #ocaml
jlouis has joined #ocaml
<Yoric[DT]>
hi
guillem_ has quit [Remote closed the connection]
maattd has quit [Connection timed out]
maattd has joined #ocaml
guillem_ has joined #ocaml
maattd has quit [Remote closed the connection]
arquebus has joined #ocaml
arquebus has left #ocaml []
<Camarade_Tux>
2;6.24.3
<Camarade_Tux>
woops, wrong channel ;)
itouch has quit [Read error: 110 (Connection timed out)]
Snark has quit ["Ex-Chat"]
Mr_Awesome has quit [Connection timed out]
Chaide has joined #ocaml
itouch has joined #ocaml
Ched- has quit [Read error: 110 (Connection timed out)]
<Eridius>
what does +'a mean?
<rwmjones>
Eridius, it's some crazy typing thing ... no one except jacques garrigue & keiko nakata really know :-)
<Eridius>
I tried to read the manual section about it, and it was talking about covariant stuff, and I got completely lost
<mbishop>
I bet Oleg knows what it is
<Yoric[DT]>
+'a means co-variant 'a
<Eridius>
and what does that mean?
<Yoric[DT]>
Let's assume a type +'a t and some types u and v such that u is a subtype of v.
<Yoric[DT]>
Then [u t] is a subtype of [v t].
<Yoric[DT]>
However, if you have [type 'a w] instead of [type +'a t], there is no relation between [u w] and [v w].
<Eridius>
huh
<Yoric[DT]>
Conversely, with [type -'a x], [u x] is a supertype of [v x].
<Yoric[DT]>
Now, I only used that about once in my life.
<Eridius>
heh, what for?
<jlouis>
for extending a subtyping relation on u/v to t
<jlouis>
u t / v t even
<bluestorm>
(i like to think of [co/contra]variance as monotonicity)
<jlouis>
by the way, the -'a is called contra-variant
maattd has joined #ocaml
<Eridius>
here's something I don't understand. The type of Printf.printf is ('a, out_channel, unit) format -> 'a, and yet I give it a string, not this mysterious parameterized format
<bluestorm>
Eridius: magic
<jlouis>
Printf.printf is a hack ;)
<Eridius>
but *how*?
<bluestorm>
it isn't a string actually
<bluestorm>
it's a ('a , ... ) blah
<bluestorm>
except their representation as code are sometimes the same thing, you see
<bluestorm>
but not always so you shouldn't expect let a = "%d" ^ " " in Printf.printf a 2 to work
<Eridius>
huh
<bluestorm>
if you want to stay sane, you should only consider printf _with it's format string_
<mrvn>
wlit "int list spec later:"25 $ lit " " $ list $ nl )
<mrvn>
()
<mrvn>
[1; 2; 3; 4] (* int list *)
<mrvn>
[1.2; 3.4; 5.6] (* float list *)
<mrvn>
[["a"; "b"; "c"];
<mrvn>
["d"; "e"; "f"]] (* string list list *)
<mrvn>
[] (* empty float list *)
<mrvn>
int [5; 6; 7; 8] (* int list spec here *)
<mrvn>
);
<Eridius>
wtf?
<mrvn>
Looks horrible, doesn't it?
<Myoma>
I don't get that code
<Myoma>
what's the point
<mbishop>
good god
<mrvn>
The thing with cps is that each step gets called with a function where to continue. Nothing ever returns.
<jlouis>
it justifies the existence of Printf.printf :)
<jlouis>
thats the point of that code
<jlouis>
but you *can* do printf without compiler support as done above
<Myoma>
CPS also makes it blatantly clear which calls can be replaced with jumps
<mrvn>
Now, if you say read from a network socket and run out of bytes to read you can just put the next function (continuation) into a callback and do something else till more data arrives.
<mrvn>
let rec loop () = wait_for_input (); loop ()
<mrvn>
And you can do "let format = `Int16 $ `Int16 $ `Int32" and use the same format for input and output if you set it up right.
<mrvn>
i.e. when the socket blocks because you send to much it can be stuffed in a callback.
<Eridius>
there are library functions that have a return type of 'a, such as Printf.printf and Marshal.from_channel. Is there any way to replicate that without compiler support? For example let f = function None -> () | Some _ -> 3;; gives a type error
<mrvn>
Eridius: You need to put `a into the type.
<Eridius>
with a backtick?
<mrvn>
Eridius: You also need to have the output type depend on the input type. In your case it is not and you actualy have 2 types.
<mrvn>
# let id x = x;;
<mrvn>
val id : 'a -> 'a = <fun>
<mrvn>
Here the output (x) depends on the input (x).
<Eridius>
my example of Marshal.from_channel has output type 'a that doesn't depend on input type
<mrvn>
Eridius: special case with compiler support
<Eridius>
hence my question. It seems like it should be possible to do this
<mrvn>
Nope.
<Eridius>
let f = function Some x -> x;; gives val f : 'a option -> 'a. It doesn't seem like adding | None -> () should break that
<mrvn>
Eridius: You need Obj.magic to do this.
<Eridius>
ugh. The Obj module is undocumented
<mrvn>
Eridius: | None -> () would say that the 'a is a unit.
<mrvn>
You can never ever have a function return 2 types depending on some internal decision tree. You can only return one type or throw an exception.
<mrvn>
Even Marshal.from_channel returns one specific 'a depending on what you assign it to.
<Myoma>
Eridius: you can do the (let f = function None -> () | Some _ -> 3) thing in languages with more expressive type systems
<mrvn>
If you could return unit or int then there would be no point for the option type (None | Some x)
<Eridius>
I suppose you're right
<Eridius>
so given that there's no documentation on the Obj module, how are you supposed to use it?
<mrvn>
Eridius: you also have "Warning: marshaling is currently not type-safe."
<mrvn>
Eridius: you are not supposed to. :)
sporkmonger has quit []
<Myoma>
there is documentation
<Eridius>
for example, I can only guess at what Obj.magic does. I assume it's purpose is to break the type of the argument, so it gets re-interpreted as whatever type the entire expression is turned into
<mrvn>
Eridius: I think the interface to C explains all the functionality of Obj.
<Myoma>
that is it
<Myoma>
perhaps you are a casual user
<Eridius>
well, I only started playing with OCaml 2 days ago
<Eridius>
:P
<Myoma>
then don't use this
<mrvn>
The you definetly should not be using Obj.
<Eridius>
I'm not planning on using it, I just want to know what it does in case some day I ever decide that I need to break the type system
DerDracle has quit [Read error: 104 (Connection reset by peer)]
<mrvn>
Eridius: Obj.* looks at the internal representation of objects and can cast them around. The cast totaly violates the type system so if you cast wrong it blows up.
<Eridius>
ok
<Eridius>
so how come OCaml doesn't provide a facility for pretty-printing arbitrary objects like the toplevel does?
<mrvn>
Well, you can do that with Obj.
<Eridius>
how do you mean?
<mbishop>
doesn't oleg have something for that?
<Eridius>
it just seems odd that it the toplevel would have it but nothing else.
<jlouis>
mbishop, Oleg is somewhat like a tin-can opener
<jlouis>
darn effective :)
<Myoma>
hehe
<mrvn>
Eridius: The only way you can do it is by violating the type system. For the interactive shell that makes sense.
<Eridius>
MetaOCaml?
<mrvn>
And yes, I would have liked it in compiled code too.
<mrvn>
Eridius: you could just get the ocaml source and cut&paste the function to pretty print. :)
<mrvn>
Actually why is there no Obj.print? Seems like the pretty print function would fit right in there.
DerDracle has joined #ocaml
Chaide has quit [Remote closed the connection]
Ched- has joined #ocaml
pango_ has joined #ocaml
pango_ has quit [Nick collision from Idoru.]
<bluestorm>
mrvn: actually
<bluestorm>
you can't "do that with Obj"
<bluestorm>
Obj only has access to the runtime representation
<bluestorm>
you can print some stuff, this is what Std.dump of Extlib does
<bluestorm>
but the toplevel printing is more deeply magical than that
<mrvn>
True. Yout get problems with type Foo = Bla | Blub | Baz
<bluestorm>
yes, it will print 0,1,2
<mrvn>
To pretty print enums you need help from the compiler/interpreter.
<bluestorm>
well
<bluestorm>
enum are ok, i mean, 2 instead of Baz is no big deal
<bluestorm>
but _polymorphic variant_ are hell
<mrvn>
not "pretty"
<mrvn>
bluestorm: 0x47576347563456 instead of `Int?
<bluestorm>
# Std.dump `foo;;
<bluestorm>
- : string = "5097222"
<bluestorm>
other ones are fun
<bluestorm>
# Std.dump (Some ());;
<bluestorm>
- : string = "(0)"
Associat0r has quit []
<mrvn>
huh? I thought that would be an Enum type with a unit
<mrvn>
(1, ())
<bluestorm>
well unit is 0, and "Some" is like a tuple of length one
Associat0r has joined #ocaml
<Eridius>
Std.dump unit_big_int is "(1, <custom>)"
<Eridius>
curious
<mrvn>
bluestorm: None would then be ()?
<Eridius>
(big_int_of_int 27) is also "(1, <custom>)". but zero_big_int is "(0, <custom>)"
<bluestorm>
mrvn: actually it isn't
<Eridius>
I wonder what that first field means
<bluestorm>
None is 0
<bluestorm>
(), if you mean the tuple of length 0, is [| |] :]
<Eridius>
oh hrm, that must be the sign
<Eridius>
(big_init_of_int (-27)) is ("-1, <custom>)"
Associat0r has quit [Read error: 104 (Connection reset by peer)]
<mrvn>
Like constructed terms, values of variant types are represented either as integers (for variants without arguments), or as blocks (for variants with an argument).
<Toonto_del_alma>
the Intel Nehalem (Nov 2008) will have a total of 4 cores, 8 threads with SMT (minimum 16 threads on OS), are you ready for it?
<jlouis>
ready?
jeddhaberstro has joined #ocaml
<Toonto_del_alma>
the ideal scenario is 4 processes running in parallel, where each process is running 4 threads (2 of them in parallel)
Axioplase is now known as Axioplase_
<mrvn>
Toonto_del_alma: And why should we be ready?
<Toonto_del_alma>
mrvn, because in the future, they will have only newer microprocessors Nehalem-based
<mrvn>
And for that we should downsize our 1024 thread programs to a measly 16 threads?
<jlouis>
mrvn, some question was asked in #llvm on another network :)
<jlouis>
same question*
<Toonto_del_alma>
mrvn, 1024 threads are too kilowatts!
<mrvn>
Toonto_del_alma: oh yeah, way to little threads. Lets start one per pixel for the raytracer.
<mrvn>
Threads.create 1600 (fun x -> Threads.create 1200 (fun y -> raytrace_pixel x y));
<mrvn>
Toonto_del_alma: ever seen one of those 64 core Mips system that only use 50W?
<mrvn>
Now that is impressive.
<mrvn>
Apropo threads. I hate locking data structures to prevent race conditions between threads.
<jlouis>
mrvn, how about using a thread per instruction executed ?
<mrvn>
jlouis: raytracing is a bit more elaborate than one instruction per pixel.
<jlouis>
mrvn, I am joking
<Toonto_del_alma>
i'm questioning if its SMT does well its context switching pushing/restoring the general purpose registers, the x87 registers, the XMM registers and its flags.
<mrvn>
Toonto_del_alma: the cpu most certainly will have per thread registers and not push them onto a stack.
<Toonto_del_alma>
they are many registers (hundreds of ns) that SMT can go slower than without it in the I/O stall
<mrvn>
Toonto_del_alma: you do know what channel you are in, right?
<Toonto_del_alma>
right, i'm in the wrong channel
bluestorm has quit [Remote closed the connection]
mbishop has quit [Remote closed the connection]
asmanur has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has quit ["Ex-Chat"]
jonafan_ is now known as jonafan
Smerdyakov has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
ido has quit [SendQ exceeded]
itouch has quit ["le devoir m'appel ..."]
mbishop has joined #ocaml
hkBst has quit [Read error: 104 (Connection reset by peer)]
Asmadeus has quit ["poof"]
netx has quit ["Leaving"]
marmotine has quit ["mv marmotine Laurie"]
Asmadeus has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]