cjeris changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/
<tsuyoshi> hey I have a question about this type variables in methods syntax
<tsuyoshi> for example:
<tsuyoshi> method set_property : 'a. string -> 'a Gobject.data_set -> unit
<tsuyoshi> why is the "'a." necessary?
<Nutssh> tsuyoshi, it means 'for all A, ......' Its used to make the type closed.
<tsuyoshi> so without the 'a., what happens? is it the same 'a for all the methods in a class?
jeberle has joined #ocaml
<Nutssh> It depends on the scoping. Without it, the type is ill-formed.
<Nutssh> You might get what you need easier through the module system. In my programming, I've rarely used ocaml's classes.
jeberle has left #ocaml []
<tsuyoshi> I've never written any classes, but I saw that in lablgtk, and it took me a while to figure out what it meant
<tsuyoshi> and then when I figured it out I was wondering.. "you can do it in regular procedures without that, so...?"
<Nutssh> Classes have a type system thats rather more complicated and messy. For that alone, I like to use them only when I need their features.
Foxyloxy has quit [Connection timed out]
jlouis__ has joined #ocaml
wren has joined #ocaml
<wren> Any lablgtk users about? I'm observing a rather strange error.
jlouis_ has quit [Read error: 110 (Connection timed out)]
G has joined #ocaml
<G> hmmm, .a .cma and .cmxa are all static ocaml libraries right?
wren has quit ["Leaving"]
<G> (or have I been misinformed?
<Smerdyakov> Those are the two library extensions, yes.
<Smerdyakov> Native code OCaml doesn't support dynamic loading.
<Smerdyakov> I expect that bytecode uses the same files for dynamic loading as static loading.
<G> so it has to be built using static libraries?
jacobian has quit [Read error: 110 (Connection timed out)]
Z4rd0Z has joined #ocaml
mbishop has joined #ocaml
pants1 has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has quit ["...and the Awesome level drops"]
love-pingoo has joined #ocaml
<tsuyoshi> wren: yeah I use lablgtk
<tsuyoshi> oh, he left
<Smerdyakov> G, _what_ has to be built using static libraries?
<tsuyoshi> g: yeah, ocaml is ordinarily all static
<tsuyoshi> a few people have gotten it to compile shared libraries.. their efforts haven't really seen any widespread use yet
Smerdyakov has quit ["Leaving"]
<G> tsuyoshi: okay I was looking for shared (Fedora is against building against static), thats all
<tsuyoshi> the ocaml runtime is a shared library iirc, but everything else is static
<tsuyoshi> I remember xavier leroy explaining the reasoning one time on the mailing list.. but I don't remember what he said exactly
<tsuyoshi> (he's the lead developer)
<G> Okay, well I've posted a message on fedora-packaging group, it may be possible to give ocaml based packages an exemption, I have no idea
<tsuyoshi> I'm surprised you don't have ocaml packages already
<G> There are
<G> (And i'm surprised that those people didn't spot it)
<tsuyoshi> oh.. but people are trying to get rid of them?
<G> well, I was packaging camlimages and ocamlsdl, and noticed it was producing static libraries, and when I packaged another program written in ocaml I thought it weird that ld etc came up clean
pstickne_ has quit [Connection reset by peer]
pstickne_ has joined #ocaml
joshcryer has joined #ocaml
G_ has joined #ocaml
<pango> ocaml natively compiled code is only linked statically... But ocaml programs can use dynamic libraries
<pango> $ echo 'let () = print_endline "Hello World!"' > hello.ml
<pango> $ ocamlopt -o hello hello.ml
<pango> $ ldd hello
<pango> linux-gate.so.1 => (0xffffe000)
<pango> libm.so.6 => /lib/tls/libm.so.6 (0x4b4de000)
<pango> libdl.so.2 => /lib/tls/libdl.so.2 (0x4b4d8000)
<pango> libc.so.6 => /lib/tls/libc.so.6 (0x4b3a4000)
<pango> /lib/ld-linux.so.2 (0x4b38b000)
<flux> there's always scaml. it's a shame it isn't in the main distribution - albeit this way it hasn't received much testing
G has quit [Read error: 110 (Connection timed out)]
G_ is now known as G
benny_ has joined #ocaml
love-pingoo has quit ["Connection reset by pear"]
benny has quit [Read error: 110 (Connection timed out)]
Z4rd0Z has quit [Read error: 110 (Connection timed out)]
G_ has joined #ocaml
G has quit [Read error: 110 (Connection timed out)]
<flux> hmm.. is comparing 'a Weak.t with 'compare' a stable function?
<flux> hm, s/stable/pure/
<flux> I'm thinking: what happens if I use that as a key to a map
<flux> actually, that might not make sense anyway.. how would one search such map..
G has joined #ocaml
fezsentido has quit [Read error: 54 (Connection reset by peer)]
G_ has quit [Read error: 110 (Connection timed out)]
love-pingoo has joined #ocaml
smimou has joined #ocaml
<G> pango, flux: thanks for the comments, I'll look into them
jer has quit [Read error: 131 (Connection reset by peer)]
<flux> looking the continuation io framework it really makes me thing syntax candy would be nice
<flux> infact I think it could look just like the one for monads
<flux> perform a <- register_read_fd fd; b <- register_write_fd; pause [a; b]; let v = random () ..
<flux> maybe I could lift the code from pa_monad..
<flux> (that would be like: register_read_fd fd (fun a -> register_write_fd (fun b -> pause [a; b] (fun () -> let v = random () .. )
jer has joined #ocaml
Demitar has joined #ocaml
smimou has quit ["bli"]
jer has quit [Read error: 145 (Connection timed out)]
malc_ has joined #ocaml
<mrvn> flux: I always made my FD structure know if it was registered or not and the write function to register when needed.
jer has joined #ocaml
Smerdyakov has joined #ocaml
jacobian has joined #ocaml
Ai_Itai has joined #ocaml
pango has quit [Remote closed the connection]
nuncanada has joined #ocaml
pango has joined #ocaml
love-pingoo has quit ["Leaving"]
screwt8 has joined #ocaml
Go4005 has joined #ocaml
<Go4005> i might be using ocaml for a commerical project ......is ocaml the only compiler ?
<flux> yes
<flux> mrvn, does that give you performance or nicer structure or what?-)
<Go4005> also is ocaml still being developed on .........if everything goes through i am sure my boss wouldnt be wanting closer connections with the language he likes it alot so far
<flux> ocaml is still being developed, by a french research group (inria.fr)
<flux> if you want vendor-independence, sml might be interesting
<Go4005> any plans for more optimization or a gcc frontendd ......etc ?
<flux> it doesn't provide all the things ocaml does, but then again, perhaps you don't miss them
<flux> I haven't heard of such plans
<flux> (but I don't subscribe to the caml mailing list - however those things don't sound very likely)
smimou has joined #ocaml
<flux> hm, is there a cpu performance counter library for ocaml? or for linux, even
<mrvn> flux: easier functionality. I (the app) don't have to care about whether the write would block or about buffering. I just call IO.write fd buf and it writes as much as possible directly, buffers the rest (if any) and adds the fd to the wait queue until the buffer got written. Then it removes the fd automatically.
<mrvn> If you use selcet you have the probblem that there is no edge trigger.
<mrvn> flux: Mostly people use inline asm. The library call could skew the counter.
<mrvn> s/could/would/
<flux> yes, but not surprisingly
malc__ has joined #ocaml
malc_ has quit [Read error: 110 (Connection timed out)]
postalchris has joined #ocaml
cjeris has joined #ocaml
postalchris has quit [Remote closed the connection]
postalchris has joined #ocaml
postalchris has quit [Remote closed the connection]
postalchris has joined #ocaml
postalchris has quit [Client Quit]
malc__ has quit ["leaving"]
postalchris has joined #ocaml
postalchris has quit [Remote closed the connection]
postalchris has joined #ocaml
postalchris has quit [Remote closed the connection]
postalchris has joined #ocaml
Demitar has quit [Read error: 113 (No route to host)]
descender is now known as code-janitor
slipstream-- has joined #ocaml
slipstream has quit [Success]
postalchris has quit [Remote closed the connection]
postalchris has joined #ocaml
<Go4005> anyone here familiar with nix ?
<flux> are there any wrappers for libevent for ocaml are actually used?
<Go4005> yea i used libevent once
<flux> I've found three somewhat critical bugs from ocaml-events - fortunately the author is still around
<Go4005> although i ended up jus using poll casue it was only 1 connection
<flux> (actually two critical, one medium bug)
<Go4005> worked for me but i jus did something very simple
<flux> the simplest test cases work
<Go4005> flux: do you know how i can see all connection ......in nix ?
<Go4005> i havent worked with iptables at all really
<flux> netstat -t
<flux> iptables also has its state table under /proc.. /proc/net, or /proc/sys/net
flux- has joined #ocaml
flux has quit [Read error: 104 (Connection reset by peer)]
nuncanada has quit ["Leaving"]
Demitar has joined #ocaml
<Go4005> will thier even be a gcc front end for ocaml ?
<postalchris> You mean a parser from OCaml to GCC IR or a parser from C to an OCaml IR?
<Go4005> i mean
<postalchris> (for C read: C/C++/Java/Fortran, any GCC input lang)
<Go4005> a way so ocaml would be better optimized
<Go4005> and run faster
<postalchris> You're begging the question there.
<postalchris> That's a good question, though. I don't know if GCC's back-end is particularly well suited to optimizing OCaml
<Go4005> would be cool
<Go4005> ocaml is about half the optimization as gcc atm i think
<flux-> llvm-backend for ocaml would be interesting
nuncanada has joined #ocaml
<Go4005> ocaml is becoming my favorte language
<Go4005> that and lua
<mrvn> juhey, another one converted.
<mrvn> postalchris: ocaml is pretty easy to transform to single assignment notation or cps or whatever you want.
<flux-> apparently some students are doing an ocaml-frontend for llvm
<Go4005> llvm ?
<flux-> perhaps within a year we'll see some results.. or not
<flux-> a virtual machine framework
<Go4005> i think a nice gcc fornt end would be good
<Go4005> nothing beats ocaml or lua
jer has quit [Read error: 145 (Connection timed out)]
<mrvn> Lets write a ocaml to C compiler. That ought to be simple.
<mrvn> or rather c++ for the objects.
<pango> C is a bad backend, that's why they started C-- ;)
<mrvn> C is a generic assembler.
<flux-> mrvn, how would the tail-call be compiled?
<pango> not good enough
<mrvn> flux-: goto
<flux-> mrvn, between functions?
<mrvn> flux-: return fn(); let gcc do tail recursion
<flux-> I think gcc doesn't do tail recursion optimization in all cases
<flux-> in any case, it wouldn't be standard C anymore
<mrvn> tail recursion or not is just an optimisation so you don't run out of stack space.
<mrvn> Doesn't make it any less C
<flux-> that's right, C doesn't define lots of things
malc_ has joined #ocaml
<flux-> it's just that a program that should run indefinitely, wouldn't
<flux-> (with constant resources too)
<Go4005> anyone here ever use scheme ?
<mbishop> anyone here read PLP2e?
<mrvn> flux-: If gcc fails to use tail recursion where appropriate then that should be fixed in gcc.
<mrvn> "Research on C-- and Quick C-- is supported by a generous gift from Microsoft Research" Thanks but no thanks.
<mbishop> er, why?
<mbishop> MSR does good work
<mbishop> in fact, MSR is a member of INRIA's ocaml consortium or whatever
<mrvn> Luckily with a bunch of others
<mrvn> c-- seems to use LUA
<mbishop> MSR also contributes to GHC a lot
<mrvn> "As of now, Quick C-- emits
<mrvn> code for the architectures x86, Alpha, MIPS, PPC, and I64 where code
<mrvn> generation for x86 is the most mature."
<mrvn> So it supports <obsolete>, <obsolete>, <obsolete except for router>, <don't have one> and <obsolete>
<flux-> mrvn, can gcc handle tail calls across differenet compilation units_
<flux-> ?
<mrvn> flux-: I don't see why that should make a difference. Any "return fn()" should become a tail call or not?
<malc_> mrvn: dude cool off, MIPS is the most used cpu out there, PPC is the thing in all the current gen consoles
<malc_> only alpha is really obsolete
<mrvn> malc_: mips32 is used in routers, mips64 is the high end one
<mrvn> mips being mips32
<flux-> right, it doesn't :)
<Go4005> my boss really likes ocaml
<Go4005> i think he will donate alot of money
<mrvn> malc_: you want at least support for mips N32 abi insted of O32.
<flux-> but, I'm off to sleep, good night..
<mrvn> malc_: and if you didn't notice, ppc is the <don't have one>.
<malc_> mrvn: well.. i do
<mrvn> malc_: 64bit capable?
<malc_> no
<malc_> come to think of it i even have mips right here on the table, and it aint no router
<mrvn> WAH, they do a nightly build so every night they checkin the "src/DATE" file which adds a changelog entry.
<mrvn> malc_: Indigo or better?
<malc_> mrvn: or better, ps2
<mrvn> That is mips64 too I believe.
<mrvn> anyway, they need amd64 support or it is completly worthless for me.
<malc_> amd64 aka the ISA from hell
<malc_> everyone is free to pick their poison ofcourse
<mrvn> the cheap fast ugly cpu basicaly everyone has nowadays
<mrvn> I can afford it, I don't have to like it. :)
<malc_> out of 5 computers around one is indeed x2..
<malc_> noisy and rarely used one at that
<mrvn> I would love a Mips laptop but where do you get one?
<malc_> naturally you solder it yourself
<mrvn> I have slight problems soldering 8 layer motherboards :)
<Go4005> why do you want a mips processor ?
<Go4005> btw can ocaml be used on embdedded machines ?
<mrvn> Go4005: energy consumption and beauty.
<mrvn> Go4005: if you write a loader for it and the compiler or interpreter works.
<Go4005> has anyone wrote one ? :P
<mrvn> A lot of embedded devices nowadays are mips or arm and can run linux.
<Go4005> how about lik a microcontroller :P
<mrvn> Write a compiler, build the runtime, have fun
<Go4005> i was kidding
<Go4005> i would us an embedded system
<Go4005> i woud use a SoC
<Go4005> i will get like a 1 ghz soc
<Go4005> put linux and compile ocaml and lua for it
RLa has joined #ocaml
<Go4005> where can i buy a SoC?
<RLa> SoC?
<Go4005> system on chip
<mattam> Summer of Code, Separation of Concerns too...
<mattam> But none are buyable :)
<RLa> how powerful system you need
<Go4005> i mean 700 mhz
<Go4005> or something
<malc_> Shadow Of the Colossus
<RLa> that says too few
<Go4005> i wonder where i could buy them
<Go4005> also
<Go4005> i cant find where to buy none of this
cjeris has quit [Read error: 104 (Connection reset by peer)]
nuncanada has quit ["Leaving"]
screwt8 has quit [Read error: 104 (Connection reset by peer)]
dbueno has joined #ocaml
<dbueno> Anyone know how to get ocamldebug to recognise custom printers for Big_int.big_int?
dbueno has quit [Client Quit]
dbueno has joined #ocaml
<pango> dbueno: since I din't use Format before, the code is probably not optimal, but it works
<pango> the printer function for type t must be of type Format.formatter -> t -> unit
RLa has quit ["Leaving"]
smimou has quit ["bli"]
postalchris has quit ["Leaving."]
<dbueno> Pango: thank you.
<pango> np
<dbueno> Turns out I wasn't linking properly with the bignum library; ocamldebug was complaining about not being able to find "Big_int"
<pango> yes, and you must load nums.cma with load_printer, too... The information is out there, but not readily available, I had to use several information sources
<dbueno> Ah, I didn't even notice that. Thank you for your research.
<dbueno> (I'm using ocamlfind, and was able to find some options to pass to that to get my .cma to link properly with the modules necessary.)
screwt8 has joined #ocaml
pango is now known as pangon8
dbueno has quit ["This computer has gone to sleep"]