<jcpiza>
i did put stack limit 1073741824 and GC.stack_limit says -1073741824 weird!!!
ertai has quit [Read error: 110 (Connection timed out)]
buluca has joined #ocaml
<pango>
can't you optimize your algorithms not to require such deep stack anyway?
<pango>
otherwise I fail to see your point
<jcpiza>
pango, i wann't optimize algorithms, i want to put relaxed algorithms, :D
<jcpiza>
i'm tunning to prevent crash
<context>
do you really need a stack that long
<jcpiza>
context, why not?
<pango>
ever heard that your programs will run on a computer?
<jcpiza>
pango, i need to know the limitations of ocaml vm before implementing my programs for this ocaml vm.
mrsolo_ has quit [Read error: 104 (Connection reset by peer)]
<pango>
that's not going to be efficient, no matter what
mrsolo has joined #ocaml
<jcpiza>
my computer is faster, i've not problem when the duration of runned program is 20 minutes instead 4 minutes.
<pango>
Implement your programs so that you don't need more than a few tens of thousands of recursive calls, and you should be safe everywhere
<jcpiza>
pango, A* needs tons of nodes
<pango>
if you need more, use cps
<jcpiza>
why cps instead ocaml?
<pango>
cps = continuation passing style
<jcpiza>
pango, cps is very complex, i only to add simple mathematical functions, long deepening
<pango>
that's gonna be slower, but you should only be limited by the heap
<jcpiza>
ohhhh!
<jcpiza>
noooo!
<jcpiza>
what is the max. size of heap?
<jcpiza>
aprox.?
<pango>
depends on the platform, I suppose
<jcpiza>
on i386, e.g.
<pango>
been running > 20GB heap processes on Linux and 64bit CPU
<jcpiza>
i've not those heavy machines
<pango>
on Linux i386, with default user/kernel split (3GB/1GB), processes are supposed to have 3GB of address space, but real limit is probably lower, depending on malloc() implementation and stuff
<jcpiza>
pango, and about 32-10=22 bit data word + 10 bit tag?
<pango>
that's the limit per object of OCaml on 32 bits archs
<jcpiza>
only 2^22 addresses, ok?
<pango>
?
<pango>
OCaml uses 32bit pointers
<jcpiza>
wait, i'm implementing a list of ints to see when it crashes
<jcpiza>
let rec make_list x = if x = 0 then [] else make_list(x-1)@[x];;
<xavierbot>
Characters 55-56:
<xavierbot>
let rec make_list x = if x = 0 then [] else make_list(x-1)@[x];;
<xavierbot>
^
<xavierbot>
This expression has type int but is here used with type int64
<jcpiza>
let rec make_list x = if x = 0 then [] else make_list( x - 1 )@[x];;
<xavierbot>
Characters 56-57:
<xavierbot>
let rec make_list x = if x = 0 then [] else make_list( x - 1 )@[x];;
<xavierbot>
^
<xavierbot>
This expression has type int but is here used with type int64
<jcpiza>
i don't understand it, it does well in my ocaml 3.10.0
<pango>
why do you insist in using non-tailrec calls and a quadratic algorithm?
<pango>
xavierbot: restart
<xavierbot>
Objective Caml version 3.10.0
<xavierbot>
Camlp4 Parsing version 3.10.0
<pango>
probably something funky with operators redefinition earlier
<pango>
let rec make_list x = if x = 0 then [] else make_list( x - 1 )@[x];;
<xavierbot>
val make_list : int -> int list = <fun>
<flux>
it might be possible to use Obj.magic trickery for that
<flux>
if not, the only other way (other from using that do-it-manually) would be to link in some C code..
<flux>
atleast this does _something_:
<fbvortex>
yeah, that's assuming you read it in a byte at a time, but I don't know how to coerce the bytes out of ocaml's float
<flux>
hm, actually, can't use the bot, it doesn't have Obj.magic
<fbvortex>
for the purposes of writing
<context>
mmm im starting to like ocaml
<flux>
let a = Array.create 8 '1' in (Obj.magic a : float)
<fbvortex>
context: it does kick some butt
<flux>
don't do that lightly, though.. it's evil :)
<context>
fbvortex: and it compiles to almost just as fast as gcc, thats what turned me on in the first place :D
<context>
its like, scripting at C like speed
<context>
:p
* context
hides in a deep dark corner
<flux>
better approach would be to use the approach in the post, I think, but its speed would be suboptimal..
<fbvortex>
flux: Obj.magic eh? Is there some place I can read more about it? BTW, I've programmed device drivers and machine-level code, I'm not averse to dirty low-level tricks if I know what I'm doing.
<flux>
fbvortex, nope
<context>
is there like (dare i say it) an eval function in caml
<flux>
fbvortex, Obj.magic basically is a cast 'a -> 'b
<flux>
fbvortex, I don't know how it interacts with the gc for instance, but that shouldn't be an issue here
<flux>
and the values need to be boxed in this case for it to work in this case; I'm not sure if the tag bit is different for float
<flux>
better read the chapter about c-interfacing
<fbvortex>
flux: I've not used mutable arrays yet, so I'm not familiar with the syntax, but wouldn't it make more sense to turn it into 8 string characters?
<flux>
fbvortex, perhaps, but I think that strings store their length in the first word. I'm not sure where the arrays store their lengths.
<flux>
fbvortex, it might be that approach is really not feasible due to that issue
<flux>
however, perhaps it would work via Bigarrays
<fbvortex>
ugh. this seems like an oversight
<flux>
infact Bigarrays might provide some more safe means of casting between different representations
<fbvortex>
are bigarrays built-in?
<flux>
yes
<flux>
actually I think some ocaml library might have binary float capabilities
<flux>
but, I'll be moving off from irc now, good luck with your float access attempts..
<context>
hmm
<fbvortex>
quick question
<context>
can module's be reopened, like in ruby
<fbvortex>
this mentions that extlib tries to replace some standard functions "to modify some functions in order to get better performances or more safety " -- do you know if it overrides any of the built-ins?
<fbvortex>
flux: Looks like you've already gone. Thanks a lot for the help.
Proteus has joined #ocaml
ertai has joined #ocaml
b00t has joined #ocaml
Tetsuo has joined #ocaml
ertai has quit [Read error: 104 (Connection reset by peer)]
filp has joined #ocaml
Tetsuo has quit [Remote closed the connection]
<flux>
I don't think extlib does anything particularly nasty. It can only affect code that is compiled with its modules. The extlib module names just happen to be the same as the standard, so if you enter open Extlib, you'll have a new List-module
<flux>
(actually extlib does do some nastry tricks when it makes for example List.map tail recursive)
rwmjones has joined #ocaml
smimou has joined #ocaml
ygrek has quit [Remote closed the connection]
Yoric[DT] has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
Yoric[DT] has quit [Read error: 110 (Connection timed out)]
Anarchos has joined #ocaml
<Anarchos>
hello everybody
<Anarchos>
i donwloaded the latest version of the compiler, unfortunately itstops on an error 'multiple targets' in the unix folder :(
<Anarchos>
how can i overcome that ?
asmanur has joined #ocaml
b00t has quit [Remote closed the connection]
<context>
anarchos: your distro doesnt have a pakcage for it ?
hkBst has joined #ocaml
asmanur has quit [Remote closed the connection]
Associat0r has quit []
asmanur has joined #ocaml
Mr_Awesome has quit [calvino.freenode.net irc.freenode.net]
opening has quit [calvino.freenode.net irc.freenode.net]
acatout has quit [calvino.freenode.net irc.freenode.net]
mbishop has quit [calvino.freenode.net irc.freenode.net]
sadmac has quit [calvino.freenode.net irc.freenode.net]
tsuyoshi has quit [calvino.freenode.net irc.freenode.net]
cygnus_ has quit [calvino.freenode.net irc.freenode.net]
Demitar has quit [calvino.freenode.net irc.freenode.net]
Anarchos has quit [calvino.freenode.net irc.freenode.net]
jcpiza has quit [calvino.freenode.net irc.freenode.net]
|Catch22| has quit [calvino.freenode.net irc.freenode.net]
ecc has quit [calvino.freenode.net irc.freenode.net]
dibblego has quit [calvino.freenode.net irc.freenode.net]
filp has quit [calvino.freenode.net irc.freenode.net]
mrsolo has quit [calvino.freenode.net irc.freenode.net]
RobertFischer has quit [calvino.freenode.net irc.freenode.net]
xavierbot has quit [calvino.freenode.net irc.freenode.net]
zmdkrbou has quit [calvino.freenode.net irc.freenode.net]
netx has quit [calvino.freenode.net irc.freenode.net]
Sparkles has quit [calvino.freenode.net irc.freenode.net]
smimou has quit [calvino.freenode.net irc.freenode.net]
rwmjones has quit [calvino.freenode.net irc.freenode.net]
kmeyer has quit [calvino.freenode.net irc.freenode.net]
jeremiah has quit [calvino.freenode.net irc.freenode.net]
gunark has quit [calvino.freenode.net irc.freenode.net]
context has quit [calvino.freenode.net irc.freenode.net]
fbvortex has quit [calvino.freenode.net irc.freenode.net]
cmeme has quit [calvino.freenode.net irc.freenode.net]
pattern has quit [calvino.freenode.net irc.freenode.net]
jdavis_ has quit [calvino.freenode.net irc.freenode.net]
unfo- has quit [calvino.freenode.net irc.freenode.net]
Smerdyakov has quit [calvino.freenode.net irc.freenode.net]
jsk has quit [calvino.freenode.net irc.freenode.net]
jlouis has quit [calvino.freenode.net irc.freenode.net]
rogo has quit [calvino.freenode.net irc.freenode.net]
Oatskool has quit [calvino.freenode.net irc.freenode.net]
seafood has quit [calvino.freenode.net irc.freenode.net]
mattam has quit [calvino.freenode.net irc.freenode.net]
richardw has quit [calvino.freenode.net irc.freenode.net]
bebui has quit [calvino.freenode.net irc.freenode.net]
__suri has quit [calvino.freenode.net irc.freenode.net]
pippijn has quit [calvino.freenode.net irc.freenode.net]
hkBst has quit [Remote closed the connection]
hkBst has joined #ocaml
cygnus_ has joined #ocaml
Demitar has joined #ocaml
Mr_Awesome has joined #ocaml
opening has joined #ocaml
acatout has joined #ocaml
mbishop has joined #ocaml
sadmac has joined #ocaml
tsuyoshi has joined #ocaml
Anarchos has joined #ocaml
jcpiza has joined #ocaml
|Catch22| has joined #ocaml
dibblego has joined #ocaml
ecc has joined #ocaml
smimou has joined #ocaml
rwmjones has joined #ocaml
kmeyer has joined #ocaml
jeremiah has joined #ocaml
gunark has joined #ocaml
context has joined #ocaml
fbvortex has joined #ocaml
cmeme has joined #ocaml
pattern has joined #ocaml
jdavis_ has joined #ocaml
Smerdyakov has joined #ocaml
unfo- has joined #ocaml
jsk has joined #ocaml
jlouis has joined #ocaml
pippijn has joined #ocaml
__suri has joined #ocaml
seafood has joined #ocaml
Oatskool has joined #ocaml
rogo has joined #ocaml
bebui has joined #ocaml
richardw has joined #ocaml
mattam has joined #ocaml
filp has joined #ocaml
mrsolo has joined #ocaml
RobertFischer has joined #ocaml
xavierbot has joined #ocaml
zmdkrbou has joined #ocaml
netx has joined #ocaml
Sparkles has joined #ocaml
ertai has joined #ocaml
seafood_ has quit []
petchema_ has joined #ocaml
<petchema_>
context: there's no compiler or interpreter or the language at runtime... In fact, almost all typing information is lost after compilation too
<flux>
context, not really opened, but you can do this: module Foo = struct include Foo let additional_foo = 42 end
<flux>
context, note that that has zero effect on other modules using module Foo
<flux>
but it can be sometimes seen, for example in the context of adding a function to List or Set-modules (or especially modules that result from using the Set.Make functor)
buluca has quit [Read error: 113 (No route to host)]
Snark has joined #ocaml
buluca has joined #ocaml
Yoric[DT] has joined #ocaml
dbueno has joined #ocaml
<Yoric[DT]>
hi again
ttamttam has joined #ocaml
asmanur has quit [Read error: 110 (Connection timed out)]
dbueno has quit ["This computer has gone to sleep"]
Tetsuo has joined #ocaml
madroach has joined #ocaml
buluca has quit [Read error: 110 (Connection timed out)]
mrsolo has quit ["Leaving"]
asmanur has joined #ocaml
ertai has quit [Read error: 110 (Connection timed out)]
asmanur_ has joined #ocaml
ygrek has joined #ocaml
Yoric[DT] has quit [Read error: 110 (Connection timed out)]
asmanur has quit [Read error: 110 (Connection timed out)]
l_a_m has quit [Remote closed the connection]
dbueno has joined #ocaml
ertai has joined #ocaml
madroach has quit [Remote closed the connection]
dbueno has quit ["This computer has gone to sleep"]
dbueno has joined #ocaml
dbueno has quit [Client Quit]
ttamttam has left #ocaml []
pango has quit [Remote closed the connection]
marmottine has joined #ocaml
Yoric[DT] has joined #ocaml
rogo has quit [Read error: 110 (Connection timed out)]
pango has joined #ocaml
Jeff_123 has joined #ocaml
<Anarchos>
i donwloaded the latest version of the compiler, unfortunately itstops on an error 'multiple targets' in the unix folder :(
<Jeff_123>
strange
<Anarchos>
line 43 of Makefile.shared
<hcarty>
Anarchos: What OS?
<Anarchos>
hcarty : BeOS
<hcarty>
I haven't worked under BeOS before, and I don't know what the OCaml support is like
<hcarty>
Not to sound condescending, but have you followed each of the steps in the INSTALL file? There are a few items beyond the normal ./configure && make && make install
<Anarchos>
it is perfect i am able to recompile the entire os since ocaml 3.06
<hcarty>
That bit me when I first tried to build from source directly
<hcarty>
Ah, ok
<Anarchos>
hcarty i used ./configure --prefix ~/config -no-shared-libs
<hcarty>
And then make world?
<Anarchos>
yes
<hcarty>
Then my apologies - I don't know enough about the OCaml build process or internals to help. Hopefully someone else can.
ygrek has quit [Remote closed the connection]
<Anarchos>
no pbm
ygrek has joined #ocaml
yakker has joined #ocaml
<Anarchos>
who is using ocaml at work ?
<yakker>
in ocamllex, how does one compose token streams? say if you have 1 rule calling another?
Jeff_123 has quit [Read error: 104 (Connection reset by peer)]
<Anarchos>
yakker just put the name of one rule inside another, i guess ?
Jeff_123 has joined #ocaml
<yakker>
Anarchos: right, which is what i'm doing, but how to compose the output of the inside rule with the output of the current one?
<Anarchos>
you have the 'as' keyword also : rule2 as ident
<yakker>
hm. i don't see how that helps here.
<Yoric[DT]>
Anarchos: depends on what you call work, but I probably do.
<Anarchos>
yakker you can call recursively a rule in another like you diid in rule2
<Anarchos>
Yoric[DT] well in the activity you do to earn money on a regularly basis ;)
<yakker>
Anarchos: yes, but my question is how to prepend the output of the current rule
<yakker>
to the token stream, when you call the other rule recursively
<yakker>
eg. say i have 2 languages - like say html and php, where 1 is nested in the other
<Anarchos>
yakker i see
<Anarchos>
maybe special functions on lexbuf ?
<yakker>
Anarchos: yes, that's what i was looking for
<yakker>
although what I'll probably do for now is to have an explicit marker that goes either way
bluestorm has joined #ocaml
<yakker>
since the marker is associated with an empty token
<yakker>
so that solves my problem.
<yakker>
i'd like to figure out how to do it the right way though
<Anarchos>
yakker i would use two lexbufs for myself
<yakker>
Anarchos: how do you use 2 lexbufs?
<Yoric[DT]>
Anarchos: I do :)
<Anarchos>
juste define another in your ocaml prelude
<Anarchos>
Yoric[DT] PhD ?
<Yoric[DT]>
But I'm a researcher, so my criteria don't necessarily apply to other people.
<Anarchos>
yakker and when you define your action, juste choose the lexbuf you want
<Anarchos>
Yoric[DT] that is ok to be a researcher !
<jonafan>
are you an anarchist
yakker has quit []
<Anarchos>
jonafan yes but if you want to ask questions, it is not the good channel ;)
Demitar has quit [Read error: 110 (Connection timed out)]
<jonafan>
i don't want to go fight with anarchists
<jonafan>
i only want to know what kind of anarchist you are
<jonafan>
a quiet anarchist
* jonafan
writes something in his notebook
ertai has quit [Read error: 110 (Connection timed out)]
ygrek has quit [Remote closed the connection]
<Anarchos>
jonafan i answered to you in private
<jonafan>
oh, you're not registered so i didn't get it
<jonafan>
hold on
<jonafan>
okay
<Anarchos>
jonafan okay
bluestorm has quit ["Konversation terminated!"]
ygrek has joined #ocaml
<Anarchos>
Yoric[DT] what is your area of research ?
<Yoric[DT]>
Semantics.
<Yoric[DT]>
Well, currently, application of semantics to system security.
<Anarchos>
ok :)
dbueno has joined #ocaml
* Yoric[DT]
needs to finish his blog entry about LRU.
dbueno has quit ["This computer has gone to sleep"]
filp has quit ["Bye"]
petchema_ has quit [Read error: 104 (Connection reset by peer)]
asmanur_ has quit [Read error: 110 (Connection timed out)]
bluestorm has joined #ocaml
CRathman has joined #ocaml
dbueno has joined #ocaml
Yoric[DT] has quit [Read error: 113 (No route to host)]
zmdkrbou has quit [Read error: 113 (No route to host)]
<pango>
Anarchos: using OCaml at work for statistics, prototypes, simulations, benchmarks...lots of throw away code, because nobody else needs to modify the code, so I have to choice of the language (sadly for now I'm the only one using OCaml)
cygnus_ has quit [calvino.freenode.net irc.freenode.net]
cygnus_ has joined #ocaml
bluestorm has quit [Remote closed the connection]
ttamtta1 has joined #ocaml
ttamtta1 has left #ocaml []
ttamttam has joined #ocaml
fbvortex has quit [Read error: 110 (Connection timed out)]
ttamttam has left #ocaml []
bongy has joined #ocaml
qpu has joined #ocaml
buluca has joined #ocaml
yakker has joined #ocaml
filp has joined #ocaml
Snark has quit ["Quitte"]
Anarchos has quit [Read error: 104 (Connection reset by peer)]
qpu has quit []
yakker has left #ocaml []
bongy has quit [Read error: 110 (Connection timed out)]
buluca has quit [Read error: 113 (No route to host)]
buluca has joined #ocaml
ita has joined #ocaml
ygrek has quit [Remote closed the connection]
filp has quit ["Bye"]
marmottine has quit ["Quitte"]
DerDracle has joined #ocaml
<pippijn>
DerDracle: binary tree structures in a line?
<DerDracle>
pippijn, type binary_tree = Leaf of int | Tree of binary_tree * binary_tree;;
<xavierbot>
Characters 0-7:
<xavierbot>
pippijn, type binary_tree = Leaf of int | Tree of binary_tree * binary_tree;;
<xavierbot>
^^^^^^^
<xavierbot>
Unbound value pippijn
Yoric[DT] has joined #ocaml
<DerDracle>
Lol, Oops.
<flux>
;; is evil here ;)
<pippijn>
hmm
<DerDracle>
flux, Yeah ;)
<pippijn>
okay that looks nice
<Yoric[DT]>
hi again
<DerDracle>
pippijn, Essentially, you can define a data structure, that refers to itself very easily.
<pippijn>
that's nice
<DerDracle>
pippijn, And then defining subsequent tree structures is very simple too: Tree( Leaf 3, Leaf 4);;
<xavierbot>
type pippijn
<xavierbot>
Characters 8-9:
<xavierbot>
Parse error: illegal begin of top_phrase
<DerDracle>
Agh :p
<DerDracle>
My brain puts them in automagically.
<pippijn>
what is ;;?
<DerDracle>
pippijn, Essentially, an entire ocaml program can be defined in a single expression , and double semicolons will terminate that expression.
<pippijn>
I see
<pippijn>
does ocaml have "statements"?
<DerDracle>
pippijn, Well, all functions return a value.
<pippijn>
i.e. expressions without value
<flux>
it does have top level statements
<pippijn>
in c, "if (a < b)" does not return a value
<flux>
let a = 42 doesn't have a value
<pippijn>
it is a statement
<DerDracle>
pippijn, But it has a concept of () -> unit, which is basically an empty value.
<flux>
(but you can only say that in the top level)
<flux>
the fact can be obscured by the toplevel, though
<pippijn>
DerDracle: is ocaml pure by default?
<flux>
let a = 42 ;;
<xavierbot>
val a : int = 42
<flux>
so it gives its interpretation of what happened: a value was defined
<pippijn>
I would like to see a language that has syntactic annotations for purity
<flux>
pippijn, ocaml is not pure by default. the only languages I know of that are are haskell and clean.
<DerDracle>
You can say something like let a = 5 in let x v = a + v in x 5
<pippijn>
I think sisal is pure
<pippijn>
there are some other tiny languages that are pure
<pippijn>
Q for example
<DerDracle>
pippijn, Not by default. Most ocaml programs employ a mixture of imperative, object oriented, and functional.
<pippijn>
are there syntactic annotations that denote pure functions?
<flux>
no
<DerDracle>
Hm, you don't syntatically declare a function pure, if that's what you're asking.
<pippijn>
in C, there are no pure functions but there is the const keyword that somewhat declares that the function doesn't modify its argument
<flux>
perhaps I should clarify: haskell or clean don't have impure functions at all (io is a matter that is handled while preserving purity)
<DerDracle>
pippijn, Right- you should know const can be easily worked around though.
<pippijn>
yes, using the IO monad
<pippijn>
DerDracle: I know
<pippijn>
DerDracle: const is nothing but a hint to the programmer, really
<flux>
clean has unique types, which address the problem somewhat differently
<flux>
but I haven't even seen any clean code
<pippijn>
it says "strlen doesn't destroy your string"
<pippijn>
flux: I have and it looks like haskell
<DerDracle>
pippijn, My like of Ocaml is- it has probably one of the best programming books I've ever read written for it.
<pippijn>
I think clean and haskell are pretty much isomorphic
<flux>
I hear there used to be a converted from clean to haskell or vice versa
<DerDracle>
pippijn, Maybe you're biased by how poor these books tend to be.
<DerDracle>
pippijn, This is 'very' project oriented.
<pippijn>
that's true
<pippijn>
DerDracle: what do you use ocaml for?
<DerDracle>
pippijn, Lots of things. I've used it a couple of times to write some simple servers/proxies.
<DerDracle>
pippijn, I don't use it very much for anything dealing with UI. But it has a nice threading library. And I use it for making simple compilers/interpreters if I want to write them by hand rather than generate them.
<pippijn>
DerDracle: how easy is it to use C from ocaml?
<DerDracle>
pippijn, One sec, there's a section of this book on it.
<pippijn>
I don't do UIs, really
<pippijn>
I write compilers, parsers, protocol analysers, etc..
<DerDracle>
pippijn, external caml name : type = "C name"
<pippijn>
DerDracle: which does.. what?
<DerDracle>
pippijn, Basically, makes a caml type that is externally declared in a c object file.
<Yoric[DT]>
s/type/value/
<pippijn>
hm
<DerDracle>
Right.
<DerDracle>
pippijn, value plus_bytecode (value * tab_val, int num_val) becomes ->
<pippijn>
external plus : int -> int -> int -> int -> int -> int -> int = "plus_bytecode" "plus_native" ;;
<xavierbot>
'external' keyword disabled
<xavierbot>
- : unit = ()
<pippijn>
DerDracle: what does this one mean?
<pippijn>
ah
<pippijn>
hm
<pippijn>
okay, I want to test that
<DerDracle>
pippijn, So, you see the example?
<pippijn>
yes
<DerDracle>
pippijn, And the part after the : defines the arity and arguments of the value.
<pippijn>
what is the difference between plus_bytecode and plus_native?
<DerDracle>
pippijn, These are normally inferred.
<pippijn>
External identifiers must be functions
<pippijn>
ah hm..
<DerDracle>
pippijn, One sec trying to understand the example myself :p
<DerDracle>
pippijn, It's been a while ;)
<pippijn>
DerDracle: what if I have a C library that contains a function named "func"
<pippijn>
DerDracle: do I have to write ocaml wrapper code for it?
<pippijn>
Yoric[DT]: nice, is there a document on that?
<pippijn>
ah
<pippijn>
oh
<pippijn>
swig :|
<DerDracle>
Right, I've used swig with ocaml a bit.
<Yoric[DT]>
I haven't tried it, mind you.
<pippijn>
I have tried swig with perl
<pippijn>
I got rid of it fast
<DerDracle>
I haven't done a great deal of Ocaml -> C binding.
<pippijn>
DerDracle: if I were to learn ocaml, I would often do it
<pippijn>
I love mixing languages :-)
<DerDracle>
pippijn, But, if you look in this book, they have a least cost path example, a calculator program, a basic interpreter.
<pippijn>
each one used for what it's good at
<DerDracle>
pippijn, I haven't gotten all the way through it to this day- but I have to say, it is one of the most complete programming books I have 'ever' read.
<pippijn>
hmm
<pippijn>
my first ocaml program:
<pippijn>
print_int (1);;
<pippijn>
print_newline ();;
<xavierbot>
1- : unit = ()
<xavierbot>
- : unit = ()
<pippijn>
pippijn@osiris ocaml $ ocaml test.ml
<pippijn>
1
<pippijn>
:)
<Yoric[DT]>
Congratulations :)
<pippijn>
thanks ;)
<Yoric[DT]>
You can drop the parenthesis around the 1, btw.
<pippijn>
nice
<pippijn>
but not the newline
<pippijn>
that one needs it
<pippijn>
why?
<Yoric[DT]>
() is actually a value
<DerDracle>
pippijn, So it can tell it is a function.
<pippijn>
oh..
<Yoric[DT]>
();;
<xavierbot>
- : unit = ()
<pippijn>
int->int;;
<xavierbot>
Characters 1-4:
<xavierbot>
int->int;;
<xavierbot>
^^^
<xavierbot>
Unbound value int
<xavierbot>
Characters 4-6:
<xavierbot>
Parse error: illegal begin of top_phrase
<pippijn>
:|
<Yoric[DT]>
Nope, the toplevel doesn't like types.
<Yoric[DT]>
Only expressions.
<qwr>
print_newline;;
<xavierbot>
- : unit -> unit = <fun>
<pippijn>
print_newline();;
<xavierbot>
- : unit = ()
<pippijn>
hmm
<pippijn>
what is unit?
<DerDracle>
So, since you provided no parameters, it curries to unit -> unit (basically the same function)
<DerDracle>
Unit is just like, an empty parameter.
<pango>
unit is the type of ()
<DerDracle>
Right.
<qwr>
pippijn: type of the () thing - type that has only one possible value. somewhat like void.
<pippijn>
ah
qpu_ has joined #ocaml
<pippijn>
hm
<pippijn>
my girlfriend wants me to leave the pc.. and she has two good arguments
<pippijn>
1) it's 0:10
<pippijn>
2) tomorrow we got to get up early
<pippijn>
so good night :-)
<Yoric[DT]>
'night
<pippijn>
and thanks
* Yoric[DT]
deduces that pippijn connects from somewhere around France/Netherlands/Belgium/Italy/Germany.
<pippijn>
germany
<Yoric[DT]>
(or somewhere to the South, but that gets complicated :))
<Yoric[DT]>
Also gute Nacht.
<pippijn>
;-)
<pippijn>
gute nacht
<DerDracle>
Phew.. I've got to brush up a bit on my Ocaml.
wy has joined #ocaml
<wy>
What's the best way to use openGL in OCaml?
<Yoric[DT]>
I've used LablGL, it was fun.
<DerDracle>
Any good UI systems yet with Ocaml?
<wy>
Yoric[DT]: What's the ubuntu package name for it?
Tetsuo has quit [Read error: 104 (Connection reset by peer)]
<DerDracle>
Man the caml hump has changed.
<Smerdyakov>
DerDracle, I have one, but it's not released.
<DerDracle>
Smerdyakov, Looking forward to it :)
<DerDracle>
Smerdyakov, What is it based off of? Or is it 100% ocaml?
<Smerdyakov>
DerDracle, I'm going to play it safe and not say any more, since it's developed at my job and I don't have explicit permission to talk about it.
<wy>
Yoric[DT]: Do you know the package name?
<DerDracle>
Smerdyakov, Alright- no problem :)
CRathman has quit ["ChatZilla 0.9.79 [Firefox 2.0.0.11/2007112718]"]
wy has quit ["Ex-Chat"]
<qwr>
DerDracle: lablgtk2?
<DerDracle>
qwr, Ew.. Gtk..
<DerDracle>
qwr, But, thanks for the suggestion.
<qwr>
DerDracle: the ocaml interface is quite nice.
* qwr
uses linux anyway. on win it maybe looks funny. haven't tryed...
<DerDracle>
qwr: Yeah, I like the Ocaml interface- but, I'd like something more professional looking.
qpu_ is now known as qpu
<pango>
DerDracle: motif ?
<Smerdyakov>
qwr, the OCaml interface is horrible.
<Smerdyakov>
qwr, horribly in mostly the same way as Gtk itself, mind you, so faithful in that respect; but still horrible.
<DerDracle>
Smerdyakov, I look even more forward to seeing your library when it's released then.
* qwr
has once tried to use C gtk. that was horrible :P