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/
thomasga has quit [Ping timeout: 252 seconds]
lpw25 has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
dapz has joined #ocaml
seliopou has quit [Quit: whaaaat]
tlockney is now known as tlockney_away
divyanshu has joined #ocaml
divyanshu has quit [Client Quit]
HoloIRCUser has joined #ocaml
HoloIRCUser is now known as _obad___
dant3 has quit [Ping timeout: 252 seconds]
jwatzman|work has quit [Quit: jwatzman|work]
dant3 has joined #ocaml
racycle has quit [Quit: ZZZzzz…]
dotfelix has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 240 seconds]
malo has quit [Remote host closed the connection]
wmealing has joined #ocaml
<wmealing> was i dreaming or at one stage did i see ocaml running in a browser without a plugin and no server side.. google isnt helping.. in my head it had some kind of a test suite with graphics and web..
<companion_cube> http://try.ocamlpro.com/ this?
<companion_cube> or js_of_ocaml in a more general way?
rgrinberg has joined #ocaml
<wmealing> i dont think its the try.omcalpro.com .. i'm researching the latter now
<wmealing> i get the feeling it was the js_of_ocaml.
shinnya has joined #ocaml
<tautologico> try ocaml uses js_of_ocaml
<tautologico> so does iocaml_js
rgrinberg has quit [Quit: Leaving.]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
shinnya has quit [Ping timeout: 240 seconds]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
rgrinberg has joined #ocaml
shinnya has joined #ocaml
manizzle has quit [Ping timeout: 245 seconds]
<rgrinberg> _obad_: i think with 4.02 there's going to be some ppx wrapper around lex/yacc
<rgrinberg> the syntax will be the same but you won't need the mll/mly ceremonial stuff
dnm has joined #ocaml
<Drup> rgrinberg: there is already sedlex as "lex with ppx"
<Drup> (done by alain frisch, go figure :p)
<rgrinberg> ah so it works with 4.01 already?
<Drup> no, it needs expansion points
<Drup> (iirc)
divyanshu has joined #ocaml
shinnya has quit [Ping timeout: 255 seconds]
<dotfelix> can someone sell ocaml to me? ie which problems does ocaml solves really well etc.
<wmealing> i've got a shiny ocaml here, for only $99.99 !
<wmealing> dotfelix: i'm only new at it.. so i'm messing around with it at the moment
<wmealing> dotfelix: what is your programming history
<dotfelix> wmealing: new to function programming, just some C and Go
<wmealing> i know C and go, so i'll do what i can to answer.. people here can correct me if wrong
<wmealing> so, you can program in a functional style, an object style or an imperative style..
<wmealing> so you can kind of.. mix it up as you see fit
<wmealing> ocaml is nearly as fast as C from my naive experiments, much faster than go
<wmealing> ocaml has a type system, which means you can use the type systems to ensure you're not doing stupid things, ie wrong pointers being passed in to a function.
<wmealing> because its compiled (like c and go) it has single file deployment..
<wmealing> i think its kinda like a static compile
<wmealing> it has "pattern matching" , not regex like.. but on the native types within the program.. i do quite a lot of erlang.. so I like that feature
<wmealing> you can, from what ive seen extend (expand ?) the syntax of the language.. to your liking
<dotfelix> yeah I have some erlang into and like pattern matching too
* wmealing nods
<dotfelix> wmealing: what's your take so far on ocaml?
<wmealing> dotfelix: before i go to explain, hows your erlang.. are you familiar with OTP ?
<wmealing> (i'm not having a problem, its relative to your answer)
<dotfelix> wmeanling: not really
<wmealing> ok
<dotfelix> but I do understand is like its std libs
<wmealing> ok.
<wmealing> so i'm familar with leaning hard on erlangs OTP system. allowing the system to recover from my programming/environmental mistakes. Ocaml seems to make me deal with the mistakes more explicitly.. which makes the software development process
<wmealing> quite a bit slower
<wmealing> admittedly, I have been programming in erlang now for about 5 years.. so I'm very familar with how it misbehaves.
waneck has joined #ocaml
<wmealing> ocaml seems to have less "hard" edges than erlang though. The standard libraries seem slightly better thought out
<wmealing> and i'll be the first to admit that I don't always know the shortest/sanest ways to do things.. so its likely there are much better ways.
<wmealing> however, as far as languages go, ocaml seems like a very "nice" language that fits many problems
<dotfelix> g8t to know
<dotfelix> what about concurrency from an erlang comparison
<wmealing> erlang you spin up the processes, then use message passing, which makes things dead easy. From what i can see.. ocaml has a slightly different game plan than erlang
<wmealing> of course only one thing can run on one cpu at any time
<wmealing> you can farm out work to different processes, but that acts more like C than erlangs implementation
<wmealing> actually, i dont think ive looked up actors in ocaml
<dotfelix> ok
manizzle has joined #ocaml
dapz has joined #ocaml
dotfelix has quit [Ping timeout: 265 seconds]
ygrek has joined #ocaml
<rgrinberg> there was a reason thread on reddit that's similar: http://www.reddit.com/r/ocaml/comments/23qjle/why_did_you_choose_ocaml/
studybot_ has joined #ocaml
studybo__ has joined #ocaml
<wmealing> interesting
<wmealing> i can't say i agree with all of the stackxchange reasoning.. but each to their own
<bernardofpc> my own point for OCaml is two-fold; first, because of theorem-proving, which is "the niche application domain of ML of excellence"
seliopou has joined #ocaml
<bernardofpc> second, because it was thanks to OCaml that I wrote a multi-purpose Erathostenes Sieve ; not that it is too hard to do or anything, but just as Dijkstra says, "having the right language allows you to write clearly what you're thinking"
studybot_ has quit [Ping timeout: 240 seconds]
<bernardofpc> anyway, time to sleep
seliopou has quit [Quit: whaaaaat]
seliopou_ has joined #ocaml
studybo__ has quit [Read error: Connection reset by peer]
dnm has quit []
seliopou_ is now known as seliopou
struktured has quit [Ping timeout: 255 seconds]
Nahra has quit [Remote host closed the connection]
tanguy` has quit [Ping timeout: 240 seconds]
Nahra has joined #ocaml
racycle__ has joined #ocaml
Nahra has quit [Remote host closed the connection]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
michael_lee has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
_obad___ has quit [Ping timeout: 258 seconds]
rgrinberg has quit [Quit: Leaving.]
Nahra has joined #ocaml
wmealing has quit [Excess Flood]
wmealing has joined #ocaml
Nahra has quit [Remote host closed the connection]
Nahra has joined #ocaml
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
struktured has joined #ocaml
axiles has joined #ocaml
manizzle has quit [Ping timeout: 245 seconds]
rgrinberg has joined #ocaml
dnm has joined #ocaml
racycle__ has quit [Quit: ZZZzzz…]
ygrek has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
ygrek has quit [Ping timeout: 252 seconds]
wmealing has left #ocaml []
clan has quit [Quit: clan]
clan has joined #ocaml
ygrek has joined #ocaml
clan has quit [Quit: clan]
<whitequark> an API design question: I have an Encoder and Decoder module
<whitequark> Decoder has quite a few errors it can raise, so I've exception Failure of error, and type error = A | B | ...
<whitequark> Encoder has only one error it can raise. currently I have exception Failure of error in Encoder too, and type error = A
<whitequark> should I keep it as is for regularity, or remove the cruft and only leave exception Overflow?
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
Simn has joined #ocaml
ollehar has joined #ocaml
zpe has joined #ocaml
tane has joined #ocaml
Kakadu has joined #ocaml
divyanshu has quit [Ping timeout: 240 seconds]
divyanshu has joined #ocaml
studybot_ has joined #ocaml
studybo__ has joined #ocaml
studybot_ has quit [Ping timeout: 240 seconds]
wwilly has joined #ocaml
ivan\ has quit [Ping timeout: 276 seconds]
shinnya has joined #ocaml
avsm has joined #ocaml
avsm1 has joined #ocaml
divyanshu has quit [Quit: Textual IRC Client: www.textualapp.com]
zpe has quit [Remote host closed the connection]
dnm_ has joined #ocaml
angerman has joined #ocaml
dnm has quit [Ping timeout: 256 seconds]
<companion_cube> whitequark: I'd use a variant for the return type, not an exception, personally
<companion_cube> or provide a _exn alternative that raises
<whitequark> it's a method used internally in protobuf decoders/encoders, and all of the error conditions are truly exceptional
<whitequark> i.e. as long as you use the same protocol on both sides, all but one of these errors will never ever get raised
rand000 has joined #ocaml
<whitequark> actually no, all of them won't
<companion_cube> oh, I see
ggole has joined #ocaml
<whitequark> I could conceivably get by with just exception Error, but that would suck for interoperability with protoc
<whitequark> so I decided to make it much more fine-grainde
mort___ has joined #ocaml
angerman has quit [Quit: Gone]
mort___ has quit [Quit: Leaving.]
mort___ has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
mort___ has quit [Client Quit]
ivan\ has joined #ocaml
nikki93 has quit [Remote host closed the connection]
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 276 seconds]
angerman has joined #ocaml
avsm has quit [Quit: Leaving.]
zpe has joined #ocaml
nikki93 has joined #ocaml
angerman has quit [Quit: Gone]
<whitequark> hm, what is the migration path from String to Bytes ?
<whitequark> I don't quite see how would I make a package compatible with 4.01 and 4.02
zpe has quit [Ping timeout: 245 seconds]
<companion_cube> Bytes is opt-in apparently
<companion_cube> (which is a byte sad)
<mrvn> What's byte?
<companion_cube> I guess it's the only reasonable way though
<companion_cube> mrvn: PR to add immutable strings
<companion_cube> and Bytes.t is the new name for mutable strings
nikki93 has quit [Ping timeout: 246 seconds]
<mrvn> urgs. That breaks basically every source
<companion_cube> you need to add -safe-string to the compiler flags
<companion_cube> not every source, come on
<mrvn> Why isn't Byte.t the immutable one?
<companion_cube> but a lot of them, probably
<whitequark> because "" should be immutable
<companion_cube> "" is immutable
<companion_cube> "true" should be too
<companion_cube> (I mean, string_of_bool true)
<whitequark> >> String.set "1" 1 2; print_endline "1"
<whitequark> er
<whitequark> hm, it broke
thomasga has joined #ocaml
<mrvn> How do I print Bytes? %s is for String.
<whitequark> good question
NoNNaN has quit [Remote host closed the connection]
<Pupnik> a lot of languages use immutable strings, they treat them just like strings. But I don't know about the specifics of what ocaml is doing.
<companion_cube> mrvn: btw, do you modify strings this often?
thomasga has quit [Client Quit]
<mrvn> companion_cube: All the time. Ever Unix.read does.
NoNNaN has joined #ocaml
thomasga has joined #ocaml
<mrvn> +y
maattdd__ has joined #ocaml
<adrien> anything that uses buffers
cdidd has quit [Remote host closed the connection]
<whitequark> Buffer.t doesn't require you to mutate strings though
<adrien> string buffers*
<whitequark> right
<companion_cube> mrvn: right, this kind of t hings should use Bytes.t
<adrien> for many things in Unix
nikki93 has joined #ocaml
<adrien> but porting shouldn't be difficult
<companion_cube> it's always the problem with retrocompatibility
<adrien> (provided Unix is migrated)
<mrvn> It should use Bigarray
<mrvn> and allocate on read
<adrien> hmm
<companion_cube> it should use a rope! :D
<adrien> if the allocation is large it might be fairly costly
<mrvn> read : fd -> off -> len -> string
<companion_cube> well that prevents you from using the same buffer several times..
<adrien> but what about when you get a read shorter than you asked for?
<whitequark> should be "fd -> off -> len -> bytes".
<mrvn> companion_cube: so?
<whitequark> ah, hm, not sure
<mrvn> adrien: then the string is shorter
<mrvn> whitequark: should have both.
<whitequark> mrvn: more like, a version that *returns* string and a version that *accepts* bytes
<adrien> mrvn: and if you read again?
<adrien> of course it's possible
ygrek has quit [Ping timeout: 245 seconds]
<mrvn> whitequark: and a third for bigarray
<adrien> but it gets more annoying to handle
<whitequark> mrvn: agreed
<companion_cube> mrvn: well, that's less efficient
<mrvn> It might have been better to have a String with phantom types.
<companion_cube> otoh I don't think you should use low-level primitives very often
<mrvn> companion_cube: bigarray is way more efficient
<companion_cube> if you allocate them every time?
<adrien> mrvn: for mmap? or for storing data?
<whitequark> mrvn: phantom types will break functors.
<adrien> and how do you print the data from a bigarray? %s definitely won't work
<mrvn> companion_cube: read/write works in 16k chunks and copies them each time. With bigarray you just have one syscall and no copying.
nikki93 has quit [Ping timeout: 245 seconds]
<whitequark> mrvn: e.g. you can't Set.Make(struct t = 'a String end)
<whitequark> that bit me really badly.
<companion_cube> mrvn: currently, where is there a copy with read/write?
<companion_cube> hmm well ok, a String.blit, but no allocation?
<mrvn> whitequark: yeah. That sucks. You need a second function with 'a t
<adrien> mrvn: mmap() is more costly for small files and if you don't want to read everything it can be annoying
<mrvn> companion_cube: in the unix module.
<adrien> and it doesn't solve the issue of reading from a pipe or socket
<whitequark> mrvn: no, you *cannot* have a functor parameterized by a type with a parameter
<whitequark> unless the functor has type 'a t itself
<mrvn> whitequark: that's what I said.
<companion_cube> right, sockes
<whitequark> a second functor, you mean. yes.
<adrien> plus it really only works when the file doesn't change size and you really want to read the data (i.e. it's not applicable for write() and then you get a non-symmetric interface for the two)
<whitequark> this really sucks. I wonder why can't ocaml just allow it.
cdidd has joined #ocaml
<whitequark> I mean, it is obviously safe
<companion_cube> what, you mean having a Set.t with elements = 'a foo ?
<whitequark> yes
<whitequark> er, no
<whitequark> with elements = bar foo.
<mrvn> companion_cube: The problem is that read/write releases the runtime lock and a String is heap allocated and can be moved by the GC. So read/write need to do the read with a local buffer, aquire the runtime lock and copy the buffer into the string and repeat till it has enough bytes. And write does the reverse.
<companion_cube> whitequark: you can, Set.Make(struct t = int list .... end) works
<mrvn> whitequark: even with elements = 'a foo should be safe
<companion_cube> mrvn: hmm, it can't use the allocated String? :(
<adrien> mrvn: my main issue with strings as buffers is the size limit on 32b
<companion_cube> mrvn: with elements = 'a foo, what's the type of Set.choose?
<mrvn> companion_cube: what if the GC moves it around while the read syscall writes to it?
<companion_cube> Set.t -> 'a t ?
<adrien> but there are really too many things that need strings currently to work
<companion_cube> mrvn: the syscall cannot trigger a GC, can it?
<mrvn> companion_cube: elements
<companion_cube> err
<companion_cube> elements ?
<mrvn> companion_cube: no, the other threads do
<whitequark> companion_cube: http://zheng.li/buzzlogs-ocaml/2013/11/30/irc.html Ctrl+F flexible arity
<companion_cube> ah, threading
<companion_cube> bleh
<mrvn> companion_cube: Set.t -> Set.elements where elements = 'a t. Shouldn't be a problem.
<companion_cube> 'a. 'a t then
<companion_cube> just use a GADT
<whitequark> right, so an indirection for every String.t put into a functorized container
<whitequark> granted, it at least won't need to match, but it still sucks hard.
<companion_cube> yes, the phantom type isn't that great...
<companion_cube> otoh you'd need sets of strings, or sets of Bytes.t, but rarely sets of both at the same time
<mrvn> Better would be if one could polymorphise the functor. modle ['a] M = Set.MAKE(N with elements = 'a t)
<whitequark> what would that do?
<companion_cube> oh well. so many features OCaml could have.
<mrvn> whitequark: allow you to have an int list set or float list set without having to call the functor multiple times.
<whitequark> mrvn: I mean, internally
<mrvn> whitequark: hopefully nothing different
<whitequark> mrvn: what would be the change to typechecker?
<mrvn> whitequark: allow you to bind type t in the functor with 'a x in the module argument
<whitequark> hmm, ok
<whitequark> could you maybe file a feature request? I'm really interested in this
<mrvn> whitequark: and then later use it with a sepcific 'a t, like int list.
<companion_cube> if the types use a postfix notation, then you'd have 'a Set.t if elements are of type 'a Set.elt ?
<companion_cube> I mean that's like a stack language
<mrvn> yes
<mrvn> (whatever you mean with postfix notation and stack language)
ollehar has quit [Ping timeout: 252 seconds]
<companion_cube> well, do you know the language forth?
<companion_cube> or factor
<whitequark> so module ['a] M = Set.Make(...) would basically add 'a to every type constructor in Set.Make?
<mrvn> yes. but I don't see how it applies to the perfectly normal ocaml type annotation in this case
<mrvn> whitequark: not every, It adds it to the overall module and then every type where it is specified for
<companion_cube> the idea is: types would actually be values in a stack language
<companion_cube> when you write val choose : t -> elt
<companion_cube> it would mean : val choose : [t
<companion_cube> rha
<mrvn> companion_cube: you could have 'a t and 'b elt.
<whitequark> mrvn: sounds really great
<companion_cube> val choose : [stack | t] -> [stack | elt]
<mrvn> giving you a ('a, 'b) Functor
<companion_cube> but the stack of types is implicit
<companion_cube> and a type like 'a list would actually be [stack | 'a list]
<companion_cube> (the two top elements are list, then 'a)
<mrvn> remove the stack and you have it
Anarchos has joined #ocaml
<mrvn> The types are simply aliased.
<mrvn> Only change would be that the aliased type has an unbound type variable ('a)
maattdd__ has quit [Ping timeout: 255 seconds]
<companion_cube> well the point would be that if elt has an argument, the argument is under it in the stack
<companion_cube> so val choose : [stack' | 'a t] -> [stack' | 'a elt] would be just an instance of the previous signature
Anarchos has quit [Ping timeout: 252 seconds]
Nuki has joined #ocaml
tobiasBora has joined #ocaml
eizo has joined #ocaml
HaikuUser has joined #ocaml
HaikuUser has quit [Remote host closed the connection]
waneck has quit [Read error: Connection reset by peer]
ikaros has joined #ocaml
<tobiasBora> Do you know who is programming tuareg mode ? Because I've really strange indentation
<tobiasBora> since an early update
<tobiasBora> If I write :
<tobiasBora> if name = "coucou" then begin
<tobiasBora> then next line is aligned with "begin" instead of "name"
nikki93 has joined #ocaml
<mrvn> because begin opens the block
<mrvn> add a line break before then
<tobiasBora> mrvn: Ok I will do that. But it was nice to be able to do one line condition ^^
<mrvn> the shouldn't need a begin then
mort___ has joined #ocaml
nikki93 has quit [Ping timeout: 245 seconds]
<tobiasBora> I mean a one line "beginning condition"
<tobiasBora> but you are right it's not important to add one line in the condition if the condition is large
<mrvn> often you can also skip the begin because you have a let or match.
ygrek has joined #ocaml
thomasga has quit [Quit: Leaving.]
nikki93 has joined #ocaml
<ggole> Both tuareg and typerex indent pretty poorly IME
<mrvn> The worst is when emacs line breaks in the middle of a string.
avsm1 has quit [Quit: Leaving.]
<ggole> typerex has problems with character literals: print_thingy '(' is considered as an opening (
<whitequark> eugh, does it even lex the source?
dapz has joined #ocaml
<ggole> It uses emacs' (flaky) language support, built on regexps
<whitequark> Sublime's language support (built on regexps) actually indents quite great
<ggole> Maybe I should try to fix that, actually
dapz has quit [Client Quit]
<ggole> There are some other situations in which it just doesn't do what I want: which is annoying, but not the end of the world
nikki93 has quit [Ping timeout: 265 seconds]
<ggole> For instance, nested or patterns: | { foo = ... | ... }: if you want a newline after the first ..., the | won't match the =
<ggole> But that's just a matter of taste really.
Thooms has joined #ocaml
thomasga has joined #ocaml
mort___ has quit [Quit: Leaving.]
studybo__ has quit [Read error: Connection reset by peer]
rand000 has quit [Quit: leaving]
maattdd__ has joined #ocaml
thomasga has quit [Quit: Leaving.]
Hannibal_Smith has joined #ocaml
maattdd__ has quit [Ping timeout: 252 seconds]
zpe has joined #ocaml
ygrek has quit [Ping timeout: 255 seconds]
nikki93 has joined #ocaml
angerman has joined #ocaml
nikki93 has quit [Ping timeout: 255 seconds]
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 255 seconds]
mort___ has joined #ocaml
nikki93 has joined #ocaml
oriba has joined #ocaml
struktured has quit [Ping timeout: 276 seconds]
Nuki has quit [Remote host closed the connection]
nikki93 has quit [Ping timeout: 240 seconds]
darkf has quit [Quit: Leaving]
jonludlam_afk is now known as jonludlam
avsm has joined #ocaml
avsm has quit [Client Quit]
ollehar has joined #ocaml
jonludlam is now known as jonludlam_afk
jonludlam_afk is now known as jonludlam
<kerneis> Error 404 Not Found
<kerneis> now, documentation as wiki sucks, but having the wiki gone sucks even more
<mrvn> A wiki is where documentation goes to die. Sometimes it actually gets burried. RIP.
rgrinberg has joined #ocaml
<whitequark> and there even wasn't much documentation to begin with
<kerneis> no but there was a few specific bits that I needed now and then
<whitequark> google cache should still contain them
<kerneis> yeah, just did that
<whitequark> perhaps you could save them somewhere
<kerneis> funny, the only time it has been snapshot by the way back machine (in 2007), it was a 404 too :-D
<jonludlam> not tried to download it; it might be big :-)
<jonludlam> I believe there are plans to rehost the info, but I don't know where
<kerneis> 132K
<jonludlam> heh
<kerneis> less than a 1MB when unzipped
<whitequark> github wiki?
<whitequark> at least that won't be gone for quite a while
<jonludlam> yep, or ocaml.org
thomasga has joined #ocaml
olauzon has joined #ocaml
studybot_ has joined #ocaml
Hannibal_Smith has quit [Quit: Sto andando via]
studybo__ has joined #ocaml
sgray10 has joined #ocaml
studybot_ has quit [Ping timeout: 240 seconds]
studybo__ is now known as studybot
<flux> I kinda wish the new Bytes module had used rw/ro tagging for the type t
<mrvn> now one needs to duplicate all string functions for mutable and immutable.
avsm has joined #ocaml
dsheets has joined #ocaml
<flux> I have trouble recalling the term, what was the type 'a foo where 'a is only used for the type?
<mrvn> flux: phantom
<flux> in any case, had it been that way there could just be type string = Bytes.ro Bytes.t
<flux> yes, I was thinking of 'ghost' but it didn't click :)
<mrvn> Problem then is to make a Set(String)
<flux> actually type string = .. could depend on if you compile with -safe-string or not
maattdd__ has joined #ocaml
<mrvn> you need a whole new set of functors with a 'a t
<flux> well the problem wouldn't be for existing code
<flux> and new code could just do Set(Bytes)? though I suppose it's bad that the module type doesn't tell if it's ro or rw
<mrvn> Also there are 3 kinds of strings: mutable, immutable and immutable for the function I call
<flux> you mean mutable, immutable and constant?
<mrvn> flux: From what was said String is now immutable. So you have to change all your code to Byte.
<mrvn> flux: whatever you call it. Point is that strings can become temporarily immutable.
<mrvn> or mutable in one part of the code and immutable in another.
<flux> with polymorphic variants and phantom types that stuff is simple
<kerneis> you completely lost me; are you talking about Core or stdlib?
<mrvn> Does Byte have the same memory representation for strings? Can one Obj.magic them to/from String?
<mrvn> kerneis: stdlib
<kerneis> oh, I wasn't aware of the Byte stuff
<mrvn> kerneis: ocaml 4.02
<mrvn> so far I think it is only optional.
<flux> I imagine it's Obj.magicable, maybe it even comes with functions for going the other way?
<ggole> How could you soundly convert without copying?
<mrvn> still misses the 3rd kind. If you get a Obj.magiced Byte passed as argument you can't assume it never changes and use it as key in a Hashtbl for example.
<flux> you cannot, if you only have constant values. but if you have values -you- cannot modify (immutable), others may still modify them :)
<ggole> Introducing that kind of problem sounds like a bad idea
<flux> with a phantom type there could be a function val constant : _ t -> [ `constant | `readable ] t
<mrvn> You need a "this never changes", a "you are not allowed to changed it" and mutable strings.
<flux> (and that function would copy)
<flux> there could also be val unsafe_constant that doesn't copy, but where you can guarantee it's not modified (ie. when you return it from the function)
<ggole> Why would you have this for Bytes.t but not for arrays and refs?
<flux> or if yuo want to go very non-ocamlish about it, you could add a runtime check :-)
<ggole> And hashtables
<mrvn> ggole: hashtables have to be mutable
<mrvn> ggole: but for arrays it makes the same sense.
<mrvn> for refs just use ! when you don't want to change it.
<flux> ggole, personally I would like to have it for everything.. baby steps maybe?-)
<mrvn> flux: the string could have a bit so a constant string wouldn't have to be copied.
<mrvn> And then you could have a 4th kind, a copy-on-write string.
<flux> and how about threads?
<flux> mutex lock on all writes?
nikki93 has joined #ocaml
<mrvn> ocamls stdlib isn't thread safe
<flux> apparently c++ string implementations have switched away from CoW
<ggole> A lot of ceremony for little actual benefit if you ask me
<mrvn> ggole: let bool_to_string = function false -> "False" | true -> "True"
<mrvn> ggole: with mutable strings that needs to allocate every time
<ggole> I'm fine with immutable strings.
<ggole> I'm talking about the access types.
<flux> well, without access types you get to use unsound casting or duplicate modules?
<mrvn> ggole: the phantom types would prevent code duplication for String and Byte.
<flux> or perhaps make 'normal' functions operating on strings/bytes functorized
<flux> for example, the Pcre module..
<ggole> If code duplication is a problem, you can solve it without making the interface complicated.
<flux> so how would you solev it for Pcre?
mort___ has quit [Quit: Leaving.]
<ggole> In fact, I don't see what code duplication has to do with access types at all
nikki93 has quit [Ping timeout: 240 seconds]
<mrvn> ggole: you can have val length : 'a String -> int but not val length : [String | Byte] -> int
<ggole> You can already do module Foo : type t ... end = UnderlyingFoo to restrict operations (such as mutation) in a type safe way
<flux> well, now you have val split : string -> string list. now you need to have that for bytes as well. but with accses types you (say) can do val split : _ bytes -> const_bytes list
<ggole> So you can have String and Bytes without any duplication, trivially.
Hannibal_Smith has joined #ocaml
<mrvn> ggole: No you can't. you need a foo_string and foo_byte function for everything.
<ggole> For the functions in the relevant modules, then
<flux> and how about splitting a mutable string with an immutable string? and vice versa?
<flux> not to mention simple things like concatenating the two
<mrvn> The number of functions is exponential with the number of string arguments.
<mrvn> and Printf.printf "%s"
<mrvn> What's the % code for Byte.t?
<ggole> I doubt there is one? Why would there be one?
<mrvn> ggole: how else do you print a mutable string?
<ggole> Bytes.t isn't a mutable string
<ggole> It's a byte array
zpe has quit [Remote host closed the connection]
tani has joined #ocaml
<mrvn> ggole: String is immutable. so how else do you do mutable strings?
zpe has joined #ocaml
<ggole> You don't.
<ggole> There's things like Buffer if you need to do updatey things.
<ggole> Makes perfect sense to me.
<mrvn> which breaks basically every code
<ggole> And it's not like there aren't several languages which already do exactly this.
<flux> for years to come, there will be libraries that will use the String
<ggole> Yes, backwards compat is the big problem there
<ggole> But you wouldn't be able to be backwards compat with access types either.
<flux> well, you could in the sense that the whole ocaml installation would need to be compiled in the same -safe-string -mode?
<mrvn> ggole: I wouldn't say that. type string could be aliased to `Mutable String.t
nikki93 has joined #ocaml
<ggole> That would break functor applications like Set.Make (String).
tane has quit [Ping timeout: 255 seconds]
<mrvn> ggole: ok, then String would be a shallow copy of Byte with String.t = `Mutable Byte.t
zpe has quit [Ping timeout: 255 seconds]
<mrvn> ggole: you can probably make it so that string and String all still works but maps to the new phantom types.
<mrvn> Or just have String as is and ConstString.
<ggole> That'd run you into trouble with string literals.
nikki93 has quit [Ping timeout: 252 seconds]
<mrvn> ggole: is "foo" const or not?
<ggole> You might be right that access types could be made to work: seems like an awful hack though.
<ggole> "foo" should have type string
<mrvn> let get_temp_name () = let s = "/tmp/blafaseXXXXXX" in tempname s; s
<mrvn> software assumes string literals are mutable
<_obad_> I have a module M and a signature S. I want to make sure the module matches the signature but I don't want to hide the module. is there a way besides module Foo_check = M : S?
<mrvn> _obad_: don't thinks so.
<ggole> Then that software will break when they compile with the new flag
<mrvn> ggole: and that is the point. A ton of stuff will break
<mrvn> Can one even write source so it works with and without the new flag?
<ggole> If you chose the access type thing, and made strings mutable by default, you wouldn't get the advantages that introducing immutable strings were supposed to deliver
<mrvn> Is there a Byte module without the flag?
<whitequark> yes
<whitequark> but type bytes = string
<mrvn> whitequark: needs to be that way
<whitequark> (works with and without) yes, use String.copy for literals
<whitequark> that literals were mutable is such an awful quirk, it should have never happened
<mrvn> the question is what happens if you mix modules compiled with the flag with modules compiled without.
<ggole> There was no way of making them immutable (other than designing OCaml with immutable strings from the start).
<whitequark> as I understand, the flag is only active intra-module
<mrvn> whitequark: maybe. C and C++ still struggel with that.
<whitequark> mrvn: hm?
<whitequark> "" has type const char* there.
<ggole> No, that's wrong. Ignore what I said.
<whitequark> (and writing there would segfault on non-Windows, so it's a non-issue for portable software)
<mrvn> whitequark: C lets you happily pass a string literal to a function taking char* and then you get a segfault when it tries to modify it.
<whitequark> no, you will get a warning due to dropping the const modifier
<mrvn> whitequark: "" has type char* in C but is const.
<mrvn> whitequark: Only in C++ do you get a warning about depreacted cast from const to non const
avsm has quit [Quit: Leaving.]
<whitequark> hm, you're right
<mrvn> whitequark: imho totaly screwed up
<ggole> Literals have type const char[K] iirc
<ggole> But of course you can cast to char *
<mrvn> ggole: nope. no const.
<mrvn> typeof("") x; gives you a char *
<mrvn> as I said: totaly screwed up
<ggole> Ah, it's const char[K] in C++.
angerman has quit [Ping timeout: 252 seconds]
<ggole> OK, yeah. That's all fucked up.
rgrinberg has quit [Quit: Leaving.]
<whitequark> C++ isn't backwards-compatible with C, yeah
<mrvn> In python3 there is b"foo" for byte arrays and "foo" for UTF-8 strings. maybe ocaml could have something similar for string literals to mark them mutable.
<ggole> Yeah, it changes a bunch of (mostly dumb) things
<ggole> typedef int; is valid C, but not C++.
<whitequark> why would anyone write that
<ggole> Why would a compiler allow it?
<whitequark> why would a compiler allow C to exist?
<mrvn> "unsigned;" is allowed in C
<companion_cube> please don't copy how C handles strings
<ggole> There's a heap of stupid C declarations that don't mean anything, but which compilers have to accept.
<ggole> int foo(struct does_not_exist); <- this is a good one
<mrvn> at least gcc warns about a lot of nonsense.
<ggole> The struct type there is defined *within the scope of the declaration*.
<ggole> If you later declare struct does_not_exist, that works but is a different type.
<mrvn> realy just within the scope? I thought that would just declare the type globally.
<ggole> No, that would be struct foo; int foo(struct foo);
rgrinberg has joined #ocaml
avsm has joined #ocaml
rgrinberg has quit [Client Quit]
dapz has joined #ocaml
rgrinberg has joined #ocaml
<mrvn> .[] is for strings, .() for arrays, .{} for Bigarray. What does Byte have?
<mrvn> .<>?
<adrien> .\/
<adrien> so you can do .\o/
<whitequark> yeah, seems like a hasty decision
<mrvn> adrien: lol
<whitequark> ocaml really should have typeclasses...
<whitequark> .[](){} is annoying and pointless
<Drup> whitequark: soon™
<ggole> Beats {String,Array,Bigarray}.get/set. But yeah.
<whitequark> Drup: yeah, you said this to me a year ago
<whitequark> :p
<whitequark> half a year maybe
<avsm> whitequark: i'm telling you soon now :-) surprise incoming soon...
<Drup> whitequark: well, it's sooner(™) now :D
<ggole> How would it work? Some kind of implicit module argument?
<mrvn> whitequark: with a typeclass the compiler couldn't optimize .[]
<Drup> mrvn: yeah it could
<mrvn> Drup: only when it knows the type
<whitequark> avsm: that's real nice!
<Drup> avsm: someone spoiled me :3
<_obad_> quick question... is there a way in vim to see the compiler output without losing the formatting?
<avsm> Drup: :-)
* whitequark has been advocating (starting using; using more, depending on how you look at it) ocaml at his company for some time already
<companion_cube> "soon" in Ocaml means in two years ;)
<companion_cube> but yes, typeclasses would be awesome
<whitequark> explaining people why they should sometimes use .[] and sometimes .() after Ruby is... annoying.
<NoNNaN> and every other feature that starts with "type" eg.: type providers
<companion_cube> type families
<whitequark> NoNNaN: you could conceivably do that today, no?
<whitequark> no support from compiler required
<_obad_> it's a tradeoff that implies mandatory annotations
<whitequark> _obad_: what is?
<_obad_> having to add : int, : int array, : string everywhere to be able to write [] and not .() or .[]
<Drup> companion_cube: type famillies would break the ML's style inference in lot's of bad way, imho
<companion_cube> I was joking
<Drup> ok :D
<whitequark> _obad_: what?
<ggole> _obad_: type classes are (an) answer to that
<NoNNaN> whitequark: unfortunately no, type providers not yet available for ocaml
<mrvn> would be nice if ocaml had polymonomorphism. Then you could declare .[] for strings, bytes, arrays and bigarrays, get the optimized version if the type is known and the generic slow one if not.
<_obad_> ggole: so no annotations yet you can use the same operator??
<Drup> mrvn: yes, well done
<whitequark> NoNNaN: aren't type providers just types autogenerated by the compiler?
<companion_cube> that's a matter of typeclass + inlining, isn't it?
<Drup> you just discovered type classes.
<ggole> Instead of seeing x.[i] and inferring x : string, you'd get x.[i] implying x : Indexable t => t or something like that
<Drup> mrvn: what you just described is *exactly* type classes ...
tlockney_away is now known as tlockney
<tautologico> I think it's not too hard to write generic support for type providers using ppx
<Drup> what is a "type provider" exactly ?
<mrvn> Drup: except type classes would not provide mutiple code flavours for a function.
<tautologico> about the "typeclasses soon", is it the implicits stuff?
<Drup> mrvn: implementation detail
<ggole> _obad_: so the one operator always implies the same type, but the type is more complicated, allowing for static dispatch of a kind.
<Drup> mrvn: you can do it, it's a trade off
<Drup> tautologico: spoilers :3
<whitequark> Drup: so it is implicits? :/
<Hannibal_Smith> <ggole> Literals have type const char[K] iirc <-You are right, this is also reported by the standard
<_obad_> ggole: I see.... but then doesn't it kinda cause implementation issues, as in you need either to box things, or have a number of implementations that is proportional to the number of typeclass combinations?
maattdd__ has quit [Ping timeout: 252 seconds]
<mrvn> Drup: one is a type system thing, the other a opimizing compiler thing
<Drup> whitequark: don't look disapointed, it's going to be awesome :p
<Hannibal_Smith> narrow string literal has type “array of n const char”, where n is the size of the string as defined below, it and has static storage duration <-
<whitequark> Drup: they're so horribly ad-hoc.
<Drup> mrvn: since when the too are not correlated ?
<Drup> the two*
<whitequark> Drup: I've seen alain's posts on the topic, I'm not really impressed
<mrvn> Drup: they are. I still want the later
<ggole> _obad_: implementation is kind of fun, I think, but I believe its manageable
Anarchos has joined #ocaml
<ggole> The usual implementation (eg, Haskell) is dictionary passing
angerman has joined #ocaml
<whitequark> aka vtables
<mrvn> ggole: you can do that with first class modules
<ggole> Right, but the vtables are per function and not per object.
<whitequark> well, it's inverted a bit
<whitequark> NoNNaN: can you summarize in one sentence, why can't ocaml have them now?
<ggole> mrvn: right, and if you make the module argument implicit using some magic lookup machinery, you have something that is a lot like type classes
<Drup> whitequark: why ?
<_obad_> oh god all that sounds pretty complicated, just so you can lose the .[] +.?
<companion_cube> ggole: you also need some prolog-like search
<companion_cube> because some typeclasses instances are kinda generic
<ggole> Well, that's what I tried to suggest with "magic lookup machinery"
<Drup> _obad_: it's not only for that, type classes have lot's of potential uses
<companion_cube> ok
<companion_cube> _obad_: if you complexify the type system to get rid of .{} .[] and such, better do it in a generic and clean way
<tautologico> like doing lens in OCaml :) (runs...)
<companion_cube> so the whole language benefits from it
<Drup> tautologico: /me screams in terror
<companion_cube> :D
<ggole> A nice way to do equality and ordering will be very welcome
<companion_cube> now I know what Drup is afraid of
<companion_cube> indeed
<gasche> avsm: I really worry about CPU time burned when doing continuous testing
<ggole> Not sure how it would interact with the existing stdlib though
<companion_cube> and hashing, and printing
<gasche> I'm not sure why this is so surprising
<companion_cube> gasche: sadly I think that's just a tear in an ocean
<adrien> hmmmm
<gasche> that's some of the tears we are responsible for
nikki93 has joined #ocaml
<adrien> need to go ask AMD for a system with their 16-core server CPUs with a 99W TDP
<_obad_> companion_cube: I think there might be a simpler hack to get rid of .[] .{} +. with maybe some extra syntax.
<_obad_> companion_cube: think of the way the formatting types work... it's a hack, but it works.. kinda
<Hannibal_Smith> adrien, don't that kind of cpu tend to have simpler core?
<companion_cube> _obad_: the problem is type inference
<tautologico> I'd like to be able to overload indexing, besides the other benefits of ad hoc polymorphism
<avsm> gasche: I'm seriously facepalming at priorities here.
<adrien> gasche: I don't think we should worry; compiler is fairly fast, code is fairly fast
<_obad_> companion_cube: how does SML do it?
<adrien> gasche: loading google.com takes much more power
<adrien> (overall)
<NoNNaN> whitequark: runtime code (generation), not all your types are known at compile time
<companion_cube> oh, the overloading thing of SML?
<_obad_> yeah
<companion_cube> it's just a default case, I think
<tautologico> _obad_: special casing
<companion_cube> like, a+b is int by default
<companion_cube> it's ugly
<gasche> adrien: do you have actual numbers on that? I would be interested
<adrien> Hannibal_Smith: mostly the same as far as I know
<companion_cube> it doesn't solve equality or comparison
<tautologico> in an expression a+b can be int/float, but inside a function it defaults to int
<adrien> gasche: look at the amount of JS there
<_obad_> hmm
<tautologico> for equality you have to declare eqtypes
<companion_cube> or php
<tautologico> it's not pretty
<_obad_> *need to get back to work*
<companion_cube> the proper way really is typeclasses
<Hannibal_Smith> adrien, same pipeline wide and deep, same branch prediction algorithm, same number of BTB buffer...?
<adrien> gasche: and put another way, a current machine is going to use at most two small regular lamps
<Hannibal_Smith> At least in production CPU like Oracle Niagara one
<Hannibal_Smith> CPU core are really more simpler
<whitequark> Drup: because it's ad-hoc. just randomly selecting some value from context instead of a proper solution
<adrien> Hannibal_Smith: mostly, yeah; cache is bigger (but shared among more CPUs); clocks are lower though
<Drup> whitequark: what is a "proper solution" ?
<Drup> ( whitequark: and what is the "proper" way of doing type classes, according to you ?)
<Hannibal_Smith> That kind of CPU seems really "narrow" so some kind of computation style
<Drup> ( whitequark: because haskell is doing exactly that ...)
<ggole> It would be nice to be able to select the (implied) implicit argument manually
<whitequark> Drup: wait, what? haskell does the same thing?
<Hannibal_Smith> Where a problem has good parallelism characteristics
* whitequark is really confusing now
<whitequark> I thought haskell solved it properly...
<Drup> what is "properly" ?
<adrien> well, the CPUs I have in mind are still clocked fairly high but not that high
<whitequark> defining typeclass as an explicit entity, etc
<adrien> and they tend to have "boost" (temporary overclock provided there's power and temperature headroom)
<Drup> whitequark: and in what is it different than having a vtable passing around ?
<whitequark> Drup: I'm talking about the interface, not implementation
<Hannibal_Smith> That kind of cpu seems interesting for something like web related servers
<Drup> whitequark: ok
<Drup> whitequark: so yes, the interface is different
<Drup> and, imho, is the bad one
<mfp> whitequark, Drup: aren't Haskell typeclasses even worse in the sense that they are global (and you can only have 1 instance)? With implicits, at least you have modules + open.
<Hannibal_Smith> I don't know to how Oracle sells the Niagara
<Drup> mfp: indeed
<Hannibal_Smith> *who
<Drup> also, there is an issue at use point
<tautologico> only one instance per type
<whitequark> Drup: mfp: hmmm, that is a good argument.
<tautologico> so people use newtypes a lot for getting around that
<Drup> with type classes, you can look at a piece of code and it's possible that you don't know which stuff is going to be used.
<tautologico> also dependencies issues between libraries like orphan instanves
<Drup> because it depends on some other file implicitly opened
<whitequark> Drup: you're probably right after all.
<tautologico> *instances
<Drup> type classes are not scoped.
<whitequark> okay, great
<Drup> (and this is terrible)
<mfp> hmm implicits can be passed hmm explicitly, cannot they? So you can know for sure if you care
nikki93 has quit [Ping timeout: 276 seconds]
<companion_cube> so, implicits would be even better?
<companion_cube> is that what you imply?
<Drup> I prefer implicits
<companion_cube> ok
<tautologico> in Idris instances are named to work around some of these issues
<gasche> Coq's type classes are better than Haskell's from a coherence point of view
<Drup> companion_cube: if you look at the backlog, I have said that since a year ago :D
<companion_cube> well, we just need to wait and pray for the upcoming implementation to be merged
<companion_cube> :)
<companion_cube> Drup: I know, it's still useful to check ;)
<gasche> the problem with implicits is that no effort is made to enforce coherence
<whitequark> there seem to be not too many objections to merge of implicits
<whitequark> gasche: coherence?
<mfp> companion_cube: they feel adhoc and all, but they are objectively better in some ways
<gasche> whitequark: the fact that the code is not ambiguous
<tautologico> because instances don't have names in Haskell, they can't be exported/imported explicitly
<whitequark> gasche: right, that's one thing that annoys me.
<Drup> whitequark: the main point, imho, is that implicits are more predictable than type classes
<companion_cube> which reminds me that I'd really like to banish 'open' :/
<whitequark> companion_cube: whoa
fraggle_ has joined #ocaml
<mfp> so.... we're a couple years away from this? -> http://www.cs.ox.ac.uk/ralf.hinze/WG2.8/24/slides/derek.pdf
<whitequark> that would make code so much more needlessly verbose
<companion_cube> well, not banish, but limit it, I hate when people start with 15 open
<mrvn> companion_cube: but not M.(...)
<companion_cube> mrvn: no, of course not
<tautologico> I'd like it if there were a way to import only some stuff from a module
<gasche> Drup: I don't see your argument about implicits being more predictable
<companion_cube> whitequark: module F = Foobar
<companion_cube> gasche: scoping?
<Drup> gasche: maybe it's a question of language
<mrvn> open Foo.Operators is nice though
<gasche> for both features it's reasonable to expect a "show resolution at this point" feature that gives you the elaborated term
<Drup> indeed
zpe has joined #ocaml
<gasche> but neither really enforce that there is some predictibility in what will be inferred
<Drup> you're probably right
<gasche> Haskell's type classes enforce a bit more, to my knowledge, what Scala does is entirely unspecified and relatively arbitrary
<gasche> and the main enabler of Haskell's predictibility is precisely the restriction to a toplevel, global scope
<gasche> (and that is bad from a language point of view)
<tautologico> Scala implicits are bad in this respect
<companion_cube> is it possible, at any point, to check whether some instances are ambiguous?
<whitequark> gasche summarizes my feelings on implicits very well
<Drup> my experience of implicits is Agda
<Drup> not Scala :)
<companion_cube> with unification it should be doable to find a "critical pair"
<gasche> I think without enabling extensions, you can only define non-ambiguous instances in Haskell
<Drup> yes
<gasche> (multi-parameter type-classes introduce ambiguities)
<companion_cube> yes, but could it be possible to do it with scoping?
<Drup> and it's very quicly a mess :/
<tautologico> though Haskellers this day seem to use these extensions a lot
<gasche> because they prefer expressivity over well-definedness
<Drup> haskellers use a lot of extensions that breaks their type inference.
<tautologico> (flexible instances, multiparameter type classes, fundeps were used a lot until recently, now it's type families)
<gasche> to my knowledge having a really satisfying type-class or implicit mechanism is still an open problem
<Drup> tautologico: and they are ok with annotating all their functions
<whitequark> gasche: have you seen what Rust does?
<tautologico> Drup: yes, not only "ok" but it's the idiomatic practice, and this isn't new
<gasche> (it's easier in dependently typed languages, but not necessarily the right answer)
lostcuaz has joined #ocaml
lostcuaz has quit [Read error: Connection reset by peer]
<Drup> tautologico: indeed
<whitequark> you need to explicitly import the typeclass; then you get all its functions in scope.
nikki93 has joined #ocaml
<whitequark> in my limited experience it has been very great; it practically always does what you'd expect
lostcuaz has joined #ocaml
<companion_cube> I think typeclasses would still make the language cleaner
lostcuaz has quit [Read error: Connection reset by peer]
<companion_cube> no more polymorphic equality or Marshall
<companion_cube> which are really ugly
<gasche> I agree, but the details still need to be worked out
<companion_cube> of course ^^
lostcuaz has joined #ocaml
<tautologico> it works well in Rust, except sometimes you need to write a lot of constraints in the type parameter
<tautologico> fn foo<T: Copy + Num + Float + Whatever, X: Copy + Whatever, ...>
<whitequark> that's true
<tautologico> type parameters that take a whole line of code :)
<tautologico> also I feel that "trait" is a better name, less confusing than "type class"
maattdd__ has joined #ocaml
<mrvn> And here I was thinking ocaml was about infering types
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<gasche> type classes infer uses of instances, but I think not inferring them is also a reasonable choice
zpe has quit [Ping timeout: 245 seconds]
<gasche> (I mean it infers constraints)
nikki93 has quit [Ping timeout: 255 seconds]
<Drup> mfp: just read the slides
<gasche> kerneis: thanks, I just fixed the typo
<Drup> mfp: I'm screaming ocamlgraph and tyxml at the part asking for examples of use for applicative functors :D
<kerneis> gasche: you're welcome
maattdd__ has quit [Ping timeout: 246 seconds]
dsheets has quit [Ping timeout: 246 seconds]
dsheets has joined #ocaml
ygrek has joined #ocaml
racycle has joined #ocaml
pminten has joined #ocaml
Arsenik has joined #ocaml
michael_lee has quit [Remote host closed the connection]
<gasche> I am wondering about patch handling
<gasche> sometimes I want to merge someone's patch somwehere, but I would like a relatively minor change
<gasche> my current policy is that, if it takes more time for me to describe the change than do it, I do it directly (generally as an amend to the patch)
<gasche> would you do differenty?
jwatzman|work has joined #ocaml
<adrien> depends on if you want to each the patch author for the subsequent patches
<gasche> I don't understand your sentence
<gasche> ah, each -> teach
<adrien> yeah, sorry :)
<adrien> I'll blame the keyboard and attempt to debug C++
Vaur has joined #ocaml
<_obad_> seems that ocamldoc ignores (** *) comments on variants... :( ?
<whitequark> I think you have to use something like (**< comment *)
<_obad_> type blah = Foo (** Foo *) | Bar (** Bar *) works
<_obad_> oh
<whitequark> not sure though, but I've seen it sometimes
zpe has joined #ocaml
nikki93 has joined #ocaml
<Drup> _obad_: I wouldn't be surprised
<_obad_> there is no talk of (**< *) in the doc and it doesn't work
<Drup> never heard of "(**< *)"
<Drup> _obad_: until recently, this annotation was not working on each method in an object, I wouldn't be surprised if it doesn't work on poly variants
<_obad_> drup: the changes.txt under ocamldoc/ talks of variants though
<Drup> _obad_: did you tried on the trunk ?
zpe has quit [Ping timeout: 245 seconds]
<_obad_> yeah 35ec048ca76f48b112fef2cf7c1671302d749b8d
pminten has quit [Remote host closed the connection]
<_obad_> oh wait no, I'm at 4.01
clan_ has joined #ocaml
<rgrinberg> I'm making a user friendly api on top of ocaml-re. If anyone wants to review and suggest stuff: https://github.com/rgrinberg/humane-re/blob/master/lib/humane_re.mli
<Drup> the name is cute x)
dlat has joined #ocaml
<Drup> (why is it not a fork of ocaml-re ?)
<whitequark> rgrinberg: great idea
<rgrinberg> not really sure if ocaml-re would be interested in this
<avsm> rgrinberg: i like the cut of that signature's jib
<smondet> rgrinberg: any reason for choosing the Emacs syntax?
<whitequark> type str is a bit odd
<rgrinberg> smondet: nah it's just what I'm testing with. will have a general constructor function later.
<whitequark> what's it for?
<_obad_> rgrindberg: do we really want labels on fold?
<rgrinberg> _obad_: yes!!!!
<whitequark> I think ~f on fold is great, ~init not so
<_obad_> or ~pos
nikki93 has quit [Ping timeout: 240 seconds]
<avsm> ~init and ~f let you choose which to curry
<whitequark> hmm, good point
<rgrinberg> _obad_, whitequark: they're also the default labels in XLabels modules
maattdd__ has joined #ocaml
<whitequark> does *anyone* use XLabels modules?
<Drup> yes
<rgrinberg> whitequark: *raises hand*
<whitequark> oh, cool
<smondet> whitequark: yes, everywhere
<_obad_> it's like automatic vs. shift
<whitequark> I really wish they were included by default
<_obad_> no
<whitequark> opened
<Drup> whitequark: also, it's the defaul in core
<flux> sadly ~f breaks @@
<whitequark> oh
<adrien> I use them from time to time
<adrien> depends
<_obad_> it's useful when you have a lot of arguments, or when they have similar or equal types
<adrien> it's mostly to use ~f:(fun ........) on several lines
<whitequark> adrien: I use arr |> List.map (fun ...)
<rgrinberg> whitequark: str is there because it's my dream that the it will work on more than 1 string type
<whitequark> rgrinberg: like what?
<adrien> whitequark: would work too :)
<rgrinberg> etc. substrings, bigstrings, ropes
<flux> rgrinberg, well, at least provide a basic String instantiation
<flux> whitequark, Bytes :)
<whitequark> rgrinberg: I mean, ocaml-re only works on strings
<rgrinberg> flux: i will, module S with type str = string that's what im working with
<_obad_> labels are like maple syrup... you want to put a little bit of it on some food, but putting it everywhere is... well I guess I'm hungry now
<avsm> rgrinberg: if it works on bigarrays, then bye-bye string in cohttp...
<rgrinberg> whitequark: hopefully not for long
<whitequark> hmm
tobiasBora has quit [Quit: Konversation terminated!]
<rgrinberg> flux: the basic string implementation is all it's going to have in the beginning
maattdd__ has quit [Ping timeout: 240 seconds]
<rgrinberg> i think ocaml-re can easily be implemented on top of ropes by simple wrapping every module with module (S : module type of String) and instantiating with rope
<flux> rgrinberg, how are you going to make that happen with the functorized interface?
<rgrinberg> flux: just instantiate the functor, then module Str = Make(String) : S with type str = string?
<rgrinberg> how i wish i could return lazy lists for some functions
clan_ has quit [Quit: clan_]
<rgrinberg> now i have to choose whether to return eager lists or these awkward folds :/
<rgrinberg> and streams suck
<companion_cube> don't use Stream
<ggole> Stream is pretty strange
clan_ has joined #ocaml
<rgrinberg> companion_cube: i would never dare to
<companion_cube> :)
<companion_cube> use some better iterator type, or lazy list, or whatever
<Drup> (* INSERT SELF PROMOTION HERE *)
<Drup> wink wink companion_cube
<rgrinberg> Drup, companion_cube: i know, i know ideally i'd have something non destructive
<Drup> rgrinberg: use Sequence
<Drup> rgrinberg: I think upstream wouldn't mine, btw
<rgrinberg> Drup: i would 100% use sequence if opam/ocamlfind didn't make it cumbersome to make optional dependencies
<Drup> cumbersome ?
<rgrinberg> i mean oasis, not ocamlfind
<Drup> oh
<Drup> huum
<Drup> it's not that terrible
S11001001 has joined #ocaml
<rgrinberg> what a complimenet
<Drup> depends of what you want exactly, "optional dependencies" can mean lot's of think
S11001001 has quit [Changing host]
S11001001 has joined #ocaml
<Drup> things*
<rgrinberg> some extra functions that return sequences if sequences is present would be the use case here
jonludlam is now known as jonludlam_afk
<companion_cube> Drup: I said nothing :DD
<rgrinberg> also, we need SequenceLabels
<companion_cube> rgrinberg: sequence is a structural type, you can define it anywhere
<rgrinberg> *wink*
<Drup> rgrinberg: since sequence is super small, self contained and pure ocaml, do you really need to have it optionnal ?
shinnya has quit [Ping timeout: 255 seconds]
<companion_cube> type 'a sequence = ('a -> unit) -> unit
<rgrinberg> ah, i thought it was abstract
<companion_cube> also yes, you can just copy/paste the ocaml file directly
nikki93 has joined #ocaml
<companion_cube> I prefer structural types when possible
<rgrinberg> i like them too, if only objects didn't suck :/
<Drup> rgrinberg: I agree with that soo much
<rgrinberg> perhaps someone will make a patch now that we have github contributors :D
<Drup> rgrinberg: well, the difficult part is that it's not super clear to make them not suck
<whitequark> what's so terrible with objects?
<rgrinberg> whitequark: they're dog slow and you can't pattern match on them
<Drup> whitequark: slow, no full row polymorphism
<whitequark> slow, hmmm
<rgrinberg> ive made some benchmarks not long ago
<_obad_> drup: what does "no full row polymorphism" mean in English?
<rgrinberg> at least 2x slower in the best case
<whitequark> rgrinberg: that's not bad at all
<ggole> Slower than what? Records?
<rgrinberg> ggole: yeah
Topher has joined #ocaml
<ggole> Mmm.
nikki93 has quit [Ping timeout: 245 seconds]
<Drup> _obad_: you can't have this function : "< foo > -> < x : int ; foo >
<ggole> I've never used objects yet.
<_obad_> drup: i.e. a function that extends an object with a method
q66 has joined #ocaml
q66 has quit [Changing host]
q66 has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
<Drup> _obad_: more generally, function that are abstractions along a "row"
<Drup> abstracts*
<_obad_> drup: where does that row terminology come from? are there rows? what are columns?
<Drup> _obad_: well, as everything, it's a type theory thingy :D
<_obad_> what's the TL;DR
nikki93 has joined #ocaml
<Drup> when you have a record type
<Drup> a row is part of this record
<Drup> of this record type*
<_obad_> is every field a row?
<Drup> not every
<Drup> some
<mrvn> records don't have row types, only objects
<Drup> mrvn: talking in general
<mrvn> right?
<Drup> mrvn: in ocaml, it's a bit more complicated
<_obad_> is it like a part of the lattice of subtypes?
<_obad_> like all elements that are <= than some element?
<Drup> no, it's different
<Drup> you can do this kind of stuff with subtyping or row polymorphism
<Drup> with objects, it's done with subtyping
<_obad_> *googles row polymorphism*
q66 has quit [Quit: Leaving]
nikki93 has quit [Ping timeout: 240 seconds]
<ggole> Row polymorphism is like heated discussion polymorphism, only a bit more heated.
<Drup> ggole: why is it heated ?
<Drup> either people don't know it or they like it, in my experience :D
<ggole> Hmm, this joke might not go over with non-English speakers.
<Drup> oh
nikki93 has joined #ocaml
<ggole> "row" being another term for "argument"
<Drup> oh :D
<_obad_> ggole: now it starts to make sense
<ggole> I was going to follow that up with something about "blazing row polymorphism", but never mind. It's dead.
<Drup> ggole: no no, it's very good, my terrible english is the one to blame :)
<ggole> Something something my type checker is on fire
<_obad_> ok so based on https://www.cs.cmu.edu/~neelk/rows.pdf slide 7 it sounds like a row is a partial record
<_obad_> type
nikki93 has quit [Ping timeout: 252 seconds]
<smondet> _obad_: this seems to explaine the difference with subtyping: http://brianmckenna.org/blog/row_polymorphism_isnt_subtyping
<Drup> _obad_: exactly
<Drup> _obad_: sorry, multi tasking is bad for pedagogy.
<_obad_> drup: so what you want is mixins
<_obad_> slide 13
q66 has joined #ocaml
q66 has quit [Changing host]
q66 has joined #ocaml
<mrvn> smondet: "Well, subtyping and type inference just don't mix. Doing type inference with row polymorphic records is much easier." Somehow I feel the exact opposite
<Drup> _obad_: mixins is the syntactic construct for that, yes :)
<smondet> @mrvn:
<smondet> I don't know
Topher has left #ocaml []
<smondet> enough about that
<mrvn> What he calls Row Polymorphism seems to be to be impossible in ocaml without adding indirection to record labels.
<mrvn> s/be/me/
<mrvn> Specifically the "let f x = x with {sum: x.a + x.b}" bit
<mrvn> That would require runtime type infos to say if the record already has "sum" and where.
<_obad_> runtime type infos are bad, mmmmkay
<Drup> mrvn: it's already in objects
tobiasBora has joined #ocaml
<mrvn> Drup: 1) objects use indirection, 2) you still can't extend objects like that
<Drup> indeed
<_obad_> drup: are they? is there a place where the runtime representation of objects is described?
<Drup> _obad_: don't have link for you to read, sorry
<whitequark> objects seem to be really obscure.
<whitequark> in many ways
Thooms has quit [Quit: WeeChat 0.3.8]
<_obad_> according to translcore.ml objects seem to be represented at least partially as arrays
<adrien> isn't everything in ocaml an array? :P
<Drup> _obad_: objects are dictionaries, basically.
<mrvn> a value
<_obad_> drup: found it, it's in camlinternalOO.ml
<mrvn> and a value can be a primitive type or a pointer to a block
zpe has joined #ocaml
<_obad_> for i = 0 to len - 1 do methods.(i*2+3) <- magic pub_labels.(i) done;
<_obad_> O.O
<adrien> open Obj
<adrien> <3
<Drup> *magic*
<adrien> should have been called "dirty"
<ggole> Object typing is almost as magical :/
<adrien> Obj.dirty
<ggole> Obj.wrong
<_obad_> adrien: it wouldn't go with the camels - arabian night - flying carpet magic theme
<whitequark> Obj.nope
<_obad_> Obj.saddam
<mrvn> I object
<Drup> to be expected :D
<adrien> _obad_: hehe :P
<whitequark> mrvn: you object!
<whitequark> (as in "you monster!")
<whitequark> although that remark should've been directed at companion_cube
<ggole> I wonder if Obj.magic would be used less often it it had a long ugly name
<companion_cube> hey
<mrvn> Obj.you_know_you_should_not_do_this
<whitequark> Obj.kill_a_kitten
<ggole> Anybody with a degree in lexical psychology here?
zpe has quit [Ping timeout: 252 seconds]
<adrien> Obj.c_plus_plus
lostcuaz has quit [Ping timeout: 265 seconds]
<whitequark> Obj.php
<adrien> short but effective
lostcuaz has joined #ocaml
<_obad_> one problem is that you can't have a class whose constructor is a thread
<_obad_> i.e. you can't have: class blah ~filename () = Lwt_io.with_open_file filename (fun blah -> ...)
<ggole> Lwt_io.with_open_file filename (fun blah -> object ... end)?
<ggole> But of course there are limitations there.
<_obad_> now try inheriting from that
<ggole> ^
<_obad_> exactly
dapz has joined #ocaml
<Drup> avsm, thomasga : did you tried the "install" target for the new makefile ?
<thomasga> which makefile ?
<Drup> huh, sorry, context
<Drup> opam
<thomasga> hum no
<Drup> I'm having a "make: src/opam-installer: commande introuvable'
<thomasga> just had a quick look: run 'make fast' maybe ?
<thomasga> or cd src && make opam-installer
<thomasga> I'm not really running opam trunk, so I don't know :p
<Drup> thomasga: the fact that "make lib-ext" was the default before and is not anymore is annoying, for packaging matters :)
<thomasga> you're right, please feel free to open a bug report
<Drup> thomasga: first I'm trying to make it install :x
<avsm> Drup: i kind of prefer the explicit lib-ext step as it makes packaging easier
<avsm> implicit downloading is the bane of packaging
<Drup> you're right, I'm just saying the change was not transparent, for packagers :)
clan_ has quit [Quit: clan_]
<Drup> now, I have "Fatal error: exception OpamSystem.Process_error(_)" :(
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
clan_ has joined #ocaml
cdidd has quit [Remote host closed the connection]
clan_ has quit [Client Quit]
nikki93 has joined #ocaml
clan_ has joined #ocaml
cdidd has joined #ocaml
rgrinberg has joined #ocaml
<whitequark> Error: This expression has type int but an expression was expected of type int
<whitequark> ಠ_ಠ
<whitequark> what
<whitequark> oh, I made a tuple of one element
<ggole> How do you do that?
<ggole> With ppx?
<mrvn> how?#
manizzle has joined #ocaml
<whitequark> yes
<whitequark> should probably report it as an error, seeing as unless I knew exactly what I just changed, I could debug it for years
<mrvn> how you can't even express a one-tuple as type.
<mrvn> +?
<whitequark> Ast_helper.Exp.tuple [a]
* whitequark shrugs
<whitequark> apparently, you can, though not in surface syntax
<mrvn> That should probably fail if the list has only one element.
<ggole> Maybe you should suggest that the function should raise Invalid_argument for an argument of length one.
rgrinberg has quit [Quit: Leaving.]
<whitequark> ggole: that wouldn't help if one would construct it directly from ADTs
<ggole> Er, how so?
<ggole> Are you saying you want tuple_or_solitary_thing instead of tuple?
<whitequark> no, I meant you can still do Pexp_tuple [a]
<ggole> Oh, I see. It isn't a private type.
<whitequark> yeah
<whitequark> probably couldn't be, Ast_helper isn't used internally
<ggole> Shame you can't hang verification code on constructors.
<whitequark> does any language at all allow that?
<whitequark> for variants especially
<ggole> You can verify in, say, C++ constructors
nikki93 has quit [Ping timeout: 276 seconds]
<whitequark> >for variants
<whitequark> well, sum types. C++ doesn't have them; Haskell, OCaml, Rust, etc don't have constructors for sum types
<ggole> It's the same idea, more or less
<whitequark> only functions returning them
<ggole> By OCaml I assume you mean SML
<ggole> But yeah.
<mrvn> ggole: if you want verification use a private type
<ggole> That works, but has downsides: the api gets larger and clumsier and harder to change, and any existing code is broken.
<whitequark> would be cool if you could match on functions by hanging an annotation on it, "this function always returns this variant"
<mrvn> one could build barebones ctr*.o and then compile the kernel like a normal C binary.
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<mrvn> usp
dapz has joined #ocaml
rgrinberg has joined #ocaml
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 245 seconds]
zpe has joined #ocaml
Thooms has joined #ocaml
shinnya has joined #ocaml
angerman_ has joined #ocaml
<whitequark> wait, what base are ocaml's '\000' escape sequences in?
<whitequark> ten? O_o
<whitequark> \009 is valid
<tautologico> what's the value of \009? 9?
<whitequark> apparently
<tautologico> weird
lostcuaz has quit [Quit: Textual IRC Client: www.textualapp.com]
zpe has quit [Ping timeout: 265 seconds]
angerman has quit [Ping timeout: 245 seconds]
dnm_ has quit []
<adrien> why?
<_obad_> 10
<adrien> why weird?
<mrvn> others have base 8
<_obad_> ridiculous escape convention is ridiculous...
nikki93 has joined #ocaml
<_obad_> I mean NO ONE EVER uses octal except for (a) Unix modes and (b) (some) C char escapes...
<_obad_> and even in C we have \x
<whitequark> it used to be prevalent on PDP-7 which used 12-bit bytes
<tautologico> yeah, but it's the convention everyone is used to because of C
nikki93 has quit [Remote host closed the connection]
<_obad_> whitequark: when's the last time you've booted a PDP-7? :)
<_obad_> tautologico: ok but even in C everyone uses \x
<tautologico> _obad_: sure, but if you see a \0xx you expect octal
<whitequark> _obad_: I think last PDP-7 was sent to a landfill before I was born
<_obad_> tautologico: true, but I guess \d123 would have been too long
<whitequark> just use \xnn
<_obad_> too bad %S uses decimal
nikki93 has joined #ocaml
<whitequark> fucking ocp-build, it is so annoying I can't use utop on trunk
ygrek has quit [Ping timeout: 246 seconds]
<rgrinberg> how does utop depend on ocp-build?
<whitequark> ocp-index*
<whitequark> still as annoying
yacks has quit [Quit: Leaving]
<Drup> whitequark: I ended up not installting it and asking emacs to use the one in the 4.01.0 switch
olauzon has quit [Quit: olauzon]
maattdd__ has joined #ocaml
nikki93 has quit [Remote host closed the connection]
olauzon has joined #ocaml
eizo has quit [Ping timeout: 240 seconds]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
lostcuaz has joined #ocaml
lostcuaz_ has joined #ocaml
lostcuaz_ has quit [Read error: Connection reset by peer]
lostcuaz_ has joined #ocaml
clan_ has quit [Quit: clan_]
clan_ has joined #ocaml
lostcuaz has quit [Ping timeout: 276 seconds]
oriba has quit [Quit: oriba]
eizo has joined #ocaml
olauzon_ has joined #ocaml
olauzon has quit [Ping timeout: 276 seconds]
olauzon_ is now known as olauzon
dsheets has quit [Ping timeout: 246 seconds]
<_obad_> so who was working on the lwt ppx extension here?
<Drup> me
<_obad_> what's the status?
<_obad_> can I use it?
<Drup> not yet
<companion_cube> yes, you can use Drup
<_obad_> :(
<_obad_> :) because I can use drup
alinab has joined #ocaml
<Drup> _obad_: why would you even need it ? wait for 4.02
<_obad_> ehhhhh.... coz I'm writing code?
<_obad_> and it will be incompatible
<Drup> sed will be your friend, the translation is trivial
<_obad_> fine
<Drup> (and it's not going to be incompatible, the lwt camlp4 syntax extension will still be there)
ikaros has quit [Quit: Ex-Chat]
<_obad_> and I need it for stream parsers anyway
Hannibal_Smith has quit [Quit: Sto andando via]
dapz has joined #ocaml
nikki93 has joined #ocaml
<whitequark> Drup: why not yet, btw?
<Drup> because it's not finished and still in a fork, it makes no sense to use it for real code
<Drup> if you want to play with it, sure :)
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
<ggole> Why doesn't List define List.t?
<mrvn> because the compiler doesn't have a functor over lists
<ggole> :|
<ggole> I guess I can module List = type 'a t = 'a list include List end
thomasga has quit [Quit: Leaving.]
malo has joined #ocaml
zpe has joined #ocaml
ousado has quit [Ping timeout: 250 seconds]
<_obad_> I want to do this: module type S = sig type t end
<_obad_> and then: module PROD(X : S)(Y : S) = struct type t = [ X.t | Y.t ] end
<_obad_> but I get: Error: The type X.t is not a polymorphic variant type
<_obad_> is there a type constraint I can use?
<mrvn> a type can't be two things unless they can be unified
<whitequark> "[> ] as 'a" is an empty polymorphic type
<whitequark> it will properly unify with any
<whitequark> though I've no idea if you can plug it there somehow
<whitequark> polymorphic variant type*
ousado has joined #ocaml
<mrvn> You can have type t = [< `X of X.t & Y.t ]
<mrvn> or type t = X of X.t | Y of Y.t
<Drup> except that it's not what he want
rand000 has joined #ocaml
<Drup> and it's probably going to be empty
<mrvn> _obad_: what do you actualy want to do?
<_obad_> well I'm hierarchically building up a message type
<_obad_> it works pretty well, so I do have for example
<mrvn> do you want type t = X.t * Y.t?
<_obad_> module X = struct type query = [`ping] let format_query fmt `ping = ... end
<_obad_> module Y = struct type query = [`reset] let format_query fmt `reset = ... end
<whitequark> _obad_: don't use `variants starting with a lowercase letter, they're deprecated
<Drup> are they ?
<whitequark> I think they are
<Drup> I never got a warning with that
<whitequark> yes, somehow there's no warning
<_obad_> module XY = struc type query = [ X.query | Y.query ] let format_query = function #X.query as q -> X.format_query q | etc
<_obad_> whitequark: hmm ok I'll uppercase them
<_obad_> anyway you get the picture
<_obad_> so it works, and I wanted to generalize it because it gets boring
<mrvn> type a = [ `A ] type b = [ `B ] type t = [ a | b ];;
<mrvn> _obad_: do you want that?
<_obad_> kinda, a and b are in their own modules
clan_ has quit [Quit: clan_]
<_obad_> and I want a module that creates the product of the two
axiles has quit [Remote host closed the connection]
<mrvn> module A = struct type a = [ `A ] end module B = struct type b = [ `B ] end module AB = struct type t = [ A.a | B.b ] end;;
<Drup> ...
<_obad_> yeah that's what I have been doing
<mrvn> _obad_: and now you want a functor that takes 2 modules and makes combined type?
<_obad_> now I want a functor... exactly
<_obad_> so I suppose you need to tell in the signature that A.a and B.b are variant types so that [ a | b ] makes sense
<companion_cube> it may be [ #a | #b ]
<whitequark> [ #a ]? I don't see that in Parsetree
<Drup> it doesn't work
<Drup> # is only for match
<whitequark> Drup: btw, what does it do for match?
<whitequark> I've never seen it
<ggole> Matches any constructor in that type
<whitequark> cool
<_obad_> yeah that's how I dispatch to submodules
<_obad_> it's pretty neat
<Drup> type t = [ 'A | 'B ]
<whitequark> imo you're overengineering
<Drup> math x with #t -> deal_with_t | `C -> stuff
<ggole> whitequark: you might find Jacques' paper on polymorphic variants interesting
<Drup> this will accept `A | `B | `C
<whitequark> caml.inria.fr/pub/papers/garrigue-polymorphic_variants-ml98.ps.gz‎
<adrien> they're <3 for tags
<whitequark> ?
<ggole> Er, you found the link faster than I did O_o
<_obad_> well it may seem overengineered so but the module hierarchy defines the system topology at the same time
<ggole> Yep
<_obad_> .ps? holy gv 1998
clan_ has joined #ocaml
<_obad_> at least it's not .dvi
<whitequark> hm... 9 pages. I'll read it tomorrow, when I'm not as braindead
* whitequark has been hacking on ppx_protobuf for 14 hours straight
<mrvn> how do you write a polymorphic variant type in a signature?
<whitequark> mrvn: [ `A ] ?
<whitequark> weird question
<mrvn> whitequark: an abstract polymorphic variant type
<ggole> Abstract how?
dotfelix has joined #ocaml
<mrvn> sig type t end
<whitequark> oh. no such thing. all types aliasing primitives are already abstract
<ggole> Just like that
<whitequark> i.e. type t = int is abstract, but known same to int
clan_ has quit [Client Quit]
<whitequark> (you can see it in Parsetree)
<ggole> You can't use open types with that signature though
<ggole> Since they imply a type variable
<mrvn> ggole: type t doesn't count as polymorphic variant
<_obad_> kinda reminds me of module type Z = sig type 'a t = < .. > as 'a end
<whitequark> type 'a t = 'a constraint 'a = [> ]
clan_ has joined #ocaml
<whitequark> seems to work.
<mrvn> type t = [> ] as 'a doesn't work as 'a is unbound and type 'a t = [> ] as 'a again doesn't count as polymorphic variant type
<whitequark> although I'm not sure what you can do withi t
<mrvn> Error: The type [> ] A.t is not a polymorphic variant type
<whitequark> I see
<ggole> Hmm.
<Drup> whitequark: that's the first thing I tried
<Drup> :/
<ggole> The only polymorphic variant types I've ever exposed were closed, which work ok
<Drup> whitequark: I'm a bit surprised it doesn't work
<ggole> eg module Foo = struct type t = [`A | `B] end type zonk = [Foo.t | `C]
<_obad_> is it me or are poly variants missing from http://caml.inria.fr/pub/docs/manual-ocaml-4.01/typedecl.html#constr-decl ?
clan_ has quit [Client Quit]
<mrvn> ggole: now do that in a functor.
<Anarchos> ggole this syntax is allowed ?
<Drup> _obad_: "module type S = sig type 'a t = ([> ] as 'a) end" and "module PROD(X : S)(Y : S) = struct type ('a,'b) t = [ 'a X.t | 'b Y.t ] end"
<ggole> mrvn: works fine? I may be missing something though.
<Drup> that *should* work
<Drup> but it doesn't
<Drup> don't know why
<Drup> it might be a question worth asking the mailing list
<ggole> module type X = sig type t = [`A | `B] end module type Y = sig type t = [`C | `D] end module F (X:X) (Y:Y) = struct type t = [X.t | Y.t] end
<mrvn> ggole: show us your functor
<mrvn> ggole: that isn't generic.
<_obad_> Drup: Error: The type [> ] X.t is not a polymorphic variant type
<mrvn> ggole: we want something you can apply to moduled A B C D E F G H recrsively to build a bigger and bigger type
<Drup> _obad_: I know
<Drup> I said it *should*
<Drup> I don't know why the typecheck don't like it
<mrvn> Drup: because you need the details of A.t, the 'a. The signature hides that.
<Drup> mrvn: it's still a poly var
<mrvn> Drup: it should but somehow isn't.
<mrvn> time to ask the ML.
<_obad_> ok
<Drup> mrvn: that's what I said ...
oriba has joined #ocaml
<Drup> mrvn: why do you repeat to me the same remark I just did ?
<mrvn> becase I agree with you
<Drup> that's a weird way of agreeing
<mfp> anybody able to explain what I'm misunderstanding about Lwt_react.E.next and/or React.S.changes in this code? -> http://paste.debian.net/96864/
<mfp> expected to print 1...20, instead keeps writing 1 1 1
rgrinberg has quit [Quit: Leaving.]
<_obad_> mail sent
clan_ has joined #ocaml
dotfelix has quit [Quit: Leaving...]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
<whitequark> jpdeplaix: ok, looks great
<whitequark> let me dust off git-svn...
pyon has joined #ocaml
<whitequark> jpdeplaix: r207793
dnm has joined #ocaml
Arsenik has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
<mfp> for the record, the issue with Lwt_react.E.next is that as per the synchrony hypothesis the next iteration is still within the same update step
thomasga has joined #ocaml
<mfp> it would maybe make sense to define Lwt_react.E.next as follows > http://paste.debian.net/96883/
<jpdeplaix> whitequark: thanks ! :)
tobiasBora has quit [Ping timeout: 246 seconds]
thomasga has quit [Ping timeout: 240 seconds]
tobiasBora has joined #ocaml
tani has quit [Quit: Verlassend]
clan_ has quit [Quit: clan_]
eizo has quit [Ping timeout: 240 seconds]
ikaros has joined #ocaml
ikaros has quit [Remote host closed the connection]
Submarine has quit [Remote host closed the connection]
rand000 has quit [Quit: leaving]
<jpdeplaix> whitequark: So I guess I should put an issue to the bug tracker for the addition to the build system ?
avsm has quit [Quit: Leaving.]
ikaros has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
<jpdeplaix> whitequark: oh well. There is a mailing-list for that. I'm writing a mail
chambart has joined #ocaml
racycle has quit [Quit: ZZZzzz…]
maattdd__ has quit [Ping timeout: 252 seconds]
sgnb has quit [Remote host closed the connection]
sgnb has joined #ocaml
olauzon has quit [Quit: olauzon]
racycle has joined #ocaml
tobiasBora has quit [Quit: Konversation terminated!]
thomasga has joined #ocaml
AltGr has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
thomasga has quit [Ping timeout: 255 seconds]
AltGr has left #ocaml []
Simn has quit [Quit: Leaving]
ollehar1 has joined #ocaml
Thooms has quit [Ping timeout: 276 seconds]
waneck has joined #ocaml
avsm has joined #ocaml
dapz has quit [Quit: Textual IRC Client: www.textualapp.com]
fraggle_laptop has joined #ocaml
ollehar1 has quit [Ping timeout: 276 seconds]
oriba has quit [Quit: oriba]
ggole has quit []
nikki93 has quit [Remote host closed the connection]
skchrko has quit [Ping timeout: 252 seconds]
tlockney is now known as tlockney_away
struktured has joined #ocaml
nikki93 has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
skchrko has joined #ocaml
lostcuaz_ has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 276 seconds]
madroach has quit [Ping timeout: 252 seconds]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
madroach has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
darkf has joined #ocaml
chambart has quit [Ping timeout: 245 seconds]
thomasga has joined #ocaml