gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0+beta1 http://permalink.gmane.org/gmane.comp.lang.caml.inria/49168
seanmcl has quit [Quit: seanmcl]
seanmcl has joined #ocaml
psnively has quit [Quit: psnively]
Edward__ has quit []
joewilliams is now known as joewilliams_away
ccasin has quit [Quit: Leaving]
thrasibule has quit [Ping timeout: 260 seconds]
jeddhaberstro has joined #ocaml
<alexyk> are there utilities to view Hashtbl?
<travisbrady> alexyk: Hashtbl.iter (fun k v -> Printf.printf "K: %d V: %d\n" k v) myht;;
<alexyk> thx!
<alexyk> how do I abbreviate Hashtbl to H?
<travisbrady> module H=Hashtbl;;
travisbrady has quit [Quit: travisbrady]
<alexyk> even in Batteries?
<alexyk> apparently
<alexyk> why, when I say: type reps = (user,int) Hashtbl.t, I get back: type reps = Batteries_uni.Hashtbl.t user int -- but I can't feed that back to repl?
<thelema> alexyk: sorry, if you have syntax extensions installed in batteries, the types you get back are in revised syntax
<thelema> the only known fix is to disable syntax extensions (which are on by default).
thrasibule has joined #ocaml
<thelema> It's a bug in findlib's handling of camlp4, not directly in batteries
<alexyk> thelema: I didn't do anything but open Batteries;; do the extensions only write syntax back? or can I use it too?
<thelema> there's two syntax extensions, one for unicode ropes and other special string types
<thelema> and the other for list comprehensions
<thelema> to enable batteries, you modified your ocamlinit. That code loads battop.ml, which loads the camlp4 extensions after it prints the banner
<alexyk> right
<alexyk> so how do the params for Hashtbl get inverted, just like in Haskell? :)
<thelema> revised syntax responses in the toplevel - loading camlp4 in the toplevel changes the responses you get (even if you don't load the revised syntax)
<alexyk> ah ok, so it's solely camlp4 thing
<thelema> yes.
<alexyk> I forgot, in OCaml you can't pattern-match in let myfunction (Constr x) = ... like in Haskell, you have to say myfunction x = match x with ..., right? or say let myfunction = fun (Constr x) -> blah | (Another y) -> more... right?
<alexyk> (in case of a single x, unless you tuple up?)
<thelema> let f = function Constr x -> ... | Constr2 y -> ...
<thelema> "fun" != "function"
<alexyk> right
<alexyk> can you have several definitions in one let or you always chain them with in?
<alexyk> I guess always in
<thelema> better to always use in, unless you need mutually recursive definitions, when you shouls use [ let foo = ... and bar = ... ]
<alexyk> right. you mentioned Enum yesterday, now I need to produce a Hashtbl out of a list, which is Json_type: Object pairs. Can I convert that to Enum and then call of_enum on it?
<thelema> you can.
<thelema> List.enum |- Hashtbl.of_enum
<alexyk> thelema: is it idiomatic?
iratsu has joined #ocaml
<thelema> In batteries, Enum is the lowest common denominator for converting from one structure to another
<alexyk> ok. so Enum is the Batteries thing?
<thelema> yes
<thelema> It's also in extlib, although not quite as pervasive.
<alexyk> ok. What's the simplest way to call Hashtbl.print -- what can I supply for the three functions it wants?
<alexyk> for this: let hash_of_list = List.enum |- Hashtbl.of_enum;; let h = hash_of_list [(1,2),(3,4)];;
krankkatze has joined #ocaml
<krankkatze> hi
<krankkatze> I'm trying to write a makefile for a project and I would like to put some of the files together un a directory
<thelema> alexyk: two functions - print the key and print the value.
<thelema> let print_int_pair_hash ht = Hashtbl.print (Pair.print Int.print) (Pair.print Int.print) ht
<thelema> krankkatze: in a subdirectory?
<krankkatze> but the modules it created can't be found when opening them from a file which is not in this directory
<krankkatze> yes thelema
<krankkatze> how should I proceed?
<alexyk> thelema: thx
krankkatze is now known as krankkatze-
seanmcl has quit [Ping timeout: 260 seconds]
<thelema> you'll need a [-I subdir] when compiling in the main dir
<thelema> this tells the compiler to look for files also in the subdir
<alexyk> do you guys use omake?
<thelema> alexyk: I used it for a while, but I'm back to ocamlbuild
<thelema> + a simple makefile
<alexyk> thelema: why did you switch back?
<krankkatze-> thanks thelema
<thelema> krankkatze-: no problem
<krankkatze-> :)
<thelema> alexyk: portability - omake isn't commonly available
<alexyk> thelema: but if it is? :)
<thelema> it's nice that omake compiles things faster than ocamlbuild... they're pretty close in ease of use if your requirements are simple.
<krankkatze-> is there a way not to have a final "ocamlopt.opt -o output file1.cmx file2.cmx ..." that takes three lines ?
<krankkatze-> like, linking only half of the files together and then the second half?
<thelema> krankkatze-: try ocamlbuild if your dependencies are reasonable.
<thelema> or use a variable for all your requirements
<krankkatze-> I'll have a look
<krankkatze-> thanks again :D
<alexyk> how do I match a result of json_of_string? It prints as Object [("key",value),...], but if I declare: let json2adj = function | Object pairs -> hash_of_list | _ -> failwith "bad adj" -- I get: Json_type.json_type -> list ('_a * '_b) -> Batteries_uni.Hashtbl.t '_a '_b = <fun>
seanmcl has joined #ocaml
<thelema> [hash_of_list pairs] ?
<alexyk> thelema: I can't get pairs inless I do objekt on the input
<thelema> Object pairs -> hash_of_list pairs
<alexyk> ah right of course
<alexyk> so why does Batteries' map is Enum.map? What's the Enum literal?
<thelema> defaults to enum.map because it's convenient. There's no real Enum literal - I use List.enum
<thelema> Enum is a bit wierd as it gets consumed as it's traversed, so a literal would work in unexpected ways, I think
<alexyk> so it's like Clojure's lazy seq for a foundation, nice
<thelema> possibly. lazy lists usually aren't as mutable as enum.
<alexyk> thelema: will hash_of_list stay polymorphic? seems like it's being restricted: http://paste.pocoo.org/show/227159/
seanmcl has quit [Ping timeout: 245 seconds]
thrasibule has quit [Ping timeout: 264 seconds]
<alexyk> or is it because js is defined?
<thelema> maybe it's because of the style - it's technically not defined as a function. try using an explicit parameter instead of point free style
<thelema> ocaml has problems generalizing point free style sometimes
<alexyk> yes
<alexyk> sad that point-free fails
<thelema> because ocaml doesn't know it's a function syntactically...
<thelema> or somesuch
fomatt has joined #ocaml
alexyk has quit [Quit: alexyk]
jeddhaberstro has quit [Quit: jeddhaberstro]
ftrvxmtrx has quit [Ping timeout: 260 seconds]
ftrvxmtrx has joined #ocaml
Amorphous has quit [Ping timeout: 248 seconds]
Amorphous has joined #ocaml
<thelema> I guess there's some syntax change of camlp4 in 3.12 that breaks pa_format:
<thelema> > + ocamlfind ocamldep -package camlp4.lib -native -pp camlp4of -I . -I ../../../libs/estring pa_format.ml
<thelema> > File "pa_format.ml", line 247, characters 19-22:
<thelema> > While expanding quotation "ctyp" in a position of "patt":
<thelema> > Parse error: EOI expected after [quotation of type] (in [quotation of type])
<thelema> if anyone can look into it, I'd appreciate it.
schmrkc has quit [Ping timeout: 258 seconds]
schmrkc has joined #ocaml
ulfdoz has joined #ocaml
schmrkc has quit [Ping timeout: 265 seconds]
schmrkc has joined #ocaml
schmrkc has quit [Changing host]
schmrkc has joined #ocaml
ChristopheT has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
derdon has joined #ocaml
Christop` has joined #ocaml
ChristopheT has quit [Ping timeout: 265 seconds]
ChristopheT has joined #ocaml
Christop` has quit [Ping timeout: 276 seconds]
Yoric has joined #ocaml
ikaros has joined #ocaml
ttamttam has joined #ocaml
thrasibule has joined #ocaml
thrasibule has quit [Ping timeout: 265 seconds]
derdon has quit [Quit: derdon]
seafood has joined #ocaml
seafood has quit [Client Quit]
seafood has joined #ocaml
Yoric has quit [Ping timeout: 240 seconds]
Christop` has joined #ocaml
ChristopheT has quit [Ping timeout: 265 seconds]
Christop` has quit [Client Quit]
ChristopheT has joined #ocaml
seanmcl has joined #ocaml
ztfw`` has joined #ocaml
ztfw` has quit [Ping timeout: 265 seconds]
ztfw`` has left #ocaml []
myu2 has joined #ocaml
sepp2k has joined #ocaml
ttamttam has quit [Quit: Leaving.]
seanmcl has quit [Quit: seanmcl]
seanmcl has joined #ocaml
myu2 has quit [Remote host closed the connection]
myu2 has joined #ocaml
seanmcl has quit [Quit: seanmcl]
seanmcl has joined #ocaml
orbitz_ has joined #ocaml
iratsu has quit [Ping timeout: 260 seconds]
ccasin has joined #ocaml
orbitz has quit [Ping timeout: 260 seconds]
alexyk has joined #ocaml
myu2 has quit [Remote host closed the connection]
monra has joined #ocaml
monra has left #ocaml []
iratsu has joined #ocaml
alexyk has quit [Ping timeout: 265 seconds]
alexyk has joined #ocaml
alexyk has quit [Ping timeout: 252 seconds]
alexyk has joined #ocaml
alexyk has quit [Ping timeout: 260 seconds]
ttamttam has joined #ocaml
ulfdoz has quit [Ping timeout: 240 seconds]
thrasibule has joined #ocaml
seanmcl has quit [Quit: seanmcl]
seanmcl has joined #ocaml
orbitz_ has quit [Quit: Reconnecting]
orbitz has joined #ocaml
thrasibule has quit [Ping timeout: 248 seconds]
thrasibule has joined #ocaml
travisbrady has joined #ocaml
ztfw has joined #ocaml
ztfw has quit [Ping timeout: 260 seconds]
mlasson has joined #ocaml
mlasson has quit [Quit: Quitte]
mlasson_ has joined #ocaml
mlasson has joined #ocaml
myu2 has joined #ocaml
mlasson has quit [Client Quit]
ulfdoz has joined #ocaml
ttamttam has quit [Quit: Leaving.]
mlasson_ has left #ocaml []
mlarsson has joined #ocaml
marque has joined #ocaml
_unK has joined #ocaml
ikaros has quit [Quit: Leave the magic to Houdini]
Christop` has joined #ocaml
ikaros has joined #ocaml
ChristopheT has quit [Read error: Operation timed out]
myu2 has quit [Remote host closed the connection]
ChristopheT has joined #ocaml
Christop` has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
sepp2k1 has joined #ocaml
sepp2k has quit [Ping timeout: 264 seconds]
emmanuelux has joined #ocaml
marque has quit [Quit: Lost terminal]
ttamttam has joined #ocaml
Yoric has joined #ocaml
gl has joined #ocaml
<gl> hey, i can't find out how to use SOCK_RAW with ocaml, i get a Exception: Unix.Unix_error (Unix.EPROTONOSUPPORT, "socket", "").
ztfw has joined #ocaml
<gl> but apparently, it's supported in the ocaml Unix module
<gl> is there any unix/network related documentation to read? ocamlunix.forge.ocamlcore.org/ocamlunix.html looks nice, but lacks of 'real life' code snippets
<adrien> don't you need to be root to be able to use that?
<gl> (i mean for this)
<gl> adrien you need to be root to run the program, not to compile it:)
<gl> oh, i omit this, the error occurs at compile-time
<adrien> :o
seanmcl has quit [Quit: seanmcl]
jcaose_ has quit [Quit: Leaving]
gl has left #ocaml []
ttamttam has quit [Quit: Leaving.]
oc13 has joined #ocaml
mbishop_ has joined #ocaml
mbishop has quit [Ping timeout: 252 seconds]
oc13 has left #ocaml []
seanmcl has joined #ocaml
seanmcl_ has joined #ocaml
seanmcl_ has quit [Client Quit]
seanmcl_ has joined #ocaml
seanmcl has quit [Ping timeout: 240 seconds]
seanmcl_ is now known as seanmcl
ulfdoz has quit [Read error: Operation timed out]
seanmcl has quit [Ping timeout: 240 seconds]
seanmcl has joined #ocaml
Yoric has quit [Quit: Yoric]
derdon has joined #ocaml
elehack has joined #ocaml
elehack has quit [Client Quit]
<fomatt> Hi, I could definitively use some help on abstract types and compilation.
<fomatt> Say for example, I have a module that abstracts the type Unix.tm
<fomatt> In my module I have type time = Unix.tm and in the interface just type time which is needed by some of module functions
<fomatt> But when I want to use that module somewhere else, the compilator asks me to provide an implementation for Unix
<fomatt> Is there a way I can encapsulate time so that Unix is not required when compiling whatever code that uses the module?
<adrien> I'm not sure that'd be possible, but why do you want to do that?
<fomatt> Well I'd rather not require to provide the implementation for all the "hidden" modules to be able to compile whatever code that is using the libray...
<fomatt> And since the type is abstract anyway nothing can be made of it but passing or receiving it from the interfaced functions
<adrien> only the type is abstract, not the code
<sgnb> fomatt: you should be able to compile module that use your abstract type
<sgnb> but for linking, you'll always need an implementation of the Unix module
<fomatt> but when i do so I get No implementations provided for the following modules: Unix
<fomatt> I see
<fomatt> I tried to go around it by declaring the abstract type polymorphic but no dice.
<fomatt> Thanks for your explanation, it makes sense that the compiler needs to know the type of course, I just hopes some compilation option could make it available somewhere in the cm* files produced by the compiler
<fomatt> sorry *hoped*
travisbrady has quit [Read error: Connection reset by peer]
travisbrady has joined #ocaml
<fomatt> Anyway thanks again. I'll stop wasting time looking for a solution then.
<fomatt> A quick question to further my understanding: the implementations are required only for the modules whose types are used in the mli file, right? If I used Unix but only within my module without it being used in the interface then linking against it should not be required, yes?
<adrien> it's getting late so I might say some bad things but I think you'd still require it
elehack has joined #ocaml
<fomatt> Thanks, indeed it's the case, I just thought I wasn;t compiling the right way. I definitively do not understand why it is needed though.
<sgnb> fomatt: if you use some function from the Unix module, you'll always have to link against it somehow
<fomatt> It makes it impossible to encapsulate libraries then.
<adrien> it's because you're using the code from the module, the type may not be visible but you need the code from it
<fomatt> But my libray has been compiled with Unix and it does not make it visible to the outside world, there's nothing related to Unix in the interface.
<fomatt> Why would the outside world when using my library need the Unix implementation?
<elehack> fomatt: because OCaml does not link the Unix module implementation code into your library; it only links it in to the final program.
<elehack> so the final program link command needs to have it available.
<adrien> actually, I'm wondering if it's not possible to "include" the library in your own library when dealing with bytecode but for native code it's definitely an error (again, it's pretty late here)
<adrien> I think I did that once by mistake, it worked for bytecode and then it failed for native code
elehack has left #ocaml []
<fomatt> Oh I see. So when I compile my library into a cmx file that cmx file is not yet linked against Unix.
<adrien> yeah
elehack has joined #ocaml
<fomatt> Thanks a lot, I'm enlightened now.
<fomatt> Although it's bizarre that the cmx does not contain what i needs from the included modules implementations... It makes it impossible to encapsulate other modules in a library then.
<fomatt> Anyway thanks gain.
<adrien> it'd take far too much space
<elehack> fomatt, what if 3 modules all use Unix? You really want the linker to be able to only emit 1 copy.
<elehack> ocamlfind also helps -- the META file declares dependencies, so the link command just says "give me the foo module" and OCamlFind automatically pulls in unix if necessary.
<fomatt> I see. Indeed it could be problematic but I would think the option to include or not the dependent modules should be available in the compiler.
<fomatt> Thanks elehack, I'm indeed using ocamlfind. Makes life much easier, even more so in the toplevel
ikaros_ has joined #ocaml
<fomatt> Indeed a META file should make it seemless. Thanks for the tip.
ikaros has quit [Ping timeout: 265 seconds]
<sgnb> adrien: you can do that, but it's not recommended
<sgnb> it can lead to strange errors
<adrien> yeah, I made it by mistake ;-)
<fomatt> I won't try it ;-) META files don't look that hard to use ;-)
thrasibule has quit [Ping timeout: 260 seconds]
_unK has quit [Remote host closed the connection]
boscop has quit [Ping timeout: 260 seconds]
boscop has joined #ocaml
ikaros_ has quit [Quit: Leave the magic to Houdini]
derdon has quit [Quit: derdon]
seanmcl has quit [Quit: seanmcl]
seanmcl has joined #ocaml