<bluestorm>
at the camlp4 level, you could try camlp4o `ocamlfind query -i-format type-conv` pa_sexp_conv.cmo yourfile.ml
<evn>
please keep in mind i know basically nothing
<bluestorm>
argh
<bluestorm>
at the camlp4 level, you could try camlp4o `ocamlfind query -i-format sexplib` pa_sexp_conv.cmo yourfile.ml
<bluestorm>
hm
<evn>
hrm it is not happy about that
<evn>
Camlp4: Uncaught exception: DynLoader.Error ("/opt/godi/lib/ocaml/pkg-lib/sexplib/pa_sexp_conv.cmo", "error while linking /opt/godi/lib/ocaml/pkg-lib/sexplib/pa_sexp_conv.cmo.\nReference to undefined global `Pa_type_conv'")
<bluestorm>
eh
<bluestorm>
at the camlp4 level, you could try camlp4o `ocamlfind query -i-format type-conv` `ocamlfind query -i-format sexplib` pa_type_conv.cmo pa_sexp_conv.cmo yourfile.ml
<bluestorm>
let me install sexplib to try your example :p
<evn>
Failure: "Pa_type_conv: path not set"
<evn>
it is from the README.txt but maybe it's not supposed to stand on its own
<bluestorm>
i think it is
<evn>
could i try camlp5 in some way?
<bluestorm>
hm
<bluestorm>
let me try to install sexplib, i'll give you the correct command line then
<evn>
thanks
zmdkrbou has quit [Read error: 113 (No route to host)]
ben has quit []
<bluestorm>
evn:
<evn>
yes
<bluestorm>
the example given works for me if i add TYPE_CONV_PATH "Test" at the beginning of the code
<bluestorm>
i find that a bit confusing, as i would have naturally used split "," "foo,bar,baz" instead (moreover, in my context, partial application of the separator makes sense)
<bluestorm>
is there a reason for that order choice ?
<flux>
I too would expect that
<mfp>
I'd also expect sep str...
<mfp>
in such cases (params with same type), I tend to use labels
<mfp>
unless the intended order is "clear" when partial app makes sense as in this case (it's just that ExtLib seems wrong IMHO)
<bluestorm>
hm
<bluestorm>
i could disturb rwjones with that next times i see him on the chan
<mfp>
probably too late to change that now
<mfp>
as the change wouldn't be reflected by the type and would break old code silently
<bluestorm>
hmm
<bluestorm>
mfp: the change will break code
<bluestorm>
but it's easy to make it noisy
<bluestorm>
for example by trying to compile with a differently-typed split function
<mfp>
ah, so changing the type altogether
<bluestorm>
even temporarily
romanoffi has joined #ocaml
<bluestorm>
there could even be some trickery that would allow one to fix the code with the temporary definition
<mfp>
that can be used to fix your code, but we'd need some lib version comparison at runtime to make sure it's being linked against the right extlib
<mfp>
s/runtime/compile time/
<bluestorm>
for example you create an abstract type string', with a construction function uGLY_FIX : string -> string', then type the new split as string' -> string' -> string
<bluestorm>
then you can fix your code by reversing the argument order and adding the function uGLY_FIX at the same time, and then ripp it off with a regexp or something like that
<bluestorm>
(that suppose you won't use uGLY_FIX in too acrobatic ways, but it's not difficult to be careful about the regexpability of the fixed code)
jlouis has joined #ocaml
<mfp>
what about (extextlib.ml -> ) include Extlib type sep let split : sep -> string -> string list = fun _ _ -> assert false then s/Extlib/Extextlib/g, compile, fix, undo rename
<mfp>
so "open Extlib" becomes "open Extextlib"
<bluestorm>
hm
<bluestorm>
the problem is that the fixed function won't compile with the Extextlib definition
<mfp>
and you can alternatively have two versions of extextlib.ml, one which reorders the args, one which doesn't, and you only need to pick one at compile time without changing your code
<mfp>
it will once you do type sep = string
<mfp>
or you can s/open Extextlib/open Extlib/g and go back to the func with the new semantics
<mfp>
actually, just remove type sep and let split = ... duh
<bluestorm>
hm
<bluestorm>
what would be interesting would be an incremental fixing of the different places
<bluestorm>
you fix the first split function in your code, then compile again and it fails at the second
<bluestorm>
mfp: i guess the fix concerning your runtime-signature-nonmismatch problem would be to add another function somewhere in Extlib, thus changing the whole signature :-'
<bluestorm>
i suggest Option.bind : 'a option -> ('a -> 'b option) -> 'b option
jlouis_ has quit [Read error: 110 (Connection timed out)]
uuuppz has joined #ocaml
<uuuppz>
thanks for the help yesterday
<uuuppz>
starting to get it... a little bit
<flux>
I think the split issue is unfixable, but one can learn to live with it ;). one could add labeled arguments (does that break any existing code?), but that's about it IMO..
<bluestorm>
hm
Tetsuo has quit [Read error: 110 (Connection timed out)]
Tetsuo has joined #ocaml
<bluestorm>
thelema: if you were to include those in your 'enhanced stdlib' thing, do you think it would be possible to change that ?
OChameau has joined #ocaml
munga has joined #ocaml
seafood__ has quit []
naufraghi has joined #ocaml
<naufraghi>
hello ocamlers!
<naufraghi>
I'm just starting with ocaml, and I have some problem with the type inference...
<thelema>
r2c and c2r seem misnamed to me. r2c works on any point, maybe p2c?
<naufraghi>
yes, after the refactoring yes
<thelema>
stylistically, all the apoints you have in your r2c and c2r functions distract -- instead of "let f x = match x with" use "let f = function ..."
<naufraghi>
is it only a syntactic option? or there is some difference in expressive power?
<thelema>
syntactic option. It just eliminates the extra binding that never gets used.
<naufraghi>
ok, I prefer having just one preferred way... python background :P
<thelema>
as you will.
<ziph>
"def foo(x): x + 1" and "foo = lambda x: x + 1" are one preferred way? :)
middayc has quit []
<qwr>
ziph: first one. lambda is a special case in python.
<naufraghi>
eheh, no flame!
* qwr
will flame, that he's not flameing.
<naufraghi>
... I have done the "function" version but it seems to be different...
ziph has quit []
<qwr>
but in ocaml the function pattern-match looks cute
<thelema>
(* raised if the (n,irr) parameters don't form
<thelema>
type elem = Pow of int | Sum of int;;
<thelema>
class bffield n irr =
<thelema>
let q = 1 lsl n in
<thelema>
let r = q + irr in
<thelema>
let p2s = let out = Array.create q 0 in
<thelema>
out.(0) <- 1;
<thelema>
out in
<thelema>
let s2p =
<thelema>
let out = Array.create q 0 in
<thelema>
out.(0) <- -1; out.(1) <- 0;
<thelema>
for i=1 to q-2 do
<thelema>
let num = p2s.(i-1) lsl 1 in
<thelema>
let entry = if num < q then num else num lxor r in
<thelema>
if entry = 1 then raise Not_irreducible;
<thelema>
oops... sorry about the paste
<bluestorm>
thelema: i've been playing with your fold_right function a bit
<bluestorm>
(the tail-rec one with a fold_right_max)
<thelema>
bluestorm: have you figured it out. It's not my function, it comes from extlib, iirc
<bluestorm>
anyway, on my computer, with big lists (~ 2M items) i found it to be GC-bound
<thelema>
hmm, I read it again and it makes sense this time...
<bluestorm>
i've got an implementation wich has the same speed on little lists, a slight overhead with medium-sized lists, and does much better on big lists (the former one is 100% to 400% slower)
<thelema>
It just reverses the list and runs through the reversed list as fold_left... any ideas why it'd become GC bound?
<thelema>
I'll happily incorporate better code.
<bluestorm>
because the first items are kept a long time in the list
<bluestorm>
hm
<bluestorm>
i mean, the items of the beginning of the list are used to build a *big* list wich is kept a long time in memory, and thus leave the minor heap
<bluestorm>
my implementation reverse the list in "chunks", and so put a lot less things in the minor heap
<thelema>
the first items are keps a long time? you mean the tail (after fold_right_max)
<bluestorm>
but 1) it is longer 2) i have absolutely no idea if the benefits are the same on other computer/arch/etc.
<bluestorm>
thelema: i mean the item in the beginning of the list (minus the fold_right_max first elements, of course)
<bluestorm>
code coming
* thelema
wonders how you did this without 1) O(n) stack space or 2) O(n) heap space
<thelema_>
hmmm... You use a bit more stack space, but only one or two frames per 100 list elements... And then unwind this spaced stack, reversing 100 elements at a time and then tail-recursive folding over them...
<bluestorm>
hm
<bluestorm>
it must be that :p
<thelema_>
I don't like the chunk_size = fold_right_max / 10 -- I'd make another global parameter instead
<bluestorm>
you're right, they're different things
<bluestorm>
as fold_right_max should be under stack_space, and chunk_size under max_list_size / stack_space
<bluestorm>
but i began using fold_right_max
<bluestorm>
(and then realized than a smaller value is a bit better)
<thelema_>
your solution passes over the list 3 times (in the big-list case) - once to find jump points, once to take, and once to fold...
<thelema_>
but it doesn't allocate such a huge temp list, which I can see causing problems for the GC
<bluestorm>
there is still a bit of GC overwork as it tends to promote things that he should not
<bluestorm>
on a 1M-long list, the first version promoted 14878500 words, while the second promoted 69340
<bluestorm>
those words being 'accidental' promotion : adding the commented Gc.minor () promotes only 136 words
<bluestorm>
(but it's much slower as they're quite frequent)
pango has quit [Remote closed the connection]
<bluestorm>
besides, i'm not sure calling Gc.* in a standard function is a good idea :p
AxleLonghorn has quit ["Leaving."]
thelema has quit [Read error: 110 (Connection timed out)]
Morphous_ has joined #ocaml
jlouis has joined #ocaml
pango has joined #ocaml
Morphous has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
marmottine has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
<bluestorm>
i realised the rev + tail-recursion was actually not needed
delamarche has joined #ocaml
<bluestorm>
and now i've got a 0-promoted-word version :)
<thelema_>
:)
<thelema_>
I like the fold_right_3 version
cygnus_ has quit [Remote closed the connection]
cygnus_ has joined #ocaml
<thelema_>
so now the stack space used approximates: fold_right_max + list_size / chunk_size + chunk_size
<bluestorm>
do you think they add up ?
<thelema_>
for a list of 2M elements, and your newest values of f_r_m and c_s, 1000 + 4000 + 500 = 5500
<bluestorm>
hmm, yes they do
<bluestorm>
the fold_right_max + part coming from the "loop" only
<bluestorm>
i tried to remove the loop
<bluestorm>
but the additional pass still add a bit of overhead
<bluestorm>
and as we can assume fold_right is mostly used with short lists, i think it's important to be as quick as possible
musicallyut has joined #ocaml
<thelema_>
don't worry about it, it's important to be quick on short lists
<thelema_>
and to not have a sudden jump in processing speed just because we cross fold_right_max
rossberg has left #ocaml []
<bluestorm>
:p
* thelema_
wonders if jump could merge with the first partial fold...
<bluestorm>
ha ha :D
<thelema_>
oops, no... jump is tail recursive...
musically_ut has quit ["Leaving"]
<thelema_>
in fold_right_3, why must chunk_size < fold_right_max?
<bluestorm>
hm
musicallyut has quit [Client Quit]
<thelema_>
they don't seem to interact at all
<bluestorm>
yes they don't
musically_ut has joined #ocaml
<bluestorm>
i assumed that the library-makers intended the stack usage to stay around fold_right_max
<thelema_>
f_r_m just determines the cutoff before switching to chunked processing
<bluestorm>
if chunk_size is much bigger, it's not true anymore
<thelema_>
stack usage is unlimited - it's still O(n), even though the constants work heavily in our favor
Linktim has quit [Read error: 110 (Connection timed out)]
<thelema_>
in fact, for large lists, chunk_size influences max stack size much more than fold_right_max
<bluestorm>
btw, it *could* be interesting to have fold_right_max and chunk_size as references, in order to allow the user to fine-tune them, but i guess this could raise delicate problem with multi-threading and what not
* thelema_
looks for a solution to this problem in general
Tetsuo has quit [Read error: 110 (Connection timed out)]
<bluestorm>
hm
<thelema_>
I guess I could functorize any functions depending on magic constants, to allow someone to generate a version that doesn't depend on the default values...
<bluestorm>
i was thinking of it too :p that would add quite a bit of source code, though
<thelema_>
but when the whole module does so (as the ropes library), ...
<bluestorm>
as i guess you'll want to "inline" the functor application in the common case
<thelema_>
exactly.
<bluestorm>
hm
<bluestorm>
on the other hand
<thelema_>
why make the common case slower just for crazy people who want to screw with "carefully chosen" constants
<bluestorm>
i'm not sure runtime-functorization add that much overhead, if it's done only once
<bluestorm>
hmm
<bluestorm>
i just said something stupid :-'
<thelema_>
runtime functorization. heh.
<bluestorm>
hehe
<bluestorm>
one could think of a (tadaam !) camlp4 extension to automagically generate those functors from the function source code :-'
<bluestorm>
(wasn't there a 'defunctorize' for caml some time ago ?)
* thelema_
wants to look into perma-hooking some camlp4 extensions into community-ocaml
jderque has joined #ocaml
<thelema_>
any camlp4 gurus?
<bluestorm>
thelema_: what's the question ?
<thelema_>
easiest way to build ocamlc so any programs compiled by it automatically get processed by a given camlp4 macro (I assume that I can merge many camlp4 macros into one mega-macro)
<bluestorm>
hm
<bluestorm>
why would you want to do that ?
<bluestorm>
(i guess alias ocamlc="ocamlc -pp 'camlp4o .../foo.cmo'" would be ok :p )
thelema has joined #ocaml
<thelema>
easiest way to build ocamlc so any programs compiled by it automatically get processed by a given camlp4 macro (I assume that I can merge many camlp4 macros into one mega-macro)
<thelema>
I guess a bash wrapper would work, but not so well for win32
<bluestorm>
i'm not sure what you want to do is a very good idea
<bluestorm>
if it's only that you're tired of typing "ocamlc -pp ..." every time, you should use an automated build process
<bluestorm>
(makefile, omake, ocamlbuild, ...)
<thelema>
no, I want the compiler to accept various syntax extensions
<bluestorm>
but hm
<thelema>
hmm, maybe I should look into the camlp4[ro]*
pango has quit [Remote closed the connection]
<bluestorm>
what's the interest, when camlp4 is in the standard distribution ?
<thelema>
I'd like even the simplest programs to get the benefit of a stdlib of p4 macros with no extra work for the developer
pango has joined #ocaml
<thelema>
imagine if users of common lisp had to enable 1000 macro packages to get all the macros in that language. The users wouldn't -- they'd write without the macros
<bluestorm>
it should be possible to do something like
<thelema>
we have that situation in ocaml now - it's just too hard for me to find, install, check dependencies, and get my command-line right
<bluestorm>
ocamlc -pp camlp4ox ....
<bluestorm>
actually i'd be more interested in an extension of ocamlfind to handle camlp4 too
<thelema>
I hear some camlp4 extensions conflict
<bluestorm>
that's very likely :p
musicallyut has joined #ocaml
<thelema>
if a maintainer merged packages with some care, he might succeed at finding and dealing with these conflicts?
<bluestorm>
hm
<thelema>
but if each person works in isolation, I see little hope for finding conflicts
<bluestorm>
the conflicts happen at the source level
<bluestorm>
if two camlp4 extension conflicts, you can't write code using both of them
<thelema>
one extension would have to change.
<bluestorm>
yes
<bluestorm>
but as it's a source-level problem
<bluestorm>
i don't see how you could still have confclits downstream
<bluestorm>
hm
<thelema>
reasons for conflict? trying to use the same tokens in syntax extensions?
<bluestorm>
for example
<bluestorm>
i think it's possible to have conflicts related to the way we insert/delete rules
<bluestorm>
see e.g. the dirty hacks of Yoric[DT] :-'
<bluestorm>
but thelema if you only enable extensions on the files that need them, you (as a packager/user of someone else code) won't ever have conflicts
<bluestorm>
because conflicting code could not be written (actually, compiled) in the first place
thelema_ has quit [Read error: 110 (Connection timed out)]
<flux>
I would very much not like to see ocamlc patched to include various extensions, especially if the documentation and implementation isn't of the same level as they are for the standard ocaml
<flux>
ocamlfind has some support for camlp4 extensions, but I've never managed to use it..
<bluestorm>
flux: ah ?
<thelema>
given two conflicting p4 macros, the difficulty of removing the conflict and making one coherent package: ???
<flux>
from my point of view, ocamlfind would be the solution
<bluestorm>
ah
<bluestorm>
the -syntax flag maybe
<bluestorm>
flux: i totally agree :)
<bluestorm>
thelema: depends on the conflict natures
<bluestorm>
if the two extension fundamentally want to do the same thing
<bluestorm>
you won't be able to use both of them
<thelema>
then write one extension that subsumes the functionality of both.
<bluestorm>
that's possible
<thelema>
I don't want to include every p4 extension out there. I want a standard set of extensions that do a bunch of nice things.
<thelema>
people are still welcome to use local macros in addition to this.
<bluestorm>
flux: you may be speaking of
<bluestorm>
-syntax <p> Use preprocessor with predicate <p>
<bluestorm>
i've used that a long time ago
<bluestorm>
i should try to use that now, i guess
hkBst has quit [brown.freenode.net irc.freenode.net]
ertai has quit [brown.freenode.net irc.freenode.net]
bla has quit [brown.freenode.net irc.freenode.net]
lnostdal has quit [brown.freenode.net irc.freenode.net]
hkBst has joined #ocaml
lnostdal has joined #ocaml
bla has joined #ocaml
ertai has joined #ocaml
<thelema>
flux: you're right, any default extensions would have to be documented thoroughly
<bluestorm>
thanks for the reminiscence :-'
<thelema>
flux: other than that (and the horrid error messages that will likely be produced), what reason not to have a standard p4 extensions?
<flux>
then there is the issue that doesn't camlp4 reduce the quality of error messages?
<flux>
and you just said that ;)
<flux>
thelema, well, any builtin extension will make the language larger, and larger doesn't necessarily mean better
munga has quit ["Leaving"]
<thelema>
the only way to fix the error messages is to hack the compiler bad. I'd like to do this, but I also want to not make Xavier Leroy come and kill me in my sleep.
<flux>
it has the potential of breaking existing code also, in the form of old identifiers becoming new keywords
<flux>
not to mention even now there could be better error messages, but I suppose that's not an easy problem..
<thelema>
These extensions would have to stay conservative... Like deriving.
<thelema>
common lisp manages to have an *extensive* set of preprocessor macros... why can't we?
jonafan has joined #ocaml
<flux>
do they all come included automatically?
<flux>
ocaml doesn't have a require-kind of mechanism for taking language extensions into use
musically_ut has quit [Remote closed the connection]
<thelema>
could one be built with p4?
<thelema>
if I had to use only one macro, one that allowed other macros to be #required = used ... that'd make the top of my list.
* thelema
really dislikes p4 extensions separateness from source code
Snrrrub__ has joined #ocaml
Linktim- has joined #ocaml
<bluestorm>
flux:
<bluestorm>
there was something written by markus mottl iirc
<bluestorm>
that allows you to specify in a comment the extensions used
psnively has joined #ocaml
thermoplyae has joined #ocaml
love-pingoo has joined #ocaml
thermoplyae has quit [Client Quit]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim_ has joined #ocaml
Linktim- has quit [Read error: 104 (Connection reset by peer)]
musically_ut has joined #ocaml
bebui has quit ["Reconnecting"]
bebui has joined #ocaml
Snrrrub___ has quit [Read error: 110 (Connection timed out)]
thelema is now known as thelema|away
bluestorm has quit [Read error: 113 (No route to host)]
bluestorm has joined #ocaml
naufraghi has left #ocaml []
naufraghi has joined #ocaml
<bluestorm>
thelema|away:
<bluestorm>
i think it's quite easy to pack numerous extensions into a single package
<bluestorm>
i haven't tried it, but i guess '-pack' would be enough
middayc has joined #ocaml
musicallyut has quit [Remote closed the connection]
OChameau has quit ["Leaving"]
* Yoric[DT]
has the feeling he was slightly insulted in absentia.
<bluestorm>
oO
jlouis_ has joined #ocaml
ttamttam has joined #ocaml
delamarche_ has joined #ocaml
delamarche has quit [Read error: 104 (Connection reset by peer)]
munga has joined #ocaml
jlouis__ has joined #ocaml
thelema|away is now known as thelema
jlouis has quit [Read error: 110 (Connection timed out)]
munga has quit ["Leaving"]
ttamttam has left #ocaml []
<Yoric[DT]>
Now back to testing performances.
jlouis_ has quit [Read error: 110 (Connection timed out)]
<petchema>
s/s// :)
<bluestorm>
:D
<Yoric[DT]>
oops
<Yoric[DT]>
caught again
<Yoric[DT]>
Is anyone around here familiar with Arrows ?
<bluestorm>
dont ask to ask :-'
<Yoric[DT]>
I'm currently working on something with three type parameters. Is this covered by the term "arrow" ?
<psnively>
No.
jlouis has joined #ocaml
<Yoric[DT]>
That is, I have an abstract data-type ('a, 'b, 'e) t with the following composition law:
<Yoric[DT]>
compose : ('a, 'b, 'e) t -> ('b, 'c, 'e) t -> ('a, 'c, 'e) t
* Yoric[DT]
afk
<bluestorm>
hm
<bluestorm>
might be an arrow
<bluestorm>
if you rephrase it (t 'e) 'a 'b -> (t 'e) 'b 'c -> (t 'e) 'a 'c
<naufraghi>
hello! I'm back with another basic question :)
thelema has quit ["traveling"]
<bluestorm>
naufraghi: are you waiting for something ?
<naufraghi>
how can i make a function that works on differtent types
<naufraghi>
no, no, just typing!
<bluestorm>
hm
<bluestorm>
is parametric polymorphism not enough ?
<naufraghi>
in my casa, a list of rpoints and a list of cpoints
<bluestorm>
naufraghi: you can't
<bluestorm>
but you can have a function over a list of points
<bluestorm>
your_function [RPoint p1; CPoint p2; CPoint p3; RPoint p4; ...] would work
<naufraghi>
yep, but the question is mainly about the syntax I've not found
* Yoric[DT]
is back
<bluestorm>
syntax ?
<Yoric[DT]>
Sorry, phone call.
<naufraghi>
yes, I have an area func
<naufraghi>
implemented for cartesian points
* Yoric[DT]
will carry on later after naufraghi's questions.
<naufraghi>
I'd like to have an area func, area : point list -> float
* Yoric[DT]
returns to see how performance[s] measurement fares.
<bluestorm>
hm
<bluestorm>
it's strange that the haskell documentation doesn't include the arrow laws
<naufraghi>
but I've not found the syntax to ask for the type of an element of the list
<bluestorm>
"ask the type" ?
<bluestorm>
you don't do that
<bluestorm>
you match the value
<bluestorm>
and see with its constructor (RPoint or CPoint) wich kind of point it is
* Yoric[DT]
knows one thing or two about arrows.
<Yoric[DT]>
It's just a question of vocabulary.
<Yoric[DT]>
Is that an arrow or something more general ?
<Yoric[DT]>
(in this case, 'e is a measure of side-effects)
<naufraghi>
yes, but, the point is inside the list (it's a stupid question, I know, but I didn't find such matching in an example)
<bluestorm>
haha Yoric[DT]
<bluestorm>
looks like there are 20-27 arrow laws
<Yoric[DT]>
20-27 ?
<bluestorm>
20 to 27
* Yoric[DT]
only knew about 3 base laws and a few derived ones.
<bluestorm>
aren't those the monad laws ?
<bluestorm>
naufraghi:
<bluestorm>
you can combine pattern matching
<Yoric[DT]>
composition / application to first element of pair / application to pair
<bluestorm>
do you know how to do pattern matching over a list ?
<naufraghi>
perhaps I'm missing that...
<bluestorm>
match your_list with [] -> (* the empty list case *) | hd::tl -> (* the head and tail case *)
<bluestorm>
let rec sum = function [] -> 0 | hd :: tl -> hd + sum tl
<bluestorm>
sum : int list -> int
ygrek has joined #ocaml
<naufraghi>
... ok, I've seen this... ok, if this is the way I'll try to move it towards my "points" :P
<bluestorm>
Yoric[DT]: you have to consider a subtype of your general type were 'e is fixed (akin to a partial application at the type level), and then see if it realize the arrow laws
<bluestorm>
naufraghi:
<Yoric[DT]>
bluestorm: do you have a link to your 20-27 laws ?
<bluestorm>
match your_point_list with [] -> | (CPoint p) :: tl -> | (RPoint p) :: tl -> ...
<naufraghi>
thanks! this is like gym!
jlouis__ has quit [Connection timed out]
<bluestorm>
naufraghi: you could do two separate matching of course
<flux>
should work, although my testing hasn't been quite extensive yet..
<evn>
neat
<flux>
I tried to keep the overhead relatively small, too, so they are mostly in C
<rwmjones>
what's libev?
<flux>
it's an event loop similar to libevent
<flux>
so basically a library around the select-system call, except it can use other kinds of polling mechanisms too
<flux>
I haven't yet implemented everything, missing is atleast polling for file change, fork-specific support and embedding other kinds of event loops
<flux>
also apparently 3.0 is missing asynchronous messaging, even though it is in the documentation..
<flux>
(now that I think of it, maybe is misjudged the problem)
psnively has quit []
<flux>
nope, not in the release
bongy has quit ["Leaving"]
<flux>
too bad, it could be useful
ita has joined #ocaml
ofaurax has joined #ocaml
Tetsuo has joined #ocaml
|Catch22| has joined #ocaml
<flux>
it's a shame that the ocaml C interface doesn't reveal the functions for converting stuff into a Unix.wait status or Unix.stat file state
<flux>
if I want to return such values from C, should I just go and copy the relevant parts from the standard library? or perhaps re-implement them in term of the visible interface..
<flux>
would that mean I would need to license under the ocaml license?-o
ttamttam has joined #ocaml
<bluestorm>
if it's not to heavy, re-implementing them as any other ocaml value looks like a 'simple' way
LordMetroid has joined #ocaml
ttamttam has left #ocaml []
Demitar has quit ["Burn the land and boil the sea. You can't take the sky from me."]
RobertFischer has joined #ocaml
<Yoric[DT]>
flux: your work sounds interesting.
<mbishop>
I'm actually liking F#..something must be wrong with me :)
Snrrrub__ has quit [Read error: 110 (Connection timed out)]
thermoplyae has joined #ocaml
<Yoric[DT]>
mbishop: :)
<Yoric[DT]>
Does anyone have a simple sample using a few kinds of different exceptions ?
<bluestorm>
mbishop: and you like F#-on-Mono too ?
<mbishop>
Well, I mostly use it on my desktop, which has Windows XP
<mbishop>
but I do have Mono here on ubuntu on my laptop, seems to work just fine
Robdor has joined #ocaml
<Ugarte>
I seem to recall issues with F# on Mono on Mac, incidentally.
<Ugarte>
-aot. Mono on Mac can't do -aot.
<Ugarte>
*shrug*
<mbishop>
Yeah I think it mentioned something about aot breakage on "some systems"
<evn>
is aot really that important
<Ugarte>
OSX. I think it works fine on Linux.
<Ugarte>
evn: Dunno.
<Ugarte>
It makes the installation process a pain, 'cause the install script fails.
<Ugarte>
IIRC.
<Ugarte>
Been a while since I did that. I do all my F# on Windows now.
<evn>
ah
<mbishop>
Yeah, I have VS 2008 Shell set up with F#
<Ugarte>
evn: F# implements some of the OCaml standard library stuff.
<mbishop>
Most of the OCaml standard library is in a compat library
<mbishop>
but you don't really need to use it
<Ugarte>
Well, unless you want to target both.
<mbishop>
unless you did indeed want the code to work with both
<mbishop>
you'd get into some trouble quick with arithmetic though
<Ugarte>
Oh, really?
jlouis_ has joined #ocaml
<mbishop>
yeah all the +, -, * etc are overloaded
<mbishop>
> let foo = 2.0 + 2.0;;
<mbishop>
val foo : float
<Ugarte>
oh, true.
<Ugarte>
I hadn't thought of that.
<Ugarte>
I've been using F# more than OCaml recently. ;)
<mbishop>
F# is pretty nice, fixes some of the annoynaces of OCaml
<evn>
i am still have some knee-jerk concern about mono's patent issues... dunno if thats still really valid or not
<evn>
-am
<bluestorm>
the problem with mono's patent issues is that they're more generally .NET patent issues
<bluestorm>
if it's a problem for you (i think it is for me), then it's kinda difficult to use F# anyway
<bluestorm>
(and, yeah, they're still really valid)
<mbishop>
I'd obviously use OCaml if I was concerned about having it run on all the major platforms, but if windows is my target, might as well use F#
<Ugarte>
I wouldn't be too worried about patent issues.
<mbishop>
although from what I've seen (looking at F# stuff brings me to a lot of crazy .Net lovers :P) the gnome guy, Icaza or whatever, works with microsoft on Mono and Moonlight
<Ugarte>
For one thing, MS and Novell have an agreement to indemnify Novell customers, IIRC.
<Ugarte>
mbishop: Right.
<bluestorm>
Ugarte:
<bluestorm>
[22:34:04] <Ugarte> For one thing, MS and Novell have an agreement to indemnify Novell customers, IIRC.
<ita>
patent issues are only a problem if you are a company and if you distribute software - or if you are a customer
<Ugarte>
Anyway, the ECMA stuff is pretty clearly OK.
<bluestorm>
i don't think F# is in the ECMA
<Ugarte>
It's the stuff on top--Forms, ADO.NET, etc--that's worrisome, if anything.
<Ugarte>
So if you don't use that, you're fine./
<bluestorm>
and big parts of Mono are not either
<Ugarte>
bluestorm: No, it isn't, but it's licensed udner a different license entirely.
<bluestorm>
(iirc Mono implements ADO.Net, ASP.Net and what not)
<Ugarte>
The MSR beta of F#, that is.
<bluestorm>
yeah, haven't heard of specific concerns regarding F#
<mbishop>
F# has that microsoft shared source license or whatever
<bluestorm>
and Don Syme seems quite open anyway
<bluestorm>
but still
<bluestorm>
Ugarte: with all the FUD from MS and the Novell deal
<mbishop>
I heard something about the F# team was thinking of changing the license to something else
<bluestorm>
i wouldn't feel safe (at a global scale)
<bluestorm>
(i'm not saying that i'm worried as an individual. But i like to use technologies wich are open, and i'm not sure .NET is)
<Ugarte>
Which allows noncommercial and maybe (I forget) some commercial use.
jlouis has quit [Read error: 110 (Connection timed out)]
<evn>
doesn't allow forks though does it
<Ugarte>
bluestorm: Well, I suppose this is the point I should admit that I do work at MS, so I'm not really an unbiased party. In the sense that there are no IP fears for me about using F# for commercial stuff.
<evn>
so they could relicense at any time
<evn>
and you would be stuck
<Ugarte>
But I'm really not very well versed in the licensing and patent issues of .NET and F#, so I can't say.
<bluestorm>
Ugarte: :p honest of you
<mbishop>
.Net is all ECMA standardized, I believe. It's some of the specific languages that aren't
<bluestorm>
mbishop: actually, C# is ECMA standardized
<Ugarte>
My impression was that the ECMA stuff was completely in the clear, and that the current beta F# releases are in the clear for noncommercial use.
<Ugarte>
But don't take that as gospel.
<bluestorm>
but .Net as a platform isn't
<Ugarte>
bluestorm: So is the CLR IL, no?
<bluestorm>
(and the CLR is, too)
<mbishop>
bluestorm: well, according to that mono page, .Net framework is ECMA
<Ugarte>
So what do you mean by ".NET as a platform"? The libraries?
<mbishop>
The .NET Framework is divided in two parts: the ECMA/ISO covered technologies and the other technologies developed on top of it like ADO.NET, ASP.NET and Windows.Forms.
<Ugarte>
Yeah.
<bluestorm>
mbishop:
AxleLonghorn has joined #ocaml
<Ugarte>
But if you build on Mono using only the ECMA stuff, I assume you're good.
<bluestorm>
the ECMA/ISO part being C# and the CLR/CLI, and the "other technologies" being all the other things
<bluestorm>
but Ugarte i agree with the fact that F# as a language is kinda safe
<bluestorm>
and the work done on the language is interesting indeed
<mbishop>
If you just write F# code and distribute the source, then there is nothing to worry about anyway heh
<mbishop>
since it doesn't involve mono...I suppose the only time you'd have to worry is if you included mono with it or something
<bluestorm>
hm
<evn>
well if mono goes away
<evn>
then what
<evn>
sure ppl still have your F# source, but
<bluestorm>
mbishop: i don't have Windows so in all case i'd use Mono
<mbishop>
bluestorm: well that's your problem :P
<bluestorm>
of course
<mbishop>
Although mono isn't the only game in town, there is that GNUdotnet or whatever
<mbishop>
it has a lot less progress, apparently
<bluestorm>
but i'd only consider the language if i could use it with a really open technology
<bluestorm>
wich i'm not sure Mono is, and i'm quite certain the MS implementation is not
<mbishop>
Fair enough
<bluestorm>
that said, i'm not too unhappy about more people interested in functional programming and ML-derived languages
<mbishop>
For me, I don't worry about the licensing, but it would be a little scary if people had problems using my code because of legal action or something
<bluestorm>
(for example i'll happily support any beginner, be it OCaml or F# )
<mbishop>
Indeed, I think OCaml could even benefit from some of F#'s changes, mostly the syntax ones
<bluestorm>
it would be interesting to have it more integrated with camlp4, but that's not something so easy to do, so i guess it'll have to wait a little bit
<Ugarte>
bluestorm: Eh, it's probably obvious that I don't consider "openness" to be a big deal. What matters to me is if I can use something, and I can use F# just fine right now. ;)
<Ugarte>
Especially if I use it for work.
<Ugarte>
No fears there.
<bluestorm>
:p
mfp has quit [Read error: 110 (Connection timed out)]
<bluestorm>
I've heard some people saying that F# is great because they will be able to "use ~OCaml at work (in a C#-place)"
<bluestorm>
i just hope that F# will not be a 'danger' to the (quite fragile already) 'ocaml community'