gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Remote host closed the connection]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Remote host closed the connection]
lamawithonel__ has joined #ocaml
lamawithonel has joined #ocaml
lamawithonel__ has quit [Ping timeout: 250 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Remote host closed the connection]
lamawithonel_ has joined #ocaml
lamawithonel has quit [Ping timeout: 255 seconds]
lamawithonel__ has joined #ocaml
lamawithonel_ has quit [Remote host closed the connection]
lopex has quit []
Reaganomicon has joined #ocaml
lamawithonel has joined #ocaml
lamawithonel__ has quit [Ping timeout: 255 seconds]
lamawithonel_ has joined #ocaml
sepp2k has quit [Quit: Leaving.]
lamawithonel has quit [Ping timeout: 255 seconds]
lamawithonel__ has joined #ocaml
alfa_y_omega has quit [Ping timeout: 240 seconds]
lamawithonel_ has quit [Ping timeout: 255 seconds]
lamawithonel has joined #ocaml
lamawithonel__ has quit [Ping timeout: 255 seconds]
alfa_y_omega has joined #ocaml
lamawithonel has quit [Ping timeout: 255 seconds]
nannto_ has quit [Quit: Leaving...]
lamawithonel has joined #ocaml
nannto_ has joined #ocaml
<NaCl> lwt! how dare you make be buffer strings!
nannto_ has quit [Read error: Connection reset by peer]
nannto_ has joined #ocaml
impy has quit [Read error: No route to host]
bzzbzz has joined #ocaml
alexyk has joined #ocaml
joewilliams_away is now known as joewilliams
joewilliams is now known as joewilliams_away
larhat has joined #ocaml
vivanov has joined #ocaml
mfp has quit [Ping timeout: 255 seconds]
ankit9 has joined #ocaml
mfp has joined #ocaml
alexyk_ has joined #ocaml
alexyk has quit [Ping timeout: 255 seconds]
alexyk_ is now known as alexyk
ygrek has joined #ocaml
alexyk has quit [Quit: alexyk]
ygrek has quit [Ping timeout: 250 seconds]
edwin has joined #ocaml
ygrek has joined #ocaml
ygrek has quit [Remote host closed the connection]
jamii has quit [Ping timeout: 244 seconds]
f[x] has joined #ocaml
ankit9 has quit [Quit: Leaving]
Cyanure has joined #ocaml
philtor has quit [Ping timeout: 240 seconds]
Cyanure has quit [Remote host closed the connection]
galaad has joined #ocaml
ankit9 has joined #ocaml
ygrek has joined #ocaml
lamawithonel has quit [Ping timeout: 255 seconds]
ankit9 has quit [Quit: Leaving]
ankit9 has joined #ocaml
lamawithonel has joined #ocaml
eikke has joined #ocaml
ftrvxmtrx_ has quit [Quit: This computer has gone to sleep]
zorun has quit [Read error: Connection reset by peer]
zorun has joined #ocaml
sgnb has quit [Remote host closed the connection]
ikaros has joined #ocaml
othiym23 has quit [Quit: Linkinus - http://linkinus.com]
avsm has joined #ocaml
ftrvxmtrx has joined #ocaml
mfp has quit [Read error: Connection reset by peer]
BiDOrD_ has joined #ocaml
avsm has quit [Read error: Connection reset by peer]
BiDOrD has quit [Ping timeout: 240 seconds]
avsm has joined #ocaml
sgnb has joined #ocaml
mfp has joined #ocaml
sgnb has quit [Remote host closed the connection]
sgnb has joined #ocaml
mfp has quit [Read error: Connection reset by peer]
lopex has joined #ocaml
mfp has joined #ocaml
_andre has joined #ocaml
hyperboreean has quit [Ping timeout: 252 seconds]
ikaros has quit [Quit: Ex-Chat]
ttblrs_ has quit [Ping timeout: 240 seconds]
ttblrs has joined #ocaml
lewis1711 has joined #ocaml
dnolen has joined #ocaml
Cyanure has joined #ocaml
Cyanure has quit [Remote host closed the connection]
Cyanure has joined #ocaml
lamawithonel has quit [Remote host closed the connection]
fraggle_laptop has joined #ocaml
_andre has quit [Ping timeout: 244 seconds]
_andre has joined #ocaml
Modius has quit [Quit: "Object-oriented design" is an oxymoron]
_andre has quit [Ping timeout: 258 seconds]
_andre has joined #ocaml
palomer has joined #ocaml
<palomer> hey guys
<palomer> quick question: I'm doing some inter process communication
<palomer> via stdin/stdout
<palomer> I'm using select and input
<palomer> my current strategy: select, read as much as possible, select, ....
<palomer> the problem is that I can't seem to nail down the "read as much as possible" bit
<flux> how are you trying to do it?
<flux> are you using input_channel?
<palomer> input buf 0 (String.length buf)
<flux> if so, you're doing it wrong :)
<flux> due to internal buffering, it cannot work reliably
<flux> you need to use Unix.read/write etc
<flux> (well I suppose output_channel is fine, but might as well use Unix for symmetry)
<flux> an alternative is to frame your messages so that you will reliably know how much data is in the stream
<flux> for example, the messages could be fixed-length, or they could have a header that indicates the length of the message
<palomer> still doesn't solve the problem of several messages coming in
<flux> of course, this will result in the possibility of your process being blocked if the whole message isn't available immediately
<flux> how come?
<palomer> take two processes, A and B
<palomer> A sends 5 messages in a row to B
<palomer> if B uses Pervasve.input, how is it supposed to know that 5 messages are coming in?
<flux> actually now that I recalled the problem again, not even framing will solve the issue
<palomer> right
<palomer> I need some kind of non blocking read
<flux> so Unix.read is the only way to go
<palomer> however, another problem pops up
<flux> unix fds can be set up in non-blocking mode
<flux> and they don't do internal buffering, which is actually what messes this up
<palomer> isn't read non blocking by default?
<flux> well, it is, in part
<palomer> in part?
<flux> so it requires by default that atleast one byte is received
<flux> by default it otherwise waits until such byte is readable
<flux> in non blocking mode that requirement is lifted
<palomer> how do I put it in non blocking mode?
<flux> Unix.set_nonblock
<palomer> another question: let's say I do Unix.read (...); select (...)
<palomer> it's possible that the file descriptor was written to between the call to read and the call to select
<palomer> in which case select will not catch it
<flux> it will
<palomer> let's say I do Unix.read (...); sleep (10 years); select (...)
<flux> it will catch it regardless
<palomer> if anything happens during those 10 years, select will catch it?
<flux> if the fd is readable when select enters, select will return immediately
<palomer> so I can chain 2 selects in a row and it won't change anything?
<palomer> ignore(select (...)); let x = select (...) in ...
<flux> well, that's a different matter, because on some unixes you should handle all actionable fds that select says are actionable
<flux> I don't know if that holds true with any modern unix though
<flux> on linux it is safe
<palomer> let's say you handle them only partially
digimmortal has joined #ocaml
<palomer> so, what you're saying is that select checks if there's anything on the file descriptor's buffer. if there is, it returns the file descriptor
<palomer> right?
<flux> yes
<flux> you can easily verify this
<flux> Unix.sleep 10; Unix.select [Unix.stdin] [] [] 1000.0
<flux> if you enter a line prior Unix.select starting, it will return immediately.
<palomer> ok, let's test this out!
<palomer> (I'm running windows btw)
<palomer> how do I test it from the repl?
<flux> make sure unix.cmxa is loaded and then copy-paste that into repl with an additional ;; ?
<palomer> good point
<palomer> yeah, you're right
lamawithonel has joined #ocaml
lewis1711 has quit [Quit: Leaving.]
<palomer> Unix.set_nonblock (Unix.stdin) throws an exception
<flux> I guess windows support is limited
<flux> it doesn't matter in theory though, if you never read an FD that you can't guarantee has data
<palomer> Unix.read blocks though
<flux> ah
<flux> did you try that from toplevel?
<flux> was it Unix.set_nonblock that raised the error or the toplevel?
<flux> because the buffered input functions don't support nonblocking io
<palomer> toplevel = repl?
<flux> yes
<palomer> I tried Unix.set_nonblock from my code
<palomer> http://pastebin.com/u113wbFq <-- here's where I call Unix.read
<palomer> (input_lines is called after a select)
<flux> and what did it raise?
<palomer> Fatal error: exception Unix.Unix_error(40, "unix_set_nonblock", "")
<flux> I guess your function swallows all exceptions
<palomer> wouldn't be surprised if stuff got swallowed up
<flux> I think typically one just does one 'read' when Unix.select an fd is readable
<flux> you would need to do Unix.selects in your loop to guarantee the fd is readable
<palomer> I do select -> read -> read -> read -> select -> read ...
<palomer> what do you suggest I do?
jderque has joined #ocaml
<flux> select -> read -> select -> read -> .. is what programs typically do.
<palomer> I wonder what this jderque fellow thinks
<palomer> what if the read is too large?
<palomer> ie, the buffer too small
<flux> it gets truncated?
<palomer> right, and then you need to call read again
<palomer> so, what you're saying is that if I read and my buffer doesn't get completely filled then it's safe to call select
<palomer> what ?
<palomer> s/what/
zorun has quit [Ping timeout: 252 seconds]
<palomer> what if it fills up my buffer _exactly_?
zorun has joined #ocaml
<palomer> doesn't work either
<flux> typically programs work like this: while true do select; read; check if buffer has accumulated enough for a command, perhaps by running a state machine; done
<palomer> ahhh, I guess that works
dnolen has quit [Quit: dnolen]
<palomer> so it's a read -> run code -> select -> read -> run code -> select loop
<palomer> ok, but what if select returns stdin, but for some other reason than reading
<palomer> Unix.read will nonetheless block
<flux> if List.mem Unix.stdin fds_ready; then ..; fi; if List.mem someotherfd fds_ready; then ..; fi
<flux> Unix.select returns a triplet indicating which fds are ready for read/write/exception
<palomer> ahhh, so it works
<palomer> I guess that covers everything
iratsu has quit [Ping timeout: 250 seconds]
iratsu has joined #ocaml
jderque has left #ocaml []
Snark has joined #ocaml
Cyanure has quit [Remote host closed the connection]
vivanov has quit [Quit: Lost terminal]
<palomer> it works!
hyperboreean has joined #ocaml
<gildor> mfp: hi
<gildor> mfp: is there a way to express SELECT * FROM log WHERE pkg IN ("bar", "foo") with sqlexpr ?
<gildor> I would like to replace ("bar", "foo") ?
<mfp> gildor: there's no direct way atm.; what I do is -> use a temp table + something like WHERE pkg IN (SELECT v FROM temp_table)
<mfp> if you set PRAGMA temp_store to the right value, the temp table will be in-mem and it should be fairly efficient
<gildor> mfp: exactly my current solution
<gildor> mfp: well, data are already in a table, so just a embedded select will do
<mfp> AFAIK, there's no better way to do it (that is, nothing available in the C API)
<mfp> when I asked on #sqlite, I was told to generate the whole ... IN (....) query as a string, which sounds worse
<gildor> ok
<mfp> only caveat is to add a mutex so that there's only one thread using the temp table at a time (if you do use a temp table, that is)
Modius has joined #ocaml
<mfp> gildor: (unrelated Q) have you ever used the WAL journal mode?
<mfp> I'm getting a DB lock (doing e.g. ".s" in sqlite3 foo.db complains with 'database is locked') only in WAL mode (but not with the normal journal), and I don't know if it's a bug in sqlexpr
fraggle_laptop has quit [Remote host closed the connection]
<gildor> mfp: no, never used the WAL journal mode, but I am pretty new to sqlite
<mfp> it's supposed to make small write transactions much faster
<palomer> as far as select is concerned, stdout and stderr are the same, right?
ankit9 has quit [Quit: Leaving]
larhat has quit [Quit: Leaving.]
munga has joined #ocaml
lopex has quit []
hyperboreean has quit [Read error: Operation timed out]
hyperboreean has joined #ocaml
galaad has quit [Ping timeout: 260 seconds]
sepp2k has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 240 seconds]
joewilliams_away is now known as joewilliams
digimmortal has quit [Ping timeout: 252 seconds]
ftrvxmtrx has joined #ocaml
alexyk has joined #ocaml
philtor has joined #ocaml
alexyk has quit [Ping timeout: 276 seconds]
vivanov has joined #ocaml
eikke has quit [Ping timeout: 252 seconds]
Tobu has quit [Quit: No Ping reply in 180 seconds.]
Tobu has joined #ocaml
enthymeme has joined #ocaml
avsm has quit [Ping timeout: 264 seconds]
ankit9 has joined #ocaml
alexyk has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 246 seconds]
avsm has joined #ocaml
avsm has quit [Quit: Leaving.]
Boscop has quit [Ping timeout: 250 seconds]
ulfdoz has joined #ocaml
Boscop has joined #ocaml
hto has joined #ocaml
sepp2k has quit [Ping timeout: 255 seconds]
eikke has joined #ocaml
eikke has quit [Quit: Lost terminal]
sepp2k has joined #ocaml
_andre has quit [Ping timeout: 244 seconds]
_andre has joined #ocaml
_andre has quit [Ping timeout: 276 seconds]
_andre has joined #ocaml
_andre has quit [Client Quit]
_andre has joined #ocaml
<NaCl> Is there a function to detect when stuff is added to a Lwt stream?
impy has joined #ocaml
iratsu has quit [Ping timeout: 250 seconds]
ftrvxmtrx has joined #ocaml
<sgnb> NaCl: in what context?
<sgnb> I'd just peek an element
<NaCl> I'm trying to iteratively process the output of a spawned process as it's running
<NaCl> I would use the line-reading function, but this program doesn't really spit out newlines until it's done
<NaCl> eh, I could just pipe the file descriptors around instead
<sgnb> you don't need streams for that
munga has quit [Ping timeout: 260 seconds]
<sgnb> your parent process can just directly read from the child's output
lopex has joined #ocaml
<sgnb> (the child must flush its output regularly though... or buffering must be disabled)
<NaCl> yeah, it does
<NaCl> I think
<malouin> How does ocaml know what type Printf.printf "%d/%f" is?
<thelema_> malouin: the compiler examines the string "%d/%f" and magically decides it's int -> float -> unit
<thelema_> Note format4 and format6 in stdlib
<malouin> thelema_: so the compiler reads "%d/%f" as a ('a,...) format6 rather than a string, the same way it reads 0x55555555l as an Int32?
<thelema_> more or less - string literals can be of type `string` or of type `(something) format6`
<malouin> ok, that makes sense.
<thelema_> this means that the format strings can't be generated at runtime.
<thelema_> at least not easily.
eb4890 has joined #ocaml
<malouin> right.
Snark has quit [Quit: Ex-Chat]
<malouin> thanks thelema_!
<sgnb> thelema_: but strings can be checked against a static format at run-time
<sgnb> and there are primitives in Pervasives to concatenate format strings
ankit9 has quit [Quit: Leaving]
<thelema_> true. That's the "not easily" solution I was thinking of. It'd also be nontrivial to have the right arguments available for the resulting format string
<sgnb> obviously
<sgnb> but in C as well
ikaros has joined #ocaml
jamii has joined #ocaml
avsm has joined #ocaml
sheets has joined #ocaml
<sheets> ocaml 3.12 without camlp4o parses {<foo=foo; bar=bar >} fine but with camlp4o parses it as {<foo=(foo; bar=bar)>} and subsequently fails type-checking. Is there a syntactic workaround?
<NaCl> awww oscigen just failed. :(
<thelema_> sheets: hmm, I recall the problem, I forget the solution.
<thelema_> this was discussed on caml-list
<sheets> oh! ok, i will go searching there
<thelema_> - PR#4673, PR#5144: camlp4 fails on object copy syntax
Boscop has quit [Ping timeout: 255 seconds]
<thelema_> sheets: check those mantis bugs
<sheets> thelema_: wow, thanks :-)
<thelema_> no syntactic workarounds proposed...
<sheets> 3.12.1 fixes but can't move to it yet
<thelema_> use bluestorm's workaround extension?
<sheets> yes, reading it now
oriba has joined #ocaml
<avsm> it might be easier just to backport the fix to your local camlp4 in 3.12.0; fairly localised
<sheets> hmm well i've built the extension and it seems to operate correctly
<sheets> now just convincing the build to use it
<avsm> cool. its often less hassle to patch ocaml than convince a build system to add a -pp ;-)
<sheets> heh i'm a little wary of that after my parmatch bug
<sheets> takes so long to rebuild and the everything dependent sees new hashes and complains about interface mismatches unless you make clean :-(
<thelema_> sheets: ocamlbuild?
<sheets> maybe i was doing something stupid but it seemed like the iteration time was 15m+
jamii has quit [Ping timeout: 258 seconds]
Boscop has joined #ocaml
<avsm> patching camlp4 is safe in that regard, unless the patch changes the output code
<sheets> i'm using ocamlbuild with ocamlfind… i think i will globally install the bugfix instead of figuring out how to coerce ocamlbuild to use a custom camlp4 include dir
<sheets> avsm: ah, yes, i see what you mean… could just patch camlp4
jamii has joined #ocaml
Anarchos has joined #ocaml
ftrvxmtrx has quit [Read error: Operation timed out]
<sheets> ugh… so the new camlp4 uses a different syntax extension object naming convention?? Camlp4OCamlFoo.cmo?? but you can still pass the old names (pa_o.cmo) to the camlp4 command?
ftrvxmtrx has joined #ocaml
vivanov has quit [Ping timeout: 252 seconds]
<NaCl> seeing that collapsed ellipsis confuses me at times. xD
<sheets> sorry :-/ my client is too smart for its own good
ulfdoz has quit [Ping timeout: 252 seconds]
<NaCl> heh
<NaCl> my first response to the guy ion the mailing list would be to use the package in fedora itself. xD
<NaCl> *in
_andre has quit [Quit: leaving]
jamii has quit [Ping timeout: 258 seconds]
lamawithonel has quit [Remote host closed the connection]
thieusoai has joined #ocaml
jamii has joined #ocaml
ygrek has quit [Ping timeout: 250 seconds]
thieusoai has quit [Remote host closed the connection]
Transformer has joined #ocaml
Transformer has quit [Excess Flood]
jamii has quit [Ping timeout: 258 seconds]
jamii has joined #ocaml
edwin has quit [Remote host closed the connection]
lamawithonel has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
jamii has quit [Ping timeout: 258 seconds]
jamii has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
jamii has quit [Read error: Connection reset by peer]
jamii has joined #ocaml
<hcarty> thelema_: Is there a print_maybe function anywhere in Batteries?
enthymeme has quit [Ping timeout: 258 seconds]
zorun has quit [Ping timeout: 244 seconds]
avsm has quit [Quit: Leaving.]
iratsu has joined #ocaml
Modius has quit [Quit: "Object-oriented design" is an oxymoron]
<Xaseron> how can i include another ocaml file?
ikaros has quit [Quit: Ex-Chat]
<sheets> Xaseron: you can include modules in other modules with "include Module" so if you have a file "myfrag.ml" you could include it in "mylib.ml" with "include Myfrag"
<Xaseron> i wrote a avl.ml with an implementation of an avltree and i like to access the methods from another file
Tobu has quit [Quit: No Ping reply in 180 seconds.]
Tobu has joined #ocaml
<sheets> Xaseron: you can simply use Avl.myfunction to reference them
<sheets> Xaseron: or you can "open Avl" or "module A = Avl" to provide a short alias
eb4890 has quit [Ping timeout: 255 seconds]
lopex has quit [Ping timeout: 240 seconds]
<Xaseron> i get Error: Reference to undefined global `Avl'
<sheets> are the files in the same directory?
<sheets> how are you building the avltree.ml?
<Xaseron> ocamlopt avl.ml
<Xaseron> yes,same directory
<NaCl> that would produce something like a.out
<NaCl> an executable, not a library
<sheets> ocamlopt avl.ml avltree.ml
lopex has joined #ocaml
<Xaseron> a thanks now it works
<olasd> 3
<olasd> erm
jamii has quit [Ping timeout: 258 seconds]
munga has joined #ocaml
jamii has joined #ocaml
BiDOrD_ has quit [Remote host closed the connection]
BiDOrD has joined #ocaml
* NaCl smacks the Str module with a large trout
<Xaseron> what is the maximum integer in ocaml?
jamii has quit [Ping timeout: 258 seconds]
<olasd> Xaseron: it's max_int
jamii has joined #ocaml
<Xaseron> easier than i thought :-)
<olasd> :)
Tobu has quit [Ping timeout: 258 seconds]
Tobu has joined #ocaml
jamii has quit [Ping timeout: 258 seconds]
jamii has joined #ocaml
munga has quit [Ping timeout: 255 seconds]
Morphous_ has quit [Ping timeout: 255 seconds]
Tobu has quit [Quit: No Ping reply in 180 seconds.]
Tobu has joined #ocaml
Morphous_ has joined #ocaml
mfp has quit [Ping timeout: 255 seconds]
Reaganomicon has quit [*.net *.split]
rwmjones has quit [*.net *.split]
patronus_ has quit [*.net *.split]
impy has quit [Quit: impy]
Reaganomicon has joined #ocaml
rwmjones has joined #ocaml
patronus_ has joined #ocaml
mfp has joined #ocaml
dnolen has joined #ocaml
jamii has quit [Ping timeout: 258 seconds]