lapinou changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | http://www.ocaml.org | OCaml 4.01.0 announce at http://bit.ly/1851A3R | Public logs at http://tunes.org/~nef/logs/ocaml/
<mmachenry> smondet: I tried do what they do with the packed library and I get circular dependencies
array has quit [Quit: Page closed]
zpe has quit [Ping timeout: 264 seconds]
<mmachenry> W: Cannot find source file matching module 'Pcf' in library Pcf
<mmachenry> But I don't see that the Jane St. repo you sent me has a module for bin_prot
<mmachenry> And I suspect W: means it's just a warning ?
lostcuaz has joined #ocaml
<Drup> yes, oasis W are just warnings
<Drup> (and sometime, just false positive)
ygrek has joined #ocaml
jao` has joined #ocaml
jao` has quit [Changing host]
jao` has joined #ocaml
nikki93 has joined #ocaml
nataren has joined #ocaml
nikki93 has quit [Ping timeout: 245 seconds]
zpe has joined #ocaml
zpe has quit [Read error: Connection reset by peer]
zpe has joined #ocaml
ollehar has quit [Ping timeout: 246 seconds]
nikki93 has joined #ocaml
AdmiralBumbleBee has quit [Ping timeout: 260 seconds]
shinnya has quit [Ping timeout: 245 seconds]
wolfnn has quit [Quit: Leaving.]
csakatoku has quit [Remote host closed the connection]
csakatoku has joined #ocaml
nikki93 has quit [Remote host closed the connection]
lovethroat has joined #ocaml
zRecursive has joined #ocaml
ygrek has quit [Ping timeout: 265 seconds]
lidenbrock has joined #ocaml
ollehar has joined #ocaml
lidenbrock has quit []
csakatoku has quit [Remote host closed the connection]
csakatoku has joined #ocaml
ygrek has joined #ocaml
nikki93 has joined #ocaml
nikki93 has quit [Remote host closed the connection]
ollehar has quit [Ping timeout: 246 seconds]
csakatoku has quit [Remote host closed the connection]
csakatoku has joined #ocaml
<mmachenry> Do you happen to know why Jane St's bin_prot doesn't have a bin_prot.ml and _oasis is happy to create their bin_prot Library with the listed modules but mine complains about a missing file?
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Read error: Connection reset by peer]
zpe has joined #ocaml
ollehar has joined #ocaml
NoNNaN has quit [Ping timeout: 240 seconds]
jpdeplaix has quit [Ping timeout: 245 seconds]
nikki93 has joined #ocaml
michael_lee has quit [Ping timeout: 272 seconds]
malo has quit [Quit: Leaving]
jpdeplaix has joined #ocaml
kyrylo has quit [Ping timeout: 260 seconds]
ollehar has quit [Ping timeout: 246 seconds]
<mmachenry> It seems to me that I can only setup tests with oasis if I say that my code is a library and then make it a dependency of the tests. Does anyone know why I am getting circular dependencies when I rewrite to my _oasis file to make it a library?
ollehar has joined #ocaml
struktured has quit [Ping timeout: 252 seconds]
aurynj has quit [Ping timeout: 252 seconds]
<zRecursive> sorry, i only use OPAM
lovethroat has quit [Ping timeout: 260 seconds]
michael_lee has joined #ocaml
<mmachenry> zRecursive: Well, they aren't mutually exclusive concepts, oasis and opam.
<mmachenry> I am using both.
csakatoku has quit [Remote host closed the connection]
palomer has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 272 seconds]
nataren has quit [Remote host closed the connection]
csakatoku has joined #ocaml
sheijk has quit [Ping timeout: 260 seconds]
tlockney_away is now known as tlockney
mmachenry has quit [Quit: Leaving.]
mmachenry has joined #ocaml
ollehar has quit [Ping timeout: 246 seconds]
mmachenry has left #ocaml []
csakatok_ has joined #ocaml
csakatoku has quit [Ping timeout: 245 seconds]
palomer has quit [Ping timeout: 264 seconds]
zpe has joined #ocaml
zpe has quit [Ping timeout: 265 seconds]
jao` has quit [Ping timeout: 252 seconds]
tlockney is now known as tlockney_away
nataren has joined #ocaml
nataren has quit [Ping timeout: 260 seconds]
lovethroat has joined #ocaml
csakatok_ has quit [Ping timeout: 245 seconds]
ygrek has quit [Ping timeout: 252 seconds]
ggole has joined #ocaml
sheijk has joined #ocaml
rand000 has joined #ocaml
nikki93 has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 245 seconds]
csakatoku has joined #ocaml
axiles has joined #ocaml
sheijk has quit [Quit: .]
rand000 has quit [Ping timeout: 265 seconds]
aurynj has joined #ocaml
philtor has quit [Ping timeout: 264 seconds]
yacks has joined #ocaml
angerman has joined #ocaml
zpe has joined #ocaml
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 272 seconds]
nataren has joined #ocaml
nataren has quit [Ping timeout: 260 seconds]
Guest___ has joined #ocaml
Simn has joined #ocaml
cago has quit [Ping timeout: 246 seconds]
nataren has joined #ocaml
nataren has quit [Remote host closed the connection]
dant3 has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 265 seconds]
angerman has quit [Read error: Connection reset by peer]
lovethroat has quit [Ping timeout: 260 seconds]
hyperboreean has quit [Quit: leaving]
hyperboreean has joined #ocaml
angerman has joined #ocaml
csakatoku has quit [Remote host closed the connection]
cago has joined #ocaml
Kakadu has joined #ocaml
angerman has quit [Read error: Connection reset by peer]
csakatok_ has joined #ocaml
angerman has joined #ocaml
Thooms has joined #ocaml
mika1 has joined #ocaml
<ggole> It's annoying that GADTs often require unnecessary indirection :/
<ggole> I wonder if that could be fixed
AltGr has joined #ocaml
ikaros has joined #ocaml
<zRecursive> ggole: What is "unnecessary indirection" ?
<ggole> You often need to be able to say "this value could be anything", and in order to do that you have to indirect through another type
<def-lkb> zRecursive: even if there is only one constructor with a single parameter, you have to box
<ggole> ie, type any = Any : _ t -> any
<ggole> I don't think that the indirection is physically necessary though
<zRecursive> thinking ...
<zRecursive> a bit like forall a in haskell ?
<ggole> I'm not familiar with Haskell's GADTs.
<zRecursive> me too
<def-lkb> This one introduces an existential variable, like a forall on the rhs in haskell
<zRecursive> data X = forall a. X a (a -> a) (a -> String)
<def-lkb> yes, but there is similar boxing
nikki93 has joined #ocaml
<def-lkb> to avoid boxing, you use "newtype" declarations in haskell, but existential context is not allowed in this case
zpe has joined #ocaml
<ggole> It would be nice if single-constructor types were flattened
<ggole> (Although I think that the behaviour of == would change with such a transformation.)
hyperboreean has quit [Ping timeout: 260 seconds]
<def-lkb> (yes, any trick resorting on representation/implementation would change :))
* ggole also wants a pony
<def-lkb> :)
<zRecursive> heh
nikki93 has quit [Ping timeout: 265 seconds]
zpe has quit [Ping timeout: 260 seconds]
hyperboreean has joined #ocaml
Guest___ has quit [Quit: Computer has gone to sleep.]
Guest_ has joined #ocaml
nataren has joined #ocaml
zRecursive has quit [Remote host closed the connection]
nataren has quit [Ping timeout: 265 seconds]
ygrek has joined #ocaml
lovethroat has joined #ocaml
dant3 has quit [Remote host closed the connection]
angerman has quit [Read error: Connection reset by peer]
dant3 has joined #ocaml
lovethroat has quit [Ping timeout: 260 seconds]
angerman has joined #ocaml
Victorutsc has joined #ocaml
<Victorutsc> can someone tell me why this doesnt compile?
<Victorutsc> fun foo2 (x:int):string = "dddd";
<Victorutsc> List.foldr(foo2, "", [1,2,5]);
<Victorutsc> i am giving foldr an int->string function dammit
<companion_cube> I guess you have several errors here
<companion_cube> "fun" isn't a function declaration, it's an anonymous function
<Victorutsc> pls do tell!
<companion_cube> let foo2 (x:int) = "dddd";; ← declare foo2
<companion_cube> fun (x:int) -> "dddd" ← anonymous function
<Victorutsc> im using SML/NJ does that matter?
<companion_cube> yes
<companion_cube> SML/NJ is SML, here it's an OCaml chan
<companion_cube> both languages are closely related, but not compatible
<Victorutsc> its dead in the #sml channel
<Victorutsc> :)
<companion_cube> ah, I see
<companion_cube> what's the (type?) error?
<Victorutsc> operator domain: 'Z * 'Y -> 'Y
<Victorutsc> operand: (int -> string) * string * int list
<Victorutsc> in expression:
<Victorutsc> List.foldr
<Victorutsc> its as if foldr doesnt like the function foo2
<Victorutsc> ive been looking at these 2 lines of code for like 3 hrs now
<def-lkb> the function passed to foldr should take two arguments: the element of the list, the current value of the accumulator and returns then new accumulator
<Victorutsc> AAHHHHHH
<Victorutsc> thats what happens when u code at 430am ;)
<Victorutsc> THANK YOU!!!!!
<def-lkb> and I think (I cheked sml std lib, but I don't know the language…) that foldr is curried, which means you should pass multiple arguments rather than a tuple
<def-lkb> something like ~ List.foldr foo2 "" [1,2,5]
<companion_cube> def-lkb: I'm not sure
<companion_cube> SML doesn't use as much currying as ocaml
<Victorutsc> ur totally right! thank you again.
<def-lkb> companion_cube: http://www.standardml.org/Basis/list.html#SIG:LIST.foldr:VAL
<def-lkb> np
<Victorutsc> ive been working with ML < 1 week :)
<def-lkb> companion_cube: but overall yes, it seems they had a hard time deciding when to curry :)
<companion_cube> interesting
<companion_cube> def-lkb: indeed, i'm surprised
<Victorutsc> fun foo2 (x:int,y:string list) = ["xxxx"];
<Victorutsc> List.foldr foo2 [] [1,2,5];
<companion_cube> half the functions are curryied
<Victorutsc> that works
<Victorutsc> the curried form & 2 args
<def-lkb> Victorutsc: good luck, it's worth your efforts :)
<Victorutsc> i do like scheme a lot, but so far ML has been driving me nuts with its strict typing :)
<Victorutsc> btw, does ocaml provide better error messages??
<companion_cube> you'll see, strong typing is your friend ;)
angerman has quit [Read error: Connection reset by peer]
dRbiG has quit [Ping timeout: 252 seconds]
<Victorutsc> i prefer flexibility of scheme
<companion_cube> "better" is hard to evaluate... in this case I think the message would also be about "expected 'a -> 'b -> 'c, but the parameter has type 'a -> 'b" or something like this
<Victorutsc> sml/nj has really inadequate error reporting, its like we're back in the 1980s
<Victorutsc> what i meant, it could've been more specific at which code fragment is bad, rather than highlighting whole line
dRbiG has joined #ocaml
<def-lkb> syntax errors are quite bad in ocaml, type errors are much better, except when error arise from an unexpected unification in a large piece of code
angerman has joined #ocaml
Guest_ has quit [Quit: Computer has gone to sleep.]
nikki93 has joined #ocaml
Guest_ has joined #ocaml
<ggole> It only shows one error, unfortunately
nikki93 has quit [Ping timeout: 260 seconds]
hyperboreean has quit [Ping timeout: 265 seconds]
johnelse_away is now known as johnelse
<flux> so, I use Cmdliner. but now I would like to put some of my --switches into a configuration way. I suppose no-one has tried bending Cmdliner into supporting that as well?
<flux> I was thinking I could give it my loaded values as default values for the arguments, but that would then change the documentation (--help) as well..
angerman has quit [Read error: Connection reset by peer]
sw1nn has joined #ocaml
angerman has joined #ocaml
noisetonepause has joined #ocaml
talzeus has joined #ocaml
talzeus has quit [Read error: Connection reset by peer]
noisetonepause has left #ocaml []
sagotch has joined #ocaml
rainbyte has joined #ocaml
adrien_o1w is now known as adrien_oww
nikki93 has joined #ocaml
malo has joined #ocaml
nataren has joined #ocaml
nikki93 has quit [Ping timeout: 252 seconds]
nataren has quit [Ping timeout: 265 seconds]
kyrylo has joined #ocaml
_andre has joined #ocaml
sagotch has quit [Quit: Page closed]
ygrek has quit [Ping timeout: 272 seconds]
jonludlam has joined #ocaml
cago has quit [Quit: Leaving.]
cago has joined #ocaml
syntropy has joined #ocaml
Guest_ has quit [Quit: Computer has gone to sleep.]
csakatok_ has quit [Remote host closed the connection]
hyperboreean has joined #ocaml
hyperboreean has quit [Client Quit]
hyperboreean has joined #ocaml
a-pyon-ement has joined #ocaml
cago1 has joined #ocaml
cago has quit [Read error: Connection reset by peer]
Guest_ has joined #ocaml
nikki93 has joined #ocaml
The-Mad-Pirate has joined #ocaml
nikki93 has quit [Ping timeout: 260 seconds]
avsm has joined #ocaml
avsm1 has joined #ocaml
ygrek has joined #ocaml
avsm has quit [Ping timeout: 245 seconds]
avsm1 has quit [Quit: Leaving.]
dsheets has quit [Ping timeout: 245 seconds]
<gasche> ggole: it's not possible to remove the indirection because of representation issues
<gasche> if you could do
<gasche> newtype erased_existential = Erased : 'a -> erased_existential
<gasche> then you could build
<gasche> [| Erased 0.; Erased "toto"; Erased true |]
<gasche> and hell would break loose
<gasche> (because this may be considered a floating-point array, for example)
<companion_cube> o/
<ggole> Hmm, I still don't see the problem
<ggole> The implementation needs to not use a specialised float array there, true
<companion_cube> agreed
nataren has joined #ocaml
<gasche> there are non-parametric operations in the runtime that are not safe with respect to values at an absolutely unknown types
<flux> can ocaml reasonably support both boxed and unboxed float arrays then?
<flux> or does it already
<flux> I suppose it must support them via 'a Array.t
<gasche> yes
uggwar_ has joined #ocaml
<flux> hmm, so all code must dynamically support both then as well?
<ggole> gasche: I'm not sure that such types would be "exposed" in that way, though
<flux> or not
<ggole> You couldn't actually write the type you suggest, for instance
<flux> can a 'a array end up as float array in some other context
<flux> so there is no actual way to actually create 'a array so that 'a is float and the floats would be boxed?
<ggole> No, there's a check
<ggole> At runtime
nataren has quit [Ping timeout: 264 seconds]
<ggole> gasche: wait, never mind. I was thinking that the 'a would be unbound, but that's wrong.
<gasche> even if we removed all the non-parametric operations from the runtime (I personally think the language would be better off), non-tagged floats would be quite problematic for calling conventions of parametric functions
<ggole> Yeah, I can imagine :(
<gasche> hm
<gasche> it would probably be possible to make it work nevertheless
<gasche> I think currently float are boxed unless they're used in context where the type-checker knows that they don't need to be
<gasche> so Erased would do that as well
<gasche> (or maybe it doesn't depend on the type-checker but later retyping at lower levels; anyway)
<ggole> For the use case I'm thinking of, the type is always a variant
<ggole> Which (I think) would be less problematic for the implementation
nikki93 has joined #ocaml
<gasche> indeed
<gasche> then you can probably use Obj.t with an abstract interface if you really need to
<gasche> but I'd use the GADT solution
<ggole> At the moment I'm using regular variants and good old assert false.
<ggole> ...enough of assert false to give me a bit of an itchy feeling, actually :/
<gasche> I don't see how existential wrapping could be replaced by assert false
nikki93 has quit [Ping timeout: 265 seconds]
root_empire has joined #ocaml
<ggole> The existential wrapping is just a trick to let me say "this value can be any leg of the GADT"
<ggole> With regular variants you have that for free: and for the cases where you want a particular flavour, you assert false.
<gasche> ok
<gasche> you could use polymorphic variants
michael_lee has quit [Ping timeout: 265 seconds]
<gasche> hm
jonludlam has quit [Ping timeout: 245 seconds]
<companion_cube> gasche: do you think Gallium could get an intern to work on ocaml-ty? ^^
yacks has quit [Ping timeout: 245 seconds]
<adrien_oww> :)
<gasche> type 'a t =
<gasche> | Foo : [> `Foo ] t
<gasche> | Bar : [> `Bar ] t
<gasche> let is_foo : [ `Foo ] t -> unit = function Foo -> ()
<gasche> let list_of_any_t = [ Foo; Bar ]
<gasche> I don't generally recommend GADTs indexed by polymorphic variants, because I don't really understand how they work
<companion_cube> adrien_oww: you hilight on this, don't you? :P
<gasche> but in this case, they may do the job
<gasche> companion_cube: would you volunteer to be such an intern?
<companion_cube> :D
<gasche> some people do take internships in the middle of their PhD
<ggole> We've been there before: I recall that polymorphic variants don't work with GADTs in some way
<companion_cube> but it's not related to my PhD :s
<gasche> but I must tell you, I think this is a tricky subject
<ggole> (IIRC there was a change at some point, but I don't know what it is.)
<gasche> yeah
<adrien_oww> companion_cube: no, I slack all day long, that's different
<gasche> I think existential wrapping with an extra constructor is your best bet ggole
<ggole> This was back when I was playing around with subtypes of GADTs - the operand type problem, if you remember that
<ggole> Hmm, ok :(
<gasche> but if you want to avoid the indirection because you're writing oh-so-efficient code, you may want to get dirty
<gasche> I remember this discussion, yes
<companion_cube> gasche: btw, I've re-implemented a kind of unrolled list for Enum.force/Gen.persistent ;)
<Simn> What's that `Foo syntax? I don't think I've seen that before.
root_empire has quit [Max SendQ exceeded]
<gasche> it's an advanced feature you don't generally need to know about, but which is nice in some situations (and often a source of complexity)
<ggole> The problem is that I have to construct (possibly somewhat long) vectors of these "any" types, so indirection hurts once per element rather than just once.
<ggole> I'm probably worrying prematurely though, so I'll go with the existential and hack it up if it turns out to be a problem.
<gasche> that's nice companion_cube
<gasche> ggole: yeah, I think that's the better choice
root_empire has joined #ocaml
ygrek has quit [Remote host closed the connection]
<ggole> Hand-unrolled lists... I wonder if it would be possible to derive a cdr-coding like transformation on variants automatically.
<gasche> companion_cube: but I don't really understand your implementation
<Simn> gasche, I see, thanks.
<gasche> why is the integer argument of Partial immutable, why cons is a ref?
<gasche> that seems inconsistent
<gasche> eg. you could just use type 'a mlist = 'a chunk list ref and 'a chunk = Vect : 'a array | Partial : 'a array * int ref
<gasche> hm
<gasche> no, you'd need a mutable list here, so maybe the mutable cdr makes sense
Guest_ has quit [Quit: Computer has gone to sleep.]
<companion_cube> well, I just hacked this quickly this morning
ygrek has joined #ocaml
Thooms has quit [Ping timeout: 264 seconds]
<gasche> so you don't have performance numbers yet?
<companion_cube> yes I do
<gasche> I would be interested for example in how much faster than BatList this is for List.map on large sequences
<gasche> I would expect the batched allocation to make it sensibly faster on trivial inlined functions
root_empire has quit [Max SendQ exceeded]
<companion_cube> gasche: I think the idea is nice in that it makes bigger and bigger chunks
<gasche> yeah
<companion_cube> so it's not wasting too much on small iterators, but still scales on big iterators
<companion_cube> of course it can still be refined
<gasche> it's like dynamic arrays, expect you don't need to merge back at resize points because you don't have random access
<companion_cube> yep
<companion_cube> it's really the simplest container ever, regarding the interface
<companion_cube> of_gen/to_gen
<gasche> François has a similar design for Queue in his drawers, we just never cared enough to put it in production
<gasche> (it doesn't have Obj.magic and goes faster than the current code; I think his buffers are fixed-size though)
a-pyon-ement has quit [Quit: Page closed]
<gasche> (but capping at 4096 is probably reasonable)
<companion_cube> yeah, it's already quite big a buffer :D
<companion_cube> a chunk*
<companion_cube> I may use it for Sequence, also
<companion_cube> anyway, the design may be improved
<companion_cube> (merging Partial and Cons together for instance)
<companion_cube> (avoids the Array.sub for the final chunk)
rainbyte has quit [Ping timeout: 260 seconds]
<ggole> Hmm, CDR-coding in OCaml would seem to require upping the tag space another bit: a non-starter, really.
<ggole> It would probably be ok for 64-bit systems, though... hmm.
<companion_cube> stop eating tags! :D
<ggole> I mean the low bit that you get on non-pointer values
<ggole> It'd have to be 2 bits (I think).
Victorutsc has left #ocaml []
<ggole> Actually, the tag word might be a better place. I forgot that Lisp implementations don't have that room (they usually use 2-word conses).
* ggole sticks the idea on the shelf
shinnya has joined #ocaml
avsm has joined #ocaml
jonludlam has joined #ocaml
dsheets has joined #ocaml
darkf has quit [Quit: Leaving]
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 245 seconds]
ygrek has quit [Ping timeout: 265 seconds]
palomer has joined #ocaml
ollehar has joined #ocaml
rand000 has joined #ocaml
thomasga has joined #ocaml
diginux has quit [Read error: Operation timed out]
diginux has joined #ocaml
nataren has joined #ocaml
malvarez has joined #ocaml
Eyyub has joined #ocaml
nataren has quit [Ping timeout: 272 seconds]
avsm has quit [Quit: Leaving.]
sagotch has joined #ocaml
Eyyub has quit [Quit: Lost terminal]
<sagotch> I have a compilation problem since this morning. it is probably trivial to solve but I do not see what is wrong...
<sagotch> ocamlfind ocamlc -package unix,str,toml -o pastek type.cmo parser.cmo lexer.cmo render.cmo render_html.cmo pastek.cmo File "_none_", line 1: Error: Error while linking parser.cmo: Reference to undefined global `Str'
<sagotch> why cant ocamlfind find str ?
<adrien_oww> sagotch: does toml depend on str?
<adrien_oww> also
<adrien_oww> you need -linkpkg
<sagotch> ah... thanks for the -linkpkg
<sagotch> It works :)
<adrien_oww> :)
ygrek has joined #ocaml
oriba has joined #ocaml
avsm has joined #ocaml
cago1 has left #ocaml []
sw1nn has quit [Ping timeout: 245 seconds]
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 245 seconds]
mika1 has quit [Quit: Leaving.]
<sagotch> And what is the problem of this one?
<sagotch> ocamlfind ocamlc -I ../src -package unix,str,toml,oUnit -linkpkg -o parser_basic.test parser_basic.cmo type.cmo parser.cmo lexer.cmo File "_none_", line 1: Error: Error while linking parser_basic.cmo: Reference to undefined global `Parser'
<sagotch> parser.cmo is in ../src/parser.cmo
<sagotch> (cmo/cmi, everything is here)
<adrien_oww> link order in ocaml is left to right
<adrien_oww> so parser.cmo should appear first
<adrien_oww> well, before parser_basic.cmo
<sagotch> oups...
<sagotch> I did not write a ocaml makefile for a whilem sorry
<adrien_oww> you shouldn't do it at all nowadays
<adrien_oww> using oasis is the canonical way now
shinnya has quit [Ping timeout: 265 seconds]
Thooms has joined #ocaml
amirmc has joined #ocaml
<sagotch> I should learn how to use oasis, but using menhir + bisect + having "<<" operators in code messing up with camlp4 seems to make things hard to handle with automated tools (and I have 6 files in my project...)
<Drup> menhir and camlp4 are very easy to integrate in oasis, probably easier than with makefiles
<Drup> (I don't know bisect, can't say anything about it)
caligula has quit [Remote host closed the connection]
caligula has joined #ocaml
AdmiralBumbleBee has joined #ocaml
kaustuv has joined #ocaml
<sagotch> the only issue with bisect is that it use camlp4
<Drup> it's not a problem with oasis
philtor has joined #ocaml
<sagotch> I can not find how to disable quotations, have any idea?
<sagotch> and I did not find any reference to no_quot in doc
mort___ has joined #ocaml
<sagotch> using a line like ` ocamlfind ocamlc -package bisect -linkpkg -syntax camlp4o -o bytecode source.ml`
<sagotch> hum, okay -ppopt is good for me
nikki93 has joined #ocaml
jonludlam has quit [Ping timeout: 260 seconds]
sagotch has quit [Ping timeout: 245 seconds]
nikki93 has quit [Ping timeout: 260 seconds]
arj has joined #ocaml
arjunguha has joined #ocaml
syntropy has quit [Quit: Page closed]
jonludlam has joined #ocaml
nataren has joined #ocaml
lovethroat has joined #ocaml
nataren has quit [Ping timeout: 265 seconds]
kaustuv has left #ocaml []
oriba has quit [Read error: Operation timed out]
oriba has joined #ocaml
Kakadu has quit [Ping timeout: 245 seconds]
nataren has joined #ocaml
nikki93 has joined #ocaml
nataren has quit [Remote host closed the connection]
Arsenik has joined #ocaml
philtor has quit [Ping timeout: 260 seconds]
nikki93 has quit [Ping timeout: 264 seconds]
arj has quit [Quit: Leaving.]
arjunguha has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
arjunguha has joined #ocaml
pminten has joined #ocaml
wolfnn has joined #ocaml
sw1nn has joined #ocaml
jao` has joined #ocaml
jao` has quit [Changing host]
jao` has joined #ocaml
jonludlam has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 252 seconds]
thomasga has quit [Quit: Leaving.]
amirmc has quit [Quit: Leaving.]
smerz has joined #ocaml
<mrvn> Is there a module to handle translating between on-disk data structures and ocaml types that supports bigarray? I don't think I need bit granularity, byte as lowest unit should suffice.
srcerer_ is now known as srcerer
<companion_cube> don't memory mapping operations of Bigarray suffice?
sw1nn has quit [Ping timeout: 245 seconds]
<mrvn> companion_cube: then how do I extract a struct { int32_t foo; int32_t bar; int64_t blub; } [] from that?
<mrvn> companion_cube: including endian conversion if needed
<adrien_oww> mrvn: bitstring?
rand000 has quit [Quit: leaving]
<companion_cube> every time I look at this lib I find it amazing, even though I don't need it
<mrvn> adrien_oww: xeah, except now for bigarray please
<mrvn> s/x/y/
nataren has joined #ocaml
<johnelse> mrvn: cstruct?
<mrvn> That looks promising.
ygrek has joined #ocaml
oriba has quit [Quit: oriba]
<mrvn> I wagely remember something bigger though that would convert a whole struct into an ocaml type and back, not just create functions to access the elements. Something they used to implement ssh in ocaml.
ulfdoz has joined #ocaml
Kakadu has joined #ocaml
<palomer> someone should create an ocaml virtual machine chrome extension
pminten has quit [Quit: Leaving]
<palomer> that would be SO cool
<mrvn> palomer: nacl?
ollehar has quit [Ping timeout: 246 seconds]
<palomer> so cool!
<r0b1> might be some work to get ocaml working with nacl?
<palomer> the project seems to be dead :/
arjunguha has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<r0b1> nacl is developed under chrome
<r0b1> shouldn't be dead
thomasga has joined #ocaml
<NaCl> NaCl?!
<r0b1> sorry
<NaCl> :P
angerman has quit [Read error: Operation timed out]
<palomer> I meant ocaml-nacl
<r0b1> ah
<r0b1> yeah
<r0b1> just found that as well
<r0b1> it looks very dead
thomasga has quit [Ping timeout: 245 seconds]
avsm has quit [Quit: Leaving.]
<Drup> palomer: obrowser
<Drup> :D
<Drup> it's an ocaml virtual machin, and it runs in chorme :D
<Drup> chrome*
zpe has joined #ocaml
zpe has quit [Read error: Connection reset by peer]
<palomer> :P
<palomer> it's also really slow :/
<Drup> (also, fwiw, ocaml code with js_of_ocaml in a browser is as fast or faster than ocaml bytecode)
zpe_ has joined #ocaml
<palomer> ah yes, the venerable js_of_ocaml
<palomer> that's definitely a possibility
<Drup> venerable ?
<Drup> it's not that old
<palomer> at least a year
<palomer> maybe 2?
<Drup> that's not old, in the ocaml landscape xD
<mrvn> 2 years? Not even old enough that I would have tried it yet.
<Drup> (and more like 3, iirc)
<palomer> ah yes, more like 3
nataren has quit [Remote host closed the connection]
aurynj has quit [Quit: Leaving]
avsm has joined #ocaml
sw1nn has joined #ocaml
Anarchos has joined #ocaml
avsm has quit [Quit: Leaving.]
Moataz-E has joined #ocaml
Moataz-E has left #ocaml []
angerman has joined #ocaml
nikki93 has joined #ocaml
ygrek has quit [Ping timeout: 252 seconds]
mort___ has quit [Quit: Leaving.]
angerman has quit [Quit: Gone]
caseyjames has joined #ocaml
johnelse is now known as johnelse_away
<caseyjames> Hola, in regards to linking in opt libraries - can I link they statically? Do I need interface files? Is there a good resource describing how I might statically link opt libraries?
<caseyjames> can I link them statically? - sorry for the typo
Myk267 has quit [Quit: Myk267]
angerman has joined #ocaml
<Drup> static link is the default
malvarez has quit [Ping timeout: 272 seconds]
<uggwar_> there's a lot of talk about ocaml's support (or lack thereof) for concurrency. can someone please enlighten me, so that i can get rid of my ignorance?
<Drup> uggwar_: you probably mean parallelism
<uggwar_> if i want to take advantage of my computer's 8 cores; how do i do it in ocaml?
<uggwar_> Drup: yes, that is the correct term. sorry :-)
<palomer> ocaml is single threaded
<palomer> you have to run multiple processes
<Drup> no problem, the confusion is common and understandable
<adrien> ocaml isn't single-threaded; allocations are
<palomer> everything is
<palomer> well, apart from whatever external libraries you're using
<uggwar_> palomer: ok, so how is this performancewise?
<nlucaroni> uggwar_ : to use right now, you can use ocaml-mpi, parmap, async, or lwt.
<palomer> 8 processes vs 8 threads?
<uggwar_> yes
<palomer> processes don't have shared memory
<palomer> they each have their own stack
<Drup> that doesn't answer the question ...
<Drup> uggwar_: so, you have multiple solutions
<Drup> uggwar_: either you fork manually and do the whole stuff by message passing
<uggwar_> i really like ocaml better than, say, haskell... so i need to find a reason not to learn something else ;)
dsheets has quit [Ping timeout: 252 seconds]
<Drup> it's possible, and it will work well for certain styles of problems
<Drup> there is several libraries to help you do that
<uggwar_> i've read about jane street's async.parallel
<Drup> you have Ocamlnet, parmap and async.parallel, mostly
<uggwar_> but the net is polluted with all kinds of noise...
AltGr has left #ocaml []
<Drup> don't mistake parallelisme with concurency, ocaml has two big library for concurency, async and lwt, but they don't offer parallelism
<palomer> ocaml.parallelism is just a way to spawn processes and communicate with them
<Drup> yes, it's a library to ease the whole "let's fork and do message passing"
<uggwar_> ok, so i have nothing to fear about multi processing in the future?
<Drup> yes, and no
<uggwar_> hehe
<palomer> ocaml is probably not the best language for doing multi core computationally intensive programming easily
<Drup> no, because we never going to have auto-parallelism
<Drup> your map on a list is never going to be automagically parallelized
<Drup> (Scala does that)
<uggwar_> well, i don't need that
<Drup> and for application that requires a lot of communication between the various task, it's not going to be great
dant3 has quit [Read error: Connection reset by peer]
<uggwar_> scala is sort of nice, but it belongs on a server. i want something a language to go to for client side as well
dant3 has joined #ocaml
<Drup> if your application requires few communication, then it's just fine
<palomer> ocaml strengths: fast, well typed, relatively simple, good gc, well designed
<palomer> ocaml weaknesses: no support for multi threading
<Drup> there is work going for a // gc
<palomer> ah yes, by that group in cambridge
<uggwar_> nice, any progress? :)
<Drup> it's going on
<Drup> we will see how it is at the end :p
<uggwar_> well, 10 months since the last commit
<Drup> there is also luca's reentrant runtime that allows interesting stuff, but it's based on ocaml 3.12
<palomer> uggwar_, you might want to consider haskell. haskell strengths: multi threading is trivial, mechanisms for keeping code pure. haskell weaknesses: purity obsession makes code unreadable. debugging is a pain. lazy evaluation can result in a vast increase in allocations
<palomer> and fanatical fan base
<uggwar_> palomer: yes, there are stuff i like about haskell, but i agree about it's weaknesses
<uggwar_> i think ocaml is far more pragmatic. and easier to get performant
<palomer> for stuff that's IO bound, use lwt
<uggwar_> the whole signle threaded gc makes me a bit sad :)
<palomer> and use your other cores to run other processes
<Drup> uggwar_: it's going to be solved
malvarez has joined #ocaml
<palomer> one big advantage of lwt: no need to put locks
<uggwar_> Drup: i think so to. lot's of stuff happened lately. ocamlpro, jane street etc
<uggwar_> how would zeromq or nanomsg work for inter communication between processes?
lovethroat has quit [Ping timeout: 264 seconds]
ulfdoz has quit [Ping timeout: 260 seconds]
<uggwar_> i've also heard that it's tough to optimize haskell. ocaml seems a lot more tuneable
<Drup> ghc is quite complicated indeed :D
<uggwar_> it's a beast :)
<uggwar_> and i don't code to be a snob ;)
<palomer> true
<uggwar_> guess what; i bet on ocaml and a solution to the parallelism by the time i master it :)
<palomer> one of haskell's appeal is its image
<uggwar_> yes, "i usually code haskell myself"...
<palomer> "I'm smarter, so I want to use a more difficult programming language"
<uggwar_> i'll continue reading RWO and just relax. thanks for the information!
<uggwar_> hehe
<palomer> then again, there's a bit of that here too
<palomer> (though, not as much)
<uggwar_> well, the world is moving towards javascript with nodejs, and i refuse
<Drup> (and this channel is less crowded than #haskell :D)
<uggwar_> i'd rather find something else to do. like gardening
<Drup> uggwar_: ocaml over js_of_ocaml over node_js ? :3
<uggwar_> Drup: i need to google that :)
mreca has joined #ocaml
<palomer> start with js_of_ocaml
<uggwar_> sounds nice :)
<uggwar_> another fantastic thing about ocaml is that i manage to build ocaml 4.01.0 with lots of libraries on my raspberry pi in less than an hour
<uggwar_> had to increase the swap a bit for core.kernel tho
<uggwar_> :)
<uggwar_> core_bench seems to have some intel asm that failed as well
<uggwar_> not sure tho
<palomer> yeah, ocaml is tight
ggole has quit []
jave has quit [Quit: ZNC - http://znc.in]
nlucaroni has quit [Quit: leaving]
jave has joined #ocaml
<palomer> if it's any indication, credit suisse moved away from haskell towards F#
<Drup> (imho, that indicates more money wrt Microsoft than a real technical choice)
<Drup> (but, well ...)
<uggwar_> i would never teach myself a language that is platform dependant. wrong in so many ways :)
<adrien> (or they also had .net)
<adrien> f# runs on mono too
<adrien> mono has a crap GC too; but that's anothe rmatter ;p
<uggwar_> i've understood that the gc in ocaml is extremely good. it's just not parallel
<adrien> there's a link between these two facts ;-)
<uggwar_> :)
sw1nn has quit [Ping timeout: 260 seconds]
nataren has joined #ocaml
<r0b1> i would have thought that a garbage collector that doesn't pause your code would be the best option
<flux> r0b1, but there are always tradeoffs
<adrien> r0b1: it's not difficult to keep a good latency in ocaml
<r0b1> yeah, truth is in the details
<adrien> takes some care but it's definitely something that can be done
sw1nn has joined #ocaml
nataren has quit [Ping timeout: 272 seconds]
nataren has joined #ocaml
arj has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
thomasga has joined #ocaml
mmachenry has joined #ocaml
ollehar has joined #ocaml
<mmachenry> I am trying to duplicated what I've seen in many janestreet packages for building my source with oasis and testing with a test executable using ounit but I'm getting circular dependencies. When I build the project without a library and tests it's fine, so I know the ode is okay. This is my github repo: https://github.com/dskippy/pcf
nikki93 has quit [Remote host closed the connection]
<companion_cube> mmachenry: I didn't look at the code, but in my experience such problems about circular deps come from missing modules
<companion_cube> ie; modules that are used within the library, but not listed in it
<mmachenry> companion_cube: Oh, I did skimp on what I exported just for this test, I'll try that.
dsheets has joined #ocaml
<companion_cube> if ocamlbuild gives you a list of modules that make a loop, the culprit is among them
<mmachenry> Also do you know if it's necessary to make my code be a library just to make the testing work for oasis?
<mmachenry> I named my library something that doesn't exist, just a name for the whole set of modules, which is what a *lot* of example code does.
<mmachenry> But I get a warning about it.
sw1nn has quit [Ping timeout: 252 seconds]
<mmachenry> companion_cube: That was it! Thanks :)
<mmachenry> It wasn't ciclic, it was missing.
<mmachenry> Weird error message.
<Drup> mmachenry: you should use the InternalModules field for stuff you don't want to export
<mmachenry> Drup: Makes sense.
<mmachenry> Do people often make a separate directory for their main.ml and have the lib elsewhere so that it can depend on the lib?
<mmachenry> Or would you just keep that in the same sub dir?
<Drup> it's cleaner
mreca has quit [Quit: Textual IRC Client: www.textualapp.com]
<mmachenry> What's cleaner, the internal? Or the separate dirs?
<Drup> separate dirs
<mmachenry> So you think I should have a dir with one file that's my mail.ml and tell oasis to build the executatable from that dir and depend on my library, which is everything in another dir?
<Drup> InternalModules are also usefull, for different purposes
<mmachenry> Will internal modules be visible to an executable I build from another directory if I include it as some of my depends?
<Drup> the issue with "everything in one dir" is that ocaml may use stuff that are not exported silently
<Drup> No
<Drup> may use silently stuff that are not exported*
_andre has quit [Quit: leaving]
sw1nn has joined #ocaml
<mmachenry> So now I can a new file that my build creates for me called pcf.mlpack since I named the library pcf.
<mmachenry> :-\ Do I need to have this new auto gen code in my src directory?
<Drup> it will be regenerated anyway
<Drup> you can even delete it, it will be generated again when you run oasis setup
mort___ has joined #ocaml
<mmachenry> If I'm just making an executable that's not necessarily intended as a library, is there a common convention for how to organize the files?
<mmachenry> I currently have src/ and test/
<mmachenry> I could make lib/ test/ and main/
<companion_cube> src/ test/ looks good to me
<mmachenry> companion_cube: And I'll have main.ml in with my other code? I like that because it feels like it belongs together. But I will need to have an executable that depends on the library I'm making out of that code.
<mmachenry> Or maybe since it's in the same dir it won't need to depend.
<mmachenry> Just the tests need to work that way.
<Drup> if it's in the same dir, no, it doesn't
<Drup> but do add the relevant modules in InternalModules
<mmachenry> Sorry for the questions all over the map. I really like OCaml but I find it's a hard language to get into for some really basic mechanics reasons.
<Drup> (personally, I had issue with this way, because you may forget to export stuff, and so on, but that's more of a library issue. Not an issue for executables)
<mmachenry> I'm just trying to get a prescriptive plan for how to make most projects.
<companion_cube> mmachenry: no pb
<Drup> mmachenry: you are right, the build system question is not really well solved in ocaml
<companion_cube> you can also look at other _oasis files on the web
<mmachenry> companion_cube: Yep, been looking at a bunch.
<companion_cube> the Lwt one is really good
<mmachenry> Until you told me though, I didn't realize that my circular deps issue was just missing deps. Weird errors.
<adrien> gasche: around?
jonludlam has joined #ocaml
ulfdoz has joined #ocaml
<mrvn> 2 years? Not even old enough that I would have tried it yet.
<mrvn> ups, ewin
* adrien rules out the fact that the conversation was about babies
<mrvn> type _ key_value = | Int_key_value : (int * int) -> int key_value | Float_key_value : (int * float) -> float key_value type t = key_value list
<mrvn> How do I have to write t to have a list of mixed int and float key_values?
<bernardofpc> http://paste.debian.net/82600/ -> so, this is more or less cleaned version with tons of global lablgtk variables
S11001001 has joined #ocaml
S11001001 has quit [Changing host]
S11001001 has joined #ocaml
<adrien> gasche: basically, I'm looking for early feedback on an email title "[RFC] Remaining changes for cross-compilation support in OCaml" that I'll send soonish to the caml-list; draft is at http://pastebin.notk.org/pastebin.php?show=m588a0126
nataren has quit [Remote host closed the connection]
sw1nn has quit [Read error: Operation timed out]
philtor has joined #ocaml
palomer has quit [Ping timeout: 245 seconds]
erider has joined #ocaml
erider has quit [Remote host closed the connection]
keithflower has quit [Quit: keithflower]
sagotch has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
axiles has quit [Remote host closed the connection]
dant3 has quit [Remote host closed the connection]
arjunguha has joined #ocaml
Thooms has quit [Quit: WeeChat 0.3.8]
<sagotch> make[1]: Entering directory `/home/ju/workspace/pastek/pastek/src' menhir parser.mly ocamlfind ocamlc -I ../src -package unix,str,toml,oUnit,bisect -syntax camlp4o -ppopt -no_quot -linkpkg -c parser.ml rm parser.ml make[1]: Leaving directory `/home/ju/workspace/pastek/pastek/src'
<sagotch> oups
<sagotch> sry for format, but is the ` rm parser.ml` just before make exiting done by ocamlfind?
<adrien> doubtful
nikki93 has joined #ocaml
mmachenry has quit [Quit: Leaving.]
nlucaroni has joined #ocaml
<nlucaroni> Is there a polymorphic function for pretty printing tables/matrices with aligned column widths?
caseyjames has quit [Quit: Page closed]
<mrvn> not in stdlib
ousado has quit [Ping timeout: 248 seconds]
<mrvn> Printf.printf can to fixed with printing if that is enough for you
ousado has joined #ocaml
<nlucaroni> sure, I was hoping for a function that would accept another pp_* function for an element of the matrix and format accordingly.
<mrvn> easy enough to write
lovethroat has joined #ocaml
Thooms has joined #ocaml
lovethroat is now known as yellowfish
yellowfish has quit [Changing host]
yellowfish has joined #ocaml
ulfdoz has quit [Ping timeout: 240 seconds]
NoNNaN has joined #ocaml
angerman has quit [Quit: Gone]
jonludlam has quit [Ping timeout: 265 seconds]
Arsenik has quit [Remote host closed the connection]
krono has joined #ocaml
<krono> hi
<krono> can somebody enlighten me what an “infix block” is?
<Drup> krono: in what context ?
<krono> the docs I find on the net say, it would be a special block within a closure
S11001001 has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<krono> (ocaml bytecode)
<krono> what is so special about it?
arj has quit [Quit: Leaving.]
<Drup> "it" ? :)
<Drup> Just post the link to this documentation
shinnya has joined #ocaml
<krono> Bytecode 44, CLOSUREREC
mmachenry has joined #ocaml
<mrvn> sounds like internal details that shouldn't concern you unless you want to work on the compiler/interpreter itself.
<krono> mrvn: I’m writing an OCaml VM
<krono> so it concerns me :)
smerz has quit [Ping timeout: 245 seconds]
kyrylo has quit [Quit: Viva la revolucion!]
<Drup> ( krono : you do realize the total absence of context you put in your ultra-specific question, do you ? :D)
<krono> Drup: jep
<krono> I hoped some interpreter guru would be in this channel by chance :)
<Drup> I think you're better off with asking the mailing list
<Drup> you can also try to see the ocapic project, I think they have an interesting documentation about the bytecode
<krono> Drup: thanks for the pointer!
<mfp> krono: maybe this snippet from js_of_ocaml could help you http://paste.debian.net/82620/
<krono> mfp: thank you
<mfp> does it make any sense to you?
<krono> a bit
<Drup> krono: what are you trying to do with a VM ? just having fun ?
<krono> Drup: research :
<krono> :)
<Drup> sure, but about what exactly ? :p
sagotch has quit [Ping timeout: 240 seconds]
<krono> I need a vehicle (ie, execution model/language) that has immutability and n-ary constructors
<krono> I test some data optimizations there
<krono> ML/Caml/OCaml fits theses ideas
<companion_cube> don't be shy, use metaOCaml already :p
nlucaroni has left #ocaml []
sagotch has joined #ocaml
<krono> companion_cube: ocaml is one of the languages only with racket being the second one
<Drup> krono: so you definitely want to check ocapic and js_of_ocaml, they both have (quite aggressive) optimization pass on the bytecode
<krono> Drup: I leave that kind of optimiziation to RPython
<companion_cube> Drup: which optimizations does js_of_ocaml perform?
mmachenry has quit [Quit: Leaving.]
<companion_cube> (and would they apply to regular code too?)
<Drup> it's still on bytecode, so you can't pipe it again in the compiler for native code
mmachenry has joined #ocaml
<Drup> but lot's of inlining and dead code elimitation. there is stuff with TCO too, but that's mostly related to weird javascript issues
<adrien> plus they target specific platforms: bare metal pic for one and javascript in a browser for the other
<Drup> yep
dant3 has joined #ocaml
<companion_cube> well, the previous compilation stages could also benefit from more agressive inlining
<companion_cube> and dead code elimination too, anyway
nataren has joined #ocaml
<Drup> companion_cube: well, ocapic both work on the assumption that the code is going to be self-contained, which is mostly not true for the compiler.
<Drup> ocapic and js_of_ocaml*
<companion_cube> depends on whether you compile a binary or a library...
<adrien> and if you want dynlink :P
<Drup> ^
<companion_cube> I still don't understand this. When does dynlink work actually?
<companion_cube> I mean, you can call Dynlink functions directly, sure
<companion_cube> but can you compile and link dynamically in a transparent way?
dant3 has quit [Ping timeout: 264 seconds]
<Drup> companion_cube: you can do far less dead code elimination in the presence of dynlink
<companion_cube> in the dynlinked library, or the dynlinking program,
<companion_cube> ?
<bernardofpc> work on the assumption that the code is going to be self-contained -> by the way, it could be nice that ocamlc warned if some variant is declared but never produced
nataren has quit [Ping timeout: 265 seconds]
<bernardofpc> of course, it could be produced by some other module using the compilation unit, but in many cases the compilation unit is the only place where the variants get created
<Drup> companion_cube: in the dynlinked lib
<companion_cube> Drup: but that's not the common case
<companion_cube> most libraries are statically linked
<Drup> except they *could* be dynlinked
<companion_cube> and when you compile a .cmxa, you should be able to optimize a lot
<companion_cube> a .cmxa ?
<Drup> the compiler assume possible dynlinking by default
<companion_cube> the compiler really lacks optimization flags
<Drup> (there is a specific flag -no-dynlink)
<adrien> cmxa is what is used to produce cmxs :)
<adrien> -no-dynlink saves space but not a lot
<companion_cube> adrien: oh. Didn't know that
<Drup> but yeah, this area of the compiler was just not worked on, because of Dynlink
<Drup> (well, I suppose it's the reason)
<companion_cube> all that for dynamic linking that currently isn't used much
<companion_cube> ...
<adrien> not sure if it's the main reason you get large binaries; I'm under the impression ocaml simply emits lots of ASM
<adrien> anyway, good night
<bernardofpc> I faced some situation where a variant "disappeared" after some refactoring, and it could be nice if the compiler noticed that no function used it and raised a warning
sillyotter has joined #ocaml
<Drup> bernardofpc: shouldn't that be mostly detected by incomplete pattern matching ?
<adrien> there is some stuff now but overall, you won't get that
<companion_cube> adrien: and no code cleaning is done
<bernardofpc> Drup: it's the other way around, i declare type t = A | B | C | D and ended up not producing C
<bernardofpc> but I still matched all cases
<adrien> when I write C code, binary size changes very little; when I write OCaml, it increases noticeably
<Drup> bernardofpc: well, it's *technically* not really an issue :p
<adrien> of course, OCaml is higher level but the difference still seems large
<Drup> bernardofpc: but yeah, I see what you mean
<adrien> GADTs!
<bernardofpc> it's something like "unused variable blah", but instead "unused type variant Foo"
<bernardofpc> (this could be even enforced if there was an accompaning .mli that hid the variant under "type t", so the ocmpiler knows no-one else is able to refer to them)
jao` has quit [Ping timeout: 264 seconds]
sillyotter has quit [Quit: Leaving]
<bernardofpc> ocamlbuild question: are there any examples of _tags file ?
<companion_cube> a lot! :)
<bernardofpc> specifically, if I want to pass -w A to ocamlc/ocamlopt, is it just ocaml: -cflags "-w A" ?
<companion_cube> hmmm
mmachenry has quit [Quit: Leaving.]
<Drup> bernardofpc: tag warn_a
<Drup> warn_A, actually
mmachenry has joined #ocaml
<Drup> if you are looking for a tag, you can grep "ocamlbuild -documentation"
sagotch has quit [Remote host closed the connection]
nikki93 has quit [Remote host closed the connection]
arjunguha has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
pango has quit [Ping timeout: 246 seconds]
<bernardofpc> Warning 35: unused for-loop index i. -> oh
<bernardofpc> using for _ = a to b is not valid... is there a way out withou using ignore(i); inside ?
<Drup> _i
<bernardofpc> nice !
<bernardofpc> will it also work in functions ?
<Drup> yes
<bernardofpc> (that must all take loads of arguments to fit in a polymorphic other)
<bernardofpc> cool
<bernardofpc> thanks Drup !
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
pango has joined #ocaml
kristi_k1dare has joined #ocaml
Thooms has quit [Ping timeout: 265 seconds]
Simn has quit [Quit: Leaving]
krono has quit [Remote host closed the connection]
wolfnn has quit [Ping timeout: 245 seconds]
sw1nn has joined #ocaml
a-pyon-ement has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-20131020]: i've been blurred!]
sw1nn has quit [Ping timeout: 248 seconds]
mort___ has quit [Quit: Leaving.]
Eyyub has joined #ocaml
mmachenry has quit [Quit: Leaving.]
zRecursive has joined #ocaml
darkf has joined #ocaml
nikki93 has joined #ocaml
thomasga has quit [Quit: Leaving.]
nataren has joined #ocaml
shinnya has quit [Ping timeout: 264 seconds]
nataren has quit [Ping timeout: 253 seconds]
nikki93 has quit [Remote host closed the connection]
madroach has quit [Ping timeout: 252 seconds]
madroach has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
nikki93 has joined #ocaml
nikki93 has quit [Remote host closed the connection]
csakatoku has joined #ocaml
nikki93 has joined #ocaml