flux__ changed the topic of #ocaml to: OCaml 3.09.2 available! Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
er has quit []
<pattern> why do i get "Uncaught exception: Stream.Error("currified constructor")" when i run this http://www.rafb.net/paste/results/7ZyNBu61.html ?
<mikeX> wow ;)
<pattern> actually a parse error, "Parse error: currified constructor"
<mikeX> pattern: shouldn't you put parentheses?
<pattern> makes no difference
<mikeX> (Unix.Unix_error (Unix.ENOENT, x, y))
<mikeX> well Unix_error expects a tupple, not sure if camlp4 somehow changes that
<pattern> hmm... this works in my example prog
<pattern> but not in my real prog
<mikeX> what's 'this'?
<mikeX> (not using tupples)?
<pattern> oh... i got it
<pattern> it was still giving me the currified constructor error, but for a different line! :P
<pattern> i'd tried the parenthesis before, and they didn't seem to work, but actually did work
<mikeX> well, it's not just the parenthesis, it's also the commas
<pattern> yeah, i had the commas too
<pattern> the curious thing is that this used to work without the parens or commas back in ocaml 3.06
<pattern> iirc
<mikeX> I wouldn't really know
<mikeX> anyway, the use of ocamlp4 is important here (I think), at least for the way the error is reported
<pattern> yeah, definitely
<pattern> thanks for your help, btw, mikex
<mikeX> np
flux__ has quit [Remote closed the connection]
Purice has joined #ocaml
descender has quit [Read error: 104 (Connection reset by peer)]
flux__ has joined #ocaml
Purice has quit ["Leaving"]
<pattern> ok... got another question... the first regex here works, but the second doesn't... http://www.rafb.net/paste/results/smibXz49.html
<pattern> i get a "Warning: line 8, chars 46-47: Invalid backslash escape in string"
<pattern> but using a backslash to escape a period is normal in regular expressions... and is even documented in str.mli
<pattern> and, again, used to work in ocaml 3.06 :(
<pango> yes, \s are used in strings, before they're transformed into regexpes
<pango> but in ocaml code, \s need to be doubled
<pattern> ah
<pattern> something else new
<pango> notice the compiler just throws a warning, the code is still compiled
<pattern> so is it a valid regex with just a single \s ?
<pattern> or do i need to double it?
<pango> depends whether you're talking about content of string, or ocaml source to generate it
<pattern> in the ocaml source that will be compiled in to a string that will in turn be made in to a regex, as i have in my example prog above
<pango> if, say, you want \( in the string, in code you must type \\(
<pango> because backslash sequences will be checked (and converted) at compile time
<pattern> cool... ok, that worked
<pattern> thanks, pango
<pango> np
<pango> I suppose 3.06 was just more silent about the issue
<pattern> not just more silent, it didn't need the doubled \s
<pattern> at least not for the regex to work
<pattern> i'm going through an old prog of mine i haven't touched in years
<pattern> used to compile just fine
<pango> as I said, it still works with single \s, I don't think it stops compilation
<pattern> but, as you can see, there have been a few changes in ocaml :)
<pattern> oh
<pattern> maybe it was just more silent then
<pango> I guess so. Maybe Changelog would confirm
<pattern> doesn't really matter much to me... i don't intend to go back to 3.06
<pango> "Warnings for ill-formed \ escapes in string and character literals."... but in 3.05 changelog ;)
<pattern> oh, maybe this source is older than i thought
mikeX has quit ["zz"]
dark_light has quit [Read error: 104 (Connection reset by peer)]
Smerdyakov has quit ["Leaving"]
bluestorm has joined #ocaml
slipstream has joined #ocaml
slipstream-- has quit [Read error: 110 (Connection timed out)]
Sir_Diddymus has joined #ocaml
__DL__ has joined #ocaml
Submarine_ has joined #ocaml
Submarine has quit [Nick collision from services.]
Submarine_ is now known as Submarine
dark_light has joined #ocaml
ulfdoz_ has joined #ocaml
ulfdoz has quit [Read error: 60 (Operation timed out)]
<bluestorm> hum
<bluestorm> in a file socket.ml i have a type socket = { name : string };; type declaration
<ketty> hum hum ^^
<bluestorm> in another file i manipulate data from this type
<bluestorm> and data.name doesn't work
<ketty> data.Socket.name
<bluestorm> i have to put data.Socket.name
<bluestorm> yes
<bluestorm> but then i've done in the second file
<bluestorm> type client = Socket.socket;;
<bluestorm> i thought this way i would be able to do data.name
<bluestorm> but it still isn't possible
<ketty> yes
<bluestorm> why ?
<bluestorm> i thought aliasing the type would allow me to use it locally
<ketty> the record-field 'name' is in the namespace of Socket
<bluestorm> hum
<bluestorm> is there a correct way to report it in the other file ?
<bluestorm> because re-declaring the same record seems me dummy
<pango> open Socket
<bluestorm> hum
<ketty> yes
<bluestorm> there is no way to export only the record ?
<ketty> if Socket is to big, you can move the type declaration into a nested module..
<bluestorm> and open it then ?
<bluestorm> hum
<ketty> yes
<bluestorm> actually socket is pretty small
<bluestorm> so there is no problem in opening it
<ketty> good :)
<bluestorm> hum i think i'll stay with data.Socket.name
<bluestorm> i don't like to open thigns with no serious reason
<bluestorm> (hum "without any serious reason", sorry)
<ketty> is there ever a "serious" reason?
<bluestorm> hum
<bluestorm> when i have type-only modules
<bluestorm> shared everywhere
<bluestorm> this is a serious reason
<ketty> ok :)
<ketty> <-- is using a lot of lazy reasons =)
<bluestorm> but in most of case open make code harder to understang, in my opinion
<ketty> yes
<ketty> true
<bluestorm> always asking "where is this function defined ?"
<ketty> mostly i bind modules to one-letter-names...
<pango> same for fields names, no ? ;)
<pango> actually type socket = Socket.socket may work, in some contexts
<pango> mmmh not really, socket seems to be now abstract
<pango> you can use functions from Socket over it, but not access its structure directly, according to some tests
love-pingoo has joined #ocaml
<pango> bluestorm: there's also ketty's suggestion, module S = Socket then you can write recordname.S.filename... depending on what you find less cryptic ;)
<bluestorm> hum
<bluestorm> recordname.Socket.rowname is ok
<bluestorm> a few more letters doesn't cost me too much
dark_light has quit [Read error: 104 (Connection reset by peer)]
eternite has joined #ocaml
slipstream-- has joined #ocaml
slipstream has quit [Read error: 110 (Connection timed out)]
Submarine has quit [Nick collision from services.]
menace has joined #ocaml
<eternite> I have a problem.
<eternite> Why this : "let str = Marshal.to_string g [Marshal.No_sharing;Marshal.Closures];;"
<eternite> raise : "Exception: Invalid_argument "output_value: abstract value (outside heap)"."
<eternite> sentence 2
<eternite> this should work...
<eternite> Sorry it is the wrong copy/past
<eternite> my exemple is : let str = Marshal.to_string print_endline [Marshal.No_sharing;Marshal.Closures];;
<eternite> and raise : Exception: Invalid_argument "output_value: abstract value (Custom)".
<dylan> print_endline is a C function.
<eternite> considere :
<eternite> et my_pure_ocaml_function(x,y)=(y,x);;
<eternite> let str = Marshal.to_string my_pure_ocaml_function [Marshal.No_sharing;Marshal.Closures];;
<dylan> hmm
<eternite> class a = object method p = print_endline "hello world" end;; let m = new a;; arshal.to_string m [Marshal.Closures];;
<eternite> This raise an exception....
<eternite> This should be fine...
<eternite> I think it is bug.
<pango> it works if compiled, I think
<eternite> not with ocamlc
<pango> seems so
<eternite> work with ocamlopt...
<eternite> that is very strange.
<eternite> This is not specified in chapter 11.5
<pango> I wonder if HashCaml does better or worse...
<eternite> It don't support object... I suppose it is the same for closure.
<bluestorm> hum
<bluestorm> type shared_table = ((string, 'a) Hashtbl.t) Shared.shared_data;;
<bluestorm> this doesn't work
<bluestorm> (where Shared.shared data is declared as "type 'a shared_data = ... ;;")
<bluestorm> i don't understand why
<bluestorm> " Unbound type parameter 'a "
<bluestorm> ah
<bluestorm> hum
<bluestorm> ><
<bluestorm> i'm stupid, sorry
<bluestorm> type 'a shared_table ...
Smerdyakov has joined #ocaml
metaperl_ has joined #ocaml
Sir_Diddymus has quit [Read error: 110 (Connection timed out)]
metaperl has quit [Read error: 110 (Connection timed out)]
metaperl_ is now known as metaperl
shachaf has joined #ocaml
finelemon has joined #ocaml
finelemo1 has quit [Read error: 110 (Connection timed out)]
Snark has joined #ocaml
finelemo1 has joined #ocaml
finelemon has quit [Read error: 110 (Connection timed out)]
menace has quit []
chessguy has joined #ocaml
chessguy has quit [Success]
eternite has quit [Read error: 110 (Connection timed out)]
Schmurtz has joined #ocaml
Schmurtz has quit ["Dodo !"]
Schmurtz has joined #ocaml
ibor has joined #ocaml
ibor has left #ocaml []
mikeX has joined #ocaml
Snark has quit ["Leaving"]
__DL__ has quit ["Bye Bye"]
_JusSx_ has joined #ocaml
_JusSx_ has quit ["leaving"]
ulfdoz_ is now known as ulfdoz
mikeX has quit ["zzz"]
love-pingoo has quit ["Connection reset by by pear"]
bluestorm has quit ["Konversation terminated!"]
ski has quit [Read error: 110 (Connection timed out)]
ski has joined #ocaml
shachaf has quit [Connection timed out]
shachaf has joined #ocaml
ski has quit [Connection timed out]
ski has joined #ocaml