ChanServ 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 | Logs at http://irclog.whitequark.org/ocaml
<whitequark> well, that part is just [%expr (&&)]
<whitequark> not different much
<whitequark> but three nested quasiquotations?
<Drup> :)
<Drup> You want a printf-like notation for ppx in order to un-nest them ? :)
<whitequark> NO
<whitequark> whitequark.org/no
<Drup> oh !
<Drup> it's so cute
pjdelport has quit [Quit: Connection closed for inactivity]
<Drup> why the strong objection, by curiosity ?
<Drup> I can think of multiple reasons :p
troutwine_away is now known as troutwine
<whitequark> I find the current printf syntax ... barely passable in a language like OCaml
<whitequark> and the current format syntax thoroughly disgusting
<Drup> ahah
<whitequark> printf should be basically
<whitequark> Printf.printf "the value of i is: {i}"
<Drup> but you can't curry that !
<companion_cube> agree with Drup
<whitequark> 80% of the time I don't want to
<companion_cube> I do :p
<companion_cube> also, what about %a ?
<Drup> whitequark: and how would you compose printers ?
<whitequark> that desugars to %a
<Drup> and how do you magically decide which printer to use ?
<whitequark> oh, right, need type-driven decisions
<whitequark> grmbl
<Drup> :D
<whitequark> I'll still make ppx_quasiquot, because I'm insane
<whitequark> using the substitution technique I elaborated earlier
<Drup> whitequark: this work just fine in a language without global type inference
<Drup> (or with lot's of introspection)
<whitequark> ocaml doesn't have global inference?
<Drup> it does, my point
<Drup> "this = type-driven code generation"
<Drup> (a field which deserves a lot of research grants, because there are lots of stuff to do)
thomasga has joined #ocaml
<whitequark> I'll just put a "let __var$i = assert false" there and substitute %a arguments with __var$i
<def`> One could imagine gathering a set of constraints and eventually call an external extension to generate an implicit instance
<whitequark> and look what type typechecker will assign
<whitequark> brutal. but efficient.
troutwine is now known as troutwine_away
<Drup> whitequark: (did you know : it's basically what eliom is doing ...)
<whitequark> hah!
<whitequark> I didn't even know that eliom needs that
<whitequark> (but it is obvious in retrospect)
pjdelport has joined #ocaml
<whitequark> ooooh I'm going to give a lightning talk on Eliom at a Rails conf in russia
<Drup> the client/server typing is a mess
<whitequark> TODO: actually learn eliom
<whitequark> (cough)
<Drup> whitequark: well, there is a video about ocsigen from OUPS :)
<Drup> whitequark: your idea is simple on paper
<Drup> and it almost work
<Drup> until you mix polymorphism in
<Drup> and then, everything explode
<whitequark> example?
<whitequark> oh, like 'a list ?
<whitequark> it'll derive a value with a free type variable
<whitequark> a type*
<Drup> No, like "the type is fixed by the client but the server doesn't know it because the inference is no bidirectionnal"
<whitequark> I'll pattern-match the generic signature of Show over that and it'll work
<whitequark> oh, in Eliom
<Drup> in general, if you have two universe (inside and outside the quotation) that needs to communicate their type constraints.
<Drup> fortunately for you, you don't need it for basic printing
<whitequark> yes...
penglingbo has quit [Ping timeout: 240 seconds]
<whitequark> you could *maybe* marry the two typing environments
<Drup> yes
<Drup> I will work on that around septembre
<Drup> september*
<Drup> I expect it to be acrobatic :D
<whitequark> lol
<bernardofpc> Drup: where do you work?
<Drup> in september, i will work in the ocsigen team, basically
<Drup> for now, in the verimag lab
<bernardofpc> is that INRIA-related ?
<Drup> french-research-that-is-not-inria :D
<bernardofpc> CNRS ?
<bernardofpc> hum, Grenoble
thomasga has quit [Quit: Leaving.]
jwatzman|work has quit [Quit: jwatzman|work]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
avsm has joined #ocaml
beanrustler has joined #ocaml
oriba has quit [Quit: oriba]
<beanrustler> Beginner question: I'm trying to run Sys.command inside an infinite while loop and I'm getting a type error. Has int, expects unit. Can anyone offer some guidance? Many thanks.
<whitequark> ignore (...)
<whitequark> i.e. ignore (Sys.command ...)
hausdorff has quit [Remote host closed the connection]
strmpnk has joined #ocaml
englishm has joined #ocaml
<beanrustler> whitequark: Wow, thanks; that certainly cleared it up. Would it be too much to ask why that's needed, or to have a reference to an explanation?
<whitequark> the idea is that purely side-effecting expressions have type `unit', and while is fundamentally an imperative construct
<whitequark> so the return type of whatever's inside is unified with unit
hausdorff has joined #ocaml
<tobiasBora_> Does anyone has ever see this error "cannot load shared library dlllwt-unix-stubs" ?
<whitequark> ohhh, I remember something like that
<tobiasBora_> (I get it when I run a bytecode of my app on windows)
<whitequark> oh, windows, so not opam. no idea then
englishm has quit [Remote host closed the connection]
englishm has joined #ocaml
<tobiasBora_> But the bytecode isn't supposed to pack all libraries ?
<whitequark> hm?
<whitequark> try building with -custom
englishm1 has joined #ocaml
<tobiasBora_> Great that's the solution I didn't though about that thank you !
Denommus has joined #ocaml
troutwine_away is now known as troutwine
hausdorff has quit [Remote host closed the connection]
craigglennie has quit [Quit: craigglennie]
<tobiasBora_> Grrrr.... I just link the Batteries library to my project (I don't use any function) and it calls the unknow C primitive wait_pid...
<tobiasBora_> Why is it raised even if I don't call any function ?
troutwine is now known as troutwine_away
q66 has quit [Quit: Leaving]
beanrustler has quit [Quit: Page closed]
tristero has quit [Ping timeout: 240 seconds]
tristero has joined #ocaml
tobiasBora_ has quit [Quit: Konversation terminated!]
hlupe has quit [Excess Flood]
hexo has joined #ocaml
deavid has quit [Ping timeout: 240 seconds]
<Drup> the video I linked on the channel a few days ago are now here : https://www.irill.org/videos/OUPS-2014-07
hausdorff has joined #ocaml
deavid has joined #ocaml
<Drup> videos* even
manizzle has quit [Ping timeout: 250 seconds]
shinnya has quit [Ping timeout: 272 seconds]
travisbrady has joined #ocaml
jao has quit [Remote host closed the connection]
jabesed has quit [Quit: Konversation terminated!]
jabesed has joined #ocaml
WraithM has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
HaseebR7 has joined #ocaml
hausdorff has quit [Remote host closed the connection]
troutwine_away is now known as troutwine
penglingbo has joined #ocaml
penglingbo has quit [Ping timeout: 245 seconds]
travisbrady has quit [Quit: travisbrady]
jprakash has quit [Ping timeout: 256 seconds]
craigglennie has joined #ocaml
jpdeplaix has quit [Ping timeout: 240 seconds]
troutwine is now known as troutwine_away
tidren has joined #ocaml
manizzle has joined #ocaml
tautologico has joined #ocaml
travisbrady has joined #ocaml
tidren has quit [Remote host closed the connection]
<tautologico> any recommended way to read the whole contents of a file?
tidren has joined #ocaml
penglingbo has joined #ocaml
jpdeplaix has joined #ocaml
<Drup> Buffer.add_channel
<Drup> + in_channel_lenght
hausdorff has joined #ocaml
hausdorff has quit [Remote host closed the connection]
hausdorff has joined #ocaml
hausdorff has quit [Remote host closed the connection]
tidren has quit [Remote host closed the connection]
<tautologico> thanks
tidren_ has joined #ocaml
ygrek has joined #ocaml
tidren_ has quit [Remote host closed the connection]
<whitequark> Drup: Eq!at 97 lines
<whitequark> and developer documentation.
<Drup> nice :)
travisbrady has quit [Quit: travisbrady]
travisbrady has joined #ocaml
<Drup> whitequark: your code is .. dense
troutwine_away is now known as troutwine
<whitequark> is it?
<Drup> well, it's your usual side, which is significantly more dense than my style, that's all ^^'
<Drup> s/side/style/
BitPuffin has quit [Ping timeout: 260 seconds]
troutwine is now known as troutwine_away
fold has quit [Ping timeout: 245 seconds]
* whitequark is looking at other possible Deriving plugins, based on what Rust has
<whitequark> Hash? Rand? Default? Clone?
<whitequark> Clone seems marginally useful and probably best *not* created automatically.
<whitequark> Rand, even less useful. Maybe for tests?
<Drup> I think companion_cube and gasche would be very interested for a fuel based Rand deriving for testing
<whitequark> I can't imagine how would I make Default work in presence of variants
<Drup> default, meh, don't see any point
<whitequark> not sure it is useful either
travisbrady has quit [Quit: travisbrady]
fold has joined #ocaml
tidren has joined #ocaml
<whitequark> ok so... Hash and Rand?
<Drup> well, json ? :p
<whitequark> Json, already accepted.
<whitequark> I don't know how to implement Hash. no hash interface to feed in OCaml.
<Drup> Hash, I know nicoo was trying to think of an interface to define hash combinators
<Drup> so, I would postpone
<whitequark> I don't really think combinators are needed, just a way to handle default types
<whitequark> builtin
<whitequark> "eat this Int64.t"
<Drup> well, the polymorphic hash function is enough then ....
<whitequark> for one, it's not cryptographically secure
travisbrady has joined #ocaml
<whitequark> or customizable
<Drup> yeah
<Drup> I don't know how you would implement it
<Drup> but tbh, I don't know shit about hashing
<whitequark> more or less I want some kind of IterBytes
penglingbo has quit [Ping timeout: 245 seconds]
<whitequark> Dump? Pickle?
englishm has quit [Remote host closed the connection]
englishm1 has quit [Quit: Leaving.]
<Drup> there is show with a pp, no point of dump
penglingbo has joined #ocaml
englishm has joined #ocaml
<Drup> oh, actually dump also does *un*marshalling
<tautologico> Default is useful when you're programming with traits / type classes
<whitequark> out of what?
<tautologico> not the case in OCaml
<Drup> whitequark: the thing that Dump outputs ? :D
<whitequark> I don't want to see the source
<Drup> Enum is mostly pointless
<Drup> I would rather have an Iter, and use companion_cube's sequence
<whitequark> Iter?
<Drup> derive an Iter function.
<Denommus> Drup: Enum?
<Drup> Denommus: link above
englishm_ has joined #ocaml
<Drup> oh, no, Enum is not an enumeration
<Drup> meh
englishm has quit [Read error: Connection reset by peer]
<Denommus> Drup: aaah, it's like an Enumerator. I was thinking of a tagged union
<Drup> those modules are badly named
<whitequark> am currently wondering if having [@@deriving Eq] create val equal_t : ... is bad
<whitequark> maybe I shouldn't have blindly cargo-culted the names from Rust
tidren has quit [Remote host closed the connection]
<whitequark> but I kinda like them
<Drup> hum ? what do you mean ?
<Denommus> whitequark: are you learning OCaml from a Rust background?
tidren has joined #ocaml
<Drup> there is no such thing as a "Rust background"
<whitequark> Denommus: no
<whitequark> also what Drup says
<Drup> Rust is too young for that
<whitequark> but I've only seen deriving in Rust
<Denommus> Drup: hehe, you have a point.
<Drup> whitequark: it comes from haskell
<whitequark> yes
tidren has quit [Read error: Connection reset by peer]
<whitequark> oh, that's Eq and Ord there, too
<Drup> what is the naming scheme in Rust ?
<Drup> yes
tidren has joined #ocaml
<whitequark> Show, Eq, Ord, Rand, Hash, Clone
<Denommus> but then, if the first statically typed language with a decent type system you have ever seen is Rust, then... well, OCaml is more approachable from Rust than from lots of mainstream languages
<Drup> and Show
<whitequark> now that we have open-types, can do deriving(Dyn)
<Drup> hum
<Drup> what would it do ?
<Denommus> I know more Rust than Haskell and now I'm trying to learn OCaml, for instance. And I already think I like it more than Haskell because of the module system
philtor has joined #ocaml
divyanshu has joined #ocaml
<Denommus> though a friend of mine is making me want applicative functors instead of generative ones. I just don't know how much the lack of applicative functors affect OCaml, though, since it is structurally typed
<whitequark> Drup: type dyn += Dyn_foo of foo = Dyn.t ;; let dyn_of_foo x = Dyn_foo x ;; let foo_of_dyn d = match d with Dyn_foo x -> Some x | _ -> None
<Drup> oh, t @@deriving Dyn would add a t case to a predefined universe type
<Drup> huum.
tidren has quit [Remote host closed the connection]
<whitequark> well, you could say
<Drup> I'm not sure how useful it is, it's not really an idiom I have in ocaml
<whitequark> @@deriving Dyn { t = "Foo_dyn.t" }
englishm has joined #ocaml
tidren has joined #ocaml
englishm_ has quit [Remote host closed the connection]
englishm has quit [Client Quit]
englishm has joined #ocaml
divyanshu has quit [Quit: Textual IRC Client: www.textualapp.com]
<Drup> whitequark: did you look at what Core have ?
<Drup> sexp and co
<Drup> type-conv too
englishm has quit [Ping timeout: 264 seconds]
<whitequark> well, yeah, type_conv
<Drup> if you want ppx_deriving to be used by everyone, you need to cover all type_conv, I'm afraid :)
<whitequark> eh, it's extensible
<whitequark> I'll let someone at janestreet do that (and quietly pray they don't NIH this as well...)
<Drup> no, don't pray
<Drup> if you pray, they will NIH it.
<whitequark> ...
<Drup> (at least, I think they will)
<whitequark> why does ounit even depend on type_conv?..
<whitequark> why does type_conv contain an union-find implementation?
troutwine_away is now known as troutwine
<whitequark> Drup: btw
<whitequark> deriving ToJson, FromJson won't have any implied dependency on yojson
<whitequark> because it uses polymorphic variants
troutwine is now known as troutwine_away
HaseebR7 has quit [Quit: Page closed]
seliopou has quit [Ping timeout: 240 seconds]
struktured has quit [Ping timeout: 240 seconds]
struktured has joined #ocaml
<whitequark> hm, does ocamlopt specialize compare too?
jabesed has quit [Quit: Konversation terminated!]
jabesed has joined #ocaml
travisbrady has quit [Quit: travisbrady]
avsm has quit [Quit: Leaving.]
<Drup> afaik, yes
jao has quit [Ping timeout: 245 seconds]
axiles has joined #ocaml
yacks has quit [Quit: Leaving]
hausdorff has joined #ocaml
yacks has joined #ocaml
siddharthv_away is now known as siddharthv
jabesed has quit [Ping timeout: 240 seconds]
<whitequark> yes
troutwine_away is now known as troutwine
jprakash has joined #ocaml
arquebus has joined #ocaml
craigglennie has quit [Quit: craigglennie]
troutwine is now known as troutwine_away
tac_ has joined #ocaml
<tac_> Hey guys
<tac_> Does Ocaml have a well-published "Core" lambda calculus like Haskell's System Fc?
<tac_> or Idris's TT (type theory)?
hausdorff has quit [Remote host closed the connection]
<Drup> no
<tac_> hmm
<Drup> there are various papers about some features
<tac_> Do optimizations just work directly on the source AST then?
<Drup> of course not
<Drup> you asked for a *well-published* Core
<Drup> :)
<Drup> there is a Core, it's just not properly formalized in a paper
<tac_> ahh
<Drup> (and it's not certainly not minimal either)
<tac_> :)
<tac_> I'm just fishing for examples of what lambda calculii look like in the wild
<tac_> for a talk on FP in general
badon has quit [Ping timeout: 240 seconds]
pgomes has joined #ocaml
<Drup> well, ocaml's IR doesn't really look like lambda calculus
<Drup> depends at which level, I guess
<tac_> gotcha
<Drup> (my opinion is that lambda calculus would be a terribly poor IR)
<tac_> In the Haskell world at least, you go through a lot of funnels until you make it down to object files
<Drup> ghc is a bit ... convoluted
<tac_> but Haskell is also willing to rely more on compiler wizardry
<tac_> for sure :)
<Drup> yeah, ocaml's compiler is not doing a lot of wizardry
<tac_> It's something like source language -> desugar loop -> core -> optimized core -> STG -> C-- -> LLVM -> Object code
<tac_> Mostly, I just want a screencap of something like this, but for Ocaml:
<Drup> you won't find any that is complete
<Drup> what you can find, however, are papers describing specific features
<tac_> hmm
<Drup> so, I would say guarigues papers, mostly
<tac_> thanks
<Drup> and people from the gallium team
<Drup> for the object system, you can probably refer to jerome vouillon's thesis.
<Drup> It's Garrigue*, sorry
<Drup> (can't spell ~~)
hausdorff has joined #ocaml
agarwal1975 has quit [Read error: Connection reset by peer]
philtor has quit [Ping timeout: 250 seconds]
agarwal1975 has joined #ocaml
struktured has quit [Ping timeout: 256 seconds]
struktured has joined #ocaml
tidren has quit [Remote host closed the connection]
tidren has joined #ocaml
tidren has quit [Ping timeout: 240 seconds]
pgomes has quit [Ping timeout: 250 seconds]
philtor has joined #ocaml
tidren has joined #ocaml
Eyyub has quit [Ping timeout: 255 seconds]
Eyyub has joined #ocaml
pgomes has joined #ocaml
ggole has joined #ocaml
pgomes has left #ocaml ["Leaving"]
troutwine_away is now known as troutwine
Simn has joined #ocaml
philtor has quit [Ping timeout: 272 seconds]
avsm has joined #ocaml
ygrek has quit [Ping timeout: 250 seconds]
seliopou has joined #ocaml
troutwine is now known as troutwine_away
Valdo has quit [Ping timeout: 240 seconds]
jordjordjord has joined #ocaml
badon has joined #ocaml
Valdo has joined #ocaml
fraggle_ has quit [Remote host closed the connection]
hhugo has joined #ocaml
avsm has quit [Read error: Connection reset by peer]
avsm has joined #ocaml
fraggle_ has joined #ocaml
parcs has quit [Read error: Connection reset by peer]
troutwine_away is now known as troutwine
hausdorff has quit [Remote host closed the connection]
troutwine is now known as troutwine_away
tautologico has quit [Quit: Connection closed for inactivity]
rand000 has joined #ocaml
FreeArtMan has joined #ocaml
parcs has joined #ocaml
tane has joined #ocaml
ygrek has joined #ocaml
demonimin has quit [Remote host closed the connection]
eikke__ has joined #ocaml
demonimin has joined #ocaml
zpe has quit [Remote host closed the connection]
_0xAX has joined #ocaml
cago has joined #ocaml
<companion_cube> Drup: gasche already wrote fuel-based random generators
<Drup> companion_cube: but not a deriving for it :3
<tac_> Ocaml is self-compiling, right?
<Drup> yes
<companion_cube> Drup: ah.
<Drup> Drup pokes at companion_cube
<Drup> come on, you can write some deriving too :D
teiresias has quit [Ping timeout: 250 seconds]
<whitequark> bleargh, deriving Ord for variants
<companion_cube> when 4.02 is out
<whitequark> I *so* do not like it
elfring has joined #ocaml
teiresias has joined #ocaml
<companion_cube> whitequark: start with a _to_int : t -> int function, write the n matching cases, and use _to_int for other cases
<companion_cube> transforms n^2 cases into 2n
<whitequark> n
<whitequark> where did you get 2n?
<companion_cube> well, you write _to_int + compare
<whitequark> (fun (a:int) b -> compare a b) (_to_int a) (_to_int b)
<whitequark> ;D
Kakadu has joined #ocaml
troutwine_away is now known as troutwine
* companion_cube coughs
<companion_cube> whitequark: do you use Lwt/async ?
<elfring> Would you like to share any experiences about configurations for comparison functions in software libraries?
<whitequark> companion_cube: Lwt
<companion_cube> elfring: what do you mean by configuring a comparison function?
<elfring> companion_cube: When would you dare to select a comparison approach which will be different from the function "compare" of the standard library?
<companion_cube> I often do, because I need specific behavior (mostly ignoring parts of the values)
<whitequark> compare is also slow
troutwine is now known as troutwine_away
<Drup> specialize compare is ok, isn't it ?
<Drup> (poly compare is very slow indeed)
<whitequark> but it won't specialize for complex structures
<Drup> indeed
<Drup> (a shame, since it would be quite fast on variants, since they are basically ints ...)
* whitequark mumbles something about deriving Ord
<Drup> :)
<companion_cube> :)
* companion_cube went the combinators way
<companion_cube> but both can be combined ;)
<elfring> Do you pass your special comparison functions around for some applications?
<companion_cube> I mostly use them for Map/Set
<Drup> companion_cube: [@@compare my_personnal_specialized_compare]
<whitequark> yeh, you can say [@equal (==)] for just that one field
<Drup> whitequark: did you already put the heuristic "if it's t, just use equal" ?
<Drup> (I didn't saw it in the documentation)
<whitequark> Drup: I looked at Core and looks like they use equal_t
<whitequark> at least where I was able to find it
<Drup> hum, ok
<whitequark> I have affixes hardcoded so far anyway
<Drup> that's probably because they auto generate it with type conv
<Drup> in batteries, it's "equal" only
darkf has quit [Read error: Connection reset by peer]
<Drup> (and in zarith too)
dant3 has joined #ocaml
<whitequark> I see
darkf has joined #ocaml
<whitequark> I will probably put it in
zpe has joined #ocaml
<elfring> When do you make comparison functions configurable in your software?
<Drup> make the profiling tells me that the polymorphic one is to slow.
<Drup> when*
<Drup> and too* ~~
<Drup> time to eat, brain needs nutriments.
<whitequark> Error: Variable _ is bound several times in this matching
<whitequark> um. wat?!
<Drup> you created a variable named "_" instead of using a pat_any ?
<whitequark> I used [%pat? _] ...
<Drup> well, try to replace it by pat_any and see if it solves it :)
<whitequark> no, that returns Ppat_any
<whitequark> oh, found another place
<whitequark> finished Ord.
hhugo has quit [Quit: Leaving.]
hhugo has joined #ocaml
<whitequark> I feel like releasing 0.1
<Drup> did you looked at what is inside type_conv ?
<whitequark> it was one of the first pieces of ocaml code i looked at
<whitequark> you can guess my reaction
<Drup> poor one :O
<Drup> (but I was talking only about the features, this time :D)
<whitequark> hm
<whitequark> what do you mean, specifically?
<Drup> to cover type_conv features with ppx_deriving
<whitequark> ah
<Drup> (so that people will not reinvent ppx_type_conv, which will have a huge overlap will ppx_deriving, like the current situation)
<Drup> with*
<whitequark> I will explicitly write this in the announce letter
<whitequark> "please do not reinvent type_conv, just open an issue and I'll implement what you want"
<companion_cube> :D
<Drup> :D
tidren has quit [Remote host closed the connection]
tidren has joined #ocaml
tidren has quit [Read error: Connection reset by peer]
tidren has joined #ocaml
<Drup> (well, i've seen several project born because "I was too lazy to report the bug upstream, it was easier to spin off my own version")
<whitequark> well, with some upstreams, it is true
<whitequark> something something OASIS
<whitequark> does a maintainer even exist in this universe? I am not convinced
<Drup> gildor is, technically, but yeah
<companion_cube> but still, it's hard to find a good alternative to oasis
badon has quit [Read error: Connection reset by peer]
badon has joined #ocaml
jonludlam has joined #ocaml
AltGr has joined #ocaml
<elfring> How are the chances to clarify the handling of comparison functions for template classes?
<whitequark> no one needs an object-oriented library of standard containers in ocaml
ski has joined #ocaml
q66 has joined #ocaml
jordjordjord has quit [Read error: Connection reset by peer]
jordjord_ has joined #ocaml
troutwine_away is now known as troutwine
badon has quit [Excess Flood]
BitPuffin has joined #ocaml
jonludlam has quit [Ping timeout: 260 seconds]
badon has joined #ocaml
jordjord_ has quit [Remote host closed the connection]
<elfring> Would you like to try out an evolving template class library a bit more for the programming language "OCaml"?
rossberg has quit [Ping timeout: 240 seconds]
<whitequark> I don't see any point in that
avsm has quit [Read error: Connection reset by peer]
avsm has joined #ocaml
<Drup> it would confuse beginners even more =')
troutwine is now known as troutwine_away
jonludlam has joined #ocaml
rossberg has joined #ocaml
tane has quit [Quit: Verlassend]
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 250 seconds]
darkf_ is now known as darkf
<jpdeplaix> 10:55:12 whitequark | something something OASIS // :) :)
<jpdeplaix> gildor gave not signes of life since the beginning of June :/
dsheets has joined #ocaml
skchrko has joined #ocaml
mfp has quit [Remote host closed the connection]
sagotch has joined #ocaml
thomasga has joined #ocaml
pminten has joined #ocaml
<nicoo> whitequark: Soon enough, we will have typecla^W implicits :>
<whitequark> yeah yeah
testcocoon has quit [Quit: Coyote finally caught me]
tac_ has quit [Ping timeout: 240 seconds]
testcocoon has joined #ocaml
sagotch has quit [Remote host closed the connection]
<companion_cube> whitequark: so what's your idea for doing typeclasses?
manizzle has quit [Ping timeout: 260 seconds]
manizzle has joined #ocaml
tidren has quit [Remote host closed the connection]
arquebus has quit [Quit: Konversation terminated!]
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
thomasga has quit [Client Quit]
maattdd has joined #ocaml
manizzle has quit [Ping timeout: 250 seconds]
pjdelport has quit [Quit: Connection closed for inactivity]
<jpdeplaix> whitequark: why show_file returns bytes ?
troutwine_away is now known as troutwine
jonludlam has quit [Ping timeout: 260 seconds]
mfp has joined #ocaml
troutwine is now known as troutwine_away
jonludlam has joined #ocaml
siddharthv is now known as siddharthv_away
rand000 has quit [Quit: leaving]
tobiasBora has joined #ocaml
arjunguha has joined #ocaml
arjunguha has quit [Client Quit]
pminten has quit [Quit: Leaving]
penglingbo has quit [Ping timeout: 256 seconds]
<elfring> How do you think about to discuss implementation details for OTCL?
ygrek has quit [Ping timeout: 260 seconds]
agarwal1975 has quit [Quit: agarwal1975]
thomasga has joined #ocaml
maufred has quit [Quit: leaving]
maattdd has quit [Ping timeout: 245 seconds]
agarwal1975 has joined #ocaml
agarwal1975 has quit [Client Quit]
craigglennie has joined #ocaml
englishm has joined #ocaml
NoNNaN has joined #ocaml
englishm_ has joined #ocaml
struktured has quit [Ping timeout: 260 seconds]
<Leonidas> can anyone explain to me how OCaml is QPL licensed, but still included in Debian, though the QPL is non-DFSG-conformant?
maattdd has joined #ocaml
penglingbo has joined #ocaml
<flux> it seems you can find a lot of discussion about this on the internets :)
<Leonidas> flux: yeah, that's actually too much discussion, I'm more interested in the conclusion :)
<nicoo> Leonidas: Doesn't Debian package the compiler (the only QPL-licensed part) spearately anyways ?
sagotch has joined #ocaml
<flux> but it's not in the non-free distribution
<flux> I would think the conclusion has been that QPL is in fact DFSG-conformant
<flux> or their version of QPL
<Leonidas> it seems so, yeah.
avsm has quit [Quit: Leaving.]
arj has joined #ocaml
shinnya has joined #ocaml
arj has quit [Quit: Leaving.]
pjdelport has joined #ocaml
darkf has quit [Quit: Leaving]
agarwal1975 has joined #ocaml
jprakash has joined #ocaml
<Unhammer> if type foo = Foo of string – is there a built-in way to do something like
<Unhammer> "foo" |> MakeMeAFoo
<Unhammer> ?
<Unhammer> or do I just have to make my own fn?
<mrvn> have your own function
<Unhammer> mkay
<mrvn> let makeMeAFoo foo = Foo foo
WraithM has quit [Ping timeout: 272 seconds]
<whitequark> jpdeplaix: because in 4.02 string prints as bytes
<whitequark> companion_cube: I'll just show you the code later
<jpdeplaix> oh you mean without -safe-string right ?
centrx has joined #ocaml
<centrx> It looks like each line ends with _two_ semicolons!?
Kakadu has quit [Ping timeout: 246 seconds]
troutwine_away is now known as troutwine
arjunguha has joined #ocaml
philtor has joined #ocaml
avsm has joined #ocaml
englishm_ has quit [Remote host closed the connection]
englishm has quit [Quit: Leaving.]
englishm has joined #ocaml
Kakadu has joined #ocaml
troutwine is now known as troutwine_away
philtor has quit [Ping timeout: 256 seconds]
avsm has quit [Quit: Leaving.]
englishm has quit [Remote host closed the connection]
englishm has joined #ocaml
englishm1 has joined #ocaml
tautologico has joined #ocaml
<Unhammer> centrx, only when you want to make the REPL (e.g. utop) evaluate something
<Unhammer> otherwise, lines end with no semicolon
<Unhammer> (a single semicolon is used to separate stuff, e.g. `print "foo"; print "bar"`, it has a quite different meaning from C/bash/python)
morphles has joined #ocaml
arjunguha has quit [Quit: Textual IRC Client: www.textualapp.com]
arjunguha has joined #ocaml
waneck has quit [Ping timeout: 240 seconds]
_0xAX has quit [Remote host closed the connection]
olauzon has joined #ocaml
ewd has joined #ocaml
<centrx> Well that's much better
rks` has quit [Ping timeout: 240 seconds]
<Unhammer> centrx, if you use emacs utop-mode, a C-j inserts two semicolons and evals
sagotch has quit [Ping timeout: 250 seconds]
sagotch has joined #ocaml
hausdorff has joined #ocaml
arjunguha has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
cago has quit [Quit: cago]
tautologico has quit [Quit: Textual IRC Client: www.textualapp.com]
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
tautologico has joined #ocaml
amirmc has joined #ocaml
troutwine_away is now known as troutwine
troutwine is now known as troutwine_away
maufred has joined #ocaml
gatorade has joined #ocaml
zpe has quit [Remote host closed the connection]
mort___ has joined #ocaml
BitPuffin has quit [Ping timeout: 240 seconds]
shinnya has quit [Ping timeout: 255 seconds]
stevej has quit [Quit: Computer has gone to sleep.]
Eyyub has quit [Ping timeout: 250 seconds]
stevej has joined #ocaml
sagotch has quit [Remote host closed the connection]
centrx has left #ocaml ["End transmission"]
ygrek has joined #ocaml
pminten has joined #ocaml
maattdd has quit [Ping timeout: 240 seconds]
arjunguha has joined #ocaml
morphles has quit [Ping timeout: 272 seconds]
oriba has joined #ocaml
teiresias has quit [Quit: BBL.]
maattdd has joined #ocaml
tautologico has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
BitPuffin has joined #ocaml
tautologico has joined #ocaml
tautologico has quit [Client Quit]
tautologico has joined #ocaml
misv has quit [Ping timeout: 240 seconds]
troutwine_away is now known as troutwine
amirmc has quit [Quit: Leaving.]
Kakadu_ has joined #ocaml
misv has joined #ocaml
maattdd has quit [Ping timeout: 255 seconds]
Kakadu has quit [Ping timeout: 246 seconds]
rz has quit [Quit: Ex-Chat]
troutwine is now known as troutwine_away
craigglennie has quit [Quit: craigglennie]
<orbitz> whitequark: how hard would it be to implement these ppx things to look like functor applications?
* orbitz will hopefully have time to look at some of your ppx stuff soon
dsheets has quit [Ping timeout: 240 seconds]
AltGr has left #ocaml [#ocaml]
hausdorff has quit [Remote host closed the connection]
hausdorff has joined #ocaml
tautologico has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
jwatzman|work has joined #ocaml
thomasga has quit [Quit: Leaving.]
demonimin has quit [Read error: Connection reset by peer]
demonimin has joined #ocaml
pminten has quit [Remote host closed the connection]
stevej has quit [Quit: ["Textual IRC Client: www.textualapp.com"]]
jonludlam has quit [Read error: Connection reset by peer]
BitPuffin has quit [Ping timeout: 264 seconds]
tidren has joined #ocaml
tidren has quit [Remote host closed the connection]
BitPuffin has joined #ocaml
troutwine_away is now known as troutwine
ollehar has joined #ocaml
_0xAX has joined #ocaml
Hannibal_Smith has joined #ocaml
troutwine is now known as troutwine_away
teiresias has joined #ocaml
BitPuffin has quit [Ping timeout: 255 seconds]
gatorade has quit [Quit: Page closed]
Hetu has joined #ocaml
Kakadu_ has quit [Ping timeout: 246 seconds]
BitPuffin has joined #ocaml
<rwmjones> cduce breaks with a very strange error on 4.02
philtor has joined #ocaml
manizzle has joined #ocaml
<def`> 2
tautologico has joined #ocaml
hausdorff has quit [Remote host closed the connection]
hausdorff has joined #ocaml
Anarchos has joined #ocaml
maattdd has joined #ocaml
Hetu has quit [Ping timeout: 250 seconds]
tac_ has joined #ocaml
troutwine_away is now known as troutwine
hausdorff has quit [Remote host closed the connection]
maattdd has quit [Ping timeout: 245 seconds]
hausdorff has joined #ocaml
relrod has quit [Remote host closed the connection]
philtor has quit [Ping timeout: 240 seconds]
manizzle has quit [Remote host closed the connection]
manizzle has joined #ocaml
troutwine is now known as troutwine_away
thomasga has joined #ocaml
arjunguha has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
oriba has quit [Quit: oriba]
englishm has quit [Remote host closed the connection]
englishm1 has quit [Quit: Leaving.]
morphles has joined #ocaml
Hetu has joined #ocaml
relrod has joined #ocaml
englishm has joined #ocaml
englishm_ has joined #ocaml
Kakadu has joined #ocaml
philtor has joined #ocaml
ewd has quit [Remote host closed the connection]
arjunguha has joined #ocaml
englishm_ has quit [Read error: Connection reset by peer]
englishm has quit [Read error: Connection reset by peer]
pgomes has joined #ocaml
englishm has joined #ocaml
englishm_ has joined #ocaml
Eyyub has joined #ocaml
_0xAX has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 240 seconds]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
philtor has quit [Ping timeout: 245 seconds]
troutwine_away is now known as troutwine
Eyyub has quit [Ping timeout: 256 seconds]
hhugo has quit [Quit: Leaving.]
troutwine is now known as troutwine_away
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
<algoriddle> Who owns the trademark, if anyone?
<Drup> inria
<Drup> (afaik)
<algoriddle> They have to go after them, if they care.
<Drup> I won't bet on inria to do anything for the ocaml community
<Leonidas> also, ocamlpro does afair quite a lot for the community, too
<Drup> (and also, lefessan is technically inria research)
oriba has joined #ocaml
<Drup> (he's just "delegated" to ocaml-pro as scientific consultant)
holomorph has joined #ocaml
arjunguha has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
hausdorff has quit [Remote host closed the connection]
<Drup> but "We own the domain and we want visibility, so we just force you to go through our website" is ridiculous, I understand the reason, but it's not a behavior I find acceptable, even if ocaml-pro is doing good stuff for the community.
<Leonidas> but it is their website, after all
<Drup> what is ?
<Leonidas> ocaml-lang.org
<Leonidas> *domain
<Leonidas> if I own ocaml-sucks.org, I doubt anyone would want me to redirect to ocaml.org ;)
<Drup> I never said they didn't have the *right* to do it, I said I don't find this behavior acceptable from lefessant
<ggole> Bit domain squatty :/
<def`> ggole +1
<Drup> exactly what ggole said.
<Leonidas> a bit, maybe.
<Leonidas> and trademark-wise it is odd, since they even have OCaml in their name.
hhugo has joined #ocaml
englishm_ has quit [Remote host closed the connection]
englishm has quit [Quit: Leaving.]
zpe has joined #ocaml
Thooms has joined #ocaml
Eyyub has joined #ocaml
hausdorff has joined #ocaml
englishm1 has joined #ocaml
englishm_ has joined #ocaml
<Kakadu> Shit
<Kakadu> Second guy can't compile lablqt
<Kakadu> Becuase Qt-developers can't fix pkg-config for Mac
<Kakadu> I will be glad to fix it myself but I do not have Mac at all
zpe has quit [Ping timeout: 240 seconds]
FreeArtMan has quit [Ping timeout: 240 seconds]
hhugo has quit [Quit: Leaving.]
Eyyub has quit [Ping timeout: 245 seconds]
hhugo has joined #ocaml
troutwine_away is now known as troutwine
<whitequark> orbitz: what is the rationale behind making them look like functor applications?
<whitequark> I don't see any reason to do that.
<orbitz> because i want to seperate out what something can be from what it is
tautologico has quit [Quit: Textual IRC Client: www.textualapp.com]
pgomes has quit [Ping timeout: 240 seconds]
troutwine is now known as troutwine_away
zpe has joined #ocaml
mort___ has quit [Quit: Leaving.]
elfring has quit [Quit: Konversation terminated!]
morphles has quit [Ping timeout: 250 seconds]
jprakash has left #ocaml [#ocaml]
<whitequark> orbitz: can you elaborate?
<orbitz> whitequark: Like we discusssed in your protobuf email, I want to generate a module that can generate and consume my type with protobufs, I don't want it to be part of my type defintion
<Drup> orbitz: this issue is that the deriving mecanism is syntactic
<Drup> you *need* the type definition
<Drup> you can't derive anything without it
<companion_cube> can't the ppx retain the type definition in memory ?
tac_ has quit [Quit: Goes to gym]
<companion_cube> because I agree, deriving stuff on foreign types would be nice
<Drup> accross compilation unit ?
<companion_cube> (open types, that is)
<Drup> errr
<Drup> yes, but please do write the infrastructure for it, because I don't want to.
<orbitz> Drup: for protobufs I don't, I just need an interface for the type
<pippijn> whitequark: why did you choose to make ppx_deriving incompatible with the original deriving (which does the module thing)?
<orbitz> for any serializer
shinnya has joined #ocaml
<companion_cube> cough GADT cough
<whitequark> pippijn: original deriving is not widely used, so compatibility is not an issue;
<Drup> huuum
<Drup> it isn't ?
<whitequark> additionally, it has an extension for using the derived types, Show<t> or something, that can't be reproduced without camlp4
<companion_cube> Drup uses it, so it's widely used
<Drup> I don't really use it, actually
<pippijn> whitequark: Show<t> is "short" for Show_t
<Drup> except for eliom-related stuff
<whitequark> pippijn: so I decided to just generate the code that exists on its own in the OCaml ecosystem
* companion_cube coughs more
<Drup> orbitz: by "interface" what do you mean
<Drup> orbitz: be precise, is it a module, what does it contains, is it ppx time, compile time or run time ?
<whitequark> yes, I want ppx_deriving to generate the code at compile-time
<whitequark> traversing GADT descriptions is hardly more useful than just polymorphic compare
<orbitz> consider sig type t val get_x : t -> int val set_x : int -> t -> t end. I want to do module Protobufified = Protobuf.Make(MyThing)
<orbitz> but MyThing is really any interface as long as it as setter's and getter's an some type t
<Drup> but it's far less powerful than a full deriving mechanism.
<whitequark> what? how would you even use that with Protobuf
<Drup> I mean, it's just a simple functor application ...
<orbitz> NO
<orbitz> No*
Hetu has quit [Quit: Verlassend]
<orbitz> I'm saying I want it to look like that
<orbitz> and be semantically like it
<orbitz> but it's actually creating this module by generating code
<Drup> I'm not sure I see the point =__=
<orbitz> because then I acn do module XMLified = XMLifier.Make(MyThing)
<Drup> I mean, if you generate code only using an interface, you're just reinventing functor application
<orbitz> and I can do module JSONified = JSONifier.Make(MyThing)
<whitequark> and what is the point of that?
englishm_ has quit [Remote host closed the connection]
englishm1 has quit [Quit: Leaving.]
<orbitz> Drup: the difference is the actual code is based on the names of the interface elements
mort___ has joined #ocaml
<Drup> is it ?
<orbitz> whitequark: the point would be taht anyone can use my type with wahtever serializer they want without me caring
paddymahoney has quit [Remote host closed the connection]
<orbitz> currently with ppx_protobuf the type defintion is intermingled with the fact that it's going to be serialized via protobuf
englishm has joined #ocaml
<orbitz> i want to decouple these things
<whitequark> then the introspection must happen at runtime
philtor has joined #ocaml
<whitequark> well
<whitequark> how would you add protobuf annotations to fields with your system?
<orbitz> No it musn't
<whitequark> then that's just impossible.
<Drup> orbitz: I think I need an exemple to show me how it's not just functor application.
<whitequark> both syntactically and semantically.
zpe has quit [Remote host closed the connection]
englishm has quit [Remote host closed the connection]
<orbitz> Drup: because functors require a conceret interace
<orbitz> I want to take interface swith names like set_* and get_*
englishm has joined #ocaml
<orbitz> and turn them into code
englishm_ has joined #ocaml
<Drup> but you have one, you have get and set.
<orbitz> Drup: I want to take any module with get_* and set_* and produce protobuf code
<whitequark> orbitz: I don't think you understand what problem deriving solves
<whitequark> because it is not possible to "take any module with get_ and set_ and produce protobuf code"
<orbitz> why isn't it?
<whitequark> this simply doesn't make sense, I'm not aware of any way you could derive protobuf encoding from that
<whitequark> you don't have enough information, and the interface is simply unsuitable
<companion_cube> orbitz: what would "MyThing" look like ?
<Drup> orbitz: so, you are reinveting functor application just to handle the fact that you want get_x instead of get ? this is silly ...
<orbitz> companion_cube: anything with a type t and functions that looke like set_* and get_*
<companion_cube> I don't see what set/get means in this case
<orbitz> Drup: no, I want to look at the module and get all functions taht look like get_* and set_*
<orbitz> companion_cube: just getters and setters on some type
<companion_cube> for instance if I have a type complex={re:float; img:float} ?
<companion_cube> what's getter/setter ?
<orbitz> get_re, set_re
<orbitz> val get_re : t -> float val set_re : float t -> t
<bitbckt> maybe you're referring to something similar to https://github.com/facebook/swift, but uses value names, rather than annotations to generate code?
<companion_cube> orbitz: that wouldn't work for sum types
<Drup> orbitz: this is really a very very minor issue to design such a complex thing
<orbitz> Drup: how so? functors cannot do this, and i want code generated at compile time
<whitequark> orbitz: that wouldn't work for sum types or tuples or polymorphic types or immutable records
<whitequark> or basically the majority of ocaml datatypes
<whitequark> except records with all mutable fields.
<Drup> orbitz: functor can't do this because you are imposing a miningless constraint
<orbitz> bitbckt: not quite, specifically i want to decouple the type i've defined with what it can be serialized with
<Drup> I mean, the only reason is because you want get_t instead of get
* companion_cube goes back to 'a ty
<Drup> this is *silly*
<orbitz> whitequark: why? it returns t on set
<orbitz> Drup: no i don't want get_t
<whitequark> orbitz: what? how would you construct a `complex' value
<whitequark> show this step by step.
<orbitz> sig type t val set_re : .. val get_re : .. val set_img ... val get_img : .. val create : re:float -> img:float -> t end
<whitequark> ok
<whitequark> the short answer is "I don't need that and no code I ever seen needs what you want, so this is not an use case I'm interested in supporting, especially since it is a huge hassle"
<orbitz> right, i didn't ask you to support it, i just asked if you knew how to do it
<whitequark> you're basically adding 1) another layer of indirection 2) requiring the ppx to import Typedtree (module definition from some other place)
<Drup> orbitz: and how do you handle sum types ?
<whitequark> for no real reason whatsoever
<orbitz> Drup: I don't know yet
<whitequark> lol
<Drup> yeah ...
<orbitz> whitequark: it is for a reason: decoupling the type defintion from the serializatoin
<companion_cube> I agree on the part that it would be nice to decouple those
<companion_cube> very nice even
<companion_cube> let the user choose
<orbitz> whitequark: with the current ppx solution, hwat happens if i need to support json too?
<Drup> orbitz: @@deriving Json
<companion_cube> that's a big limitation with Core
<whitequark> you define a type that uses the existing type as manifest
paddymahoney has joined #ocaml
<whitequark> then add @@deriving Json to that
<companion_cube> Drup: you can only do this in your code
<orbitz> whitequark: does that work if it's someone elses type?
<whitequark> yes
<orbitz> how does that look then?
<orbitz> and what if their concrete type is hidden from me?
<orbitz> (I just have a manipulation API)
<bitbckt> I see what you mean, now... *click*
<whitequark> if their concrete type is hidden from you, you don't use *type-driven* code generation
<companion_cube> that means you can't use any library then...
<orbitz> whitequark: then that's fine, i want to use signatuer direven code generation or whatever you want to call it
<companion_cube> whitequark: what do you mean by "use the existing type as manifest"?
<Drup> that means we could benefit for *one standard tool* for the whole ecosystem.
mort___ has quit [Quit: Leaving.]
<Drup> from*
<whitequark> companion_cube: orbitz: let me demonstrate with an example
<companion_cube> no way a library writer will know which deviring to provide
<companion_cube> "oh you wanted json? too bad I derived only xml"
<orbitz> Drup: I'm not sure I'm explaining my goal clearly enough
<orbitz> Drup: whatever the mechanism: I want to decouple what external formats a type can turn into from the defintion of the type
<Drup> orbitz: I think I got the goal right, I disagree completly with the method, however
<orbitz> Something that looks like functor application seems like an obvious starting point
<whitequark> so for example, you have Pervasives.fpclass
<whitequark> and you want to derive Show for it
<Drup> and afa the goal goes
<whitequark> that's what you say, yes?
<orbitz> whitequark: for the simplest case, yes
<Drup> I would prefer a @@deriving companion_cube's GADT serializer thing
<companion_cube> ^^
<Drup> this would be actually correctly designed
<orbitz> Drup, companion_cube what is that?
<Drup> instead of trying to piggy back functor application syntax for something different
<companion_cube> it's a GADT that describes the structure of a type
<orbitz> Drup: like i said, functor application seems a reasonable starting point, but i don't really care waht it looks like as long as it's not intermingling the type defintion with the serialization
<Drup> orbitz: no but the starting point is wrong
<Drup> don't try to fiddle with the application point, fiddle with the starting one
<orbitz> Drup: like i said, i don't really care what it looks like
<orbitz> companion_cube: does it require still knowing the concrete defintion of the type?
jwatzman|work has quit [Quit: jwatzman|work]
<whitequark> M.myfpclass and Pervasives.fpclass are now identical for all intents and purposes
<Drup> whitequark: tbh, it's not optimal to have to rewrite the type ;)
<whitequark> now you may say, "but this requires me to describe the type twice"
<whitequark> psychic powers, etc
<bitbckt> haha
<whitequark> now take a look at e.g. this example: https://github.com/whitequark/ppx_protobuf#integers
<companion_cube> whitequark: tht wouldn't work for private types :/
<whitequark> without rewriting the type, where would you specify all those attributes?
<whitequark> and for the really simplest case I will write another ppx, that imports Typedtree and uses Untypetree to write the plain definition for you
<orbitz> i could specify those attributes on the API functions
<whitequark> orbitz: wat?
<whitequark> no
<whitequark> you would not know what the user would want to derive
<whitequark> as you just said
<orbitz> I know they want an int
<whitequark> so you wouldn't know to define [@protobuf.encoding varint];;
<orbitz> what form that int takes on the wire is up to me
<whitequark> you need to attach attributes to fields or accessors or whatever, invariably
<whitequark> I do not see your syntax allowing that.
<orbitz> if this is about concrete syntax just throw that out of your head
<orbitz> I don't care abou the syntax
<orbitz> I want to be able to write serializers for types I can't see
<orbitz> and don't own
<whitequark> write them by hand.
<whitequark> since you can't see them, type-driven code generation, by definition, doesn't work
<orbitz> I know
<whitequark> if you don't own them, you can use the method I presented above
<whitequark> not sure about private ones...
<Drup> orbitz: and anyway, you don't see/own ... but you still except this "MyThing" to be available ?
<orbitz> I'm arguing there is another option than type-driven code geneation and writing by hand
<nlucaroni> as in, type x = Module.y [@@deriving Json] or something?
<orbitz> Drup: what do you mean?
<Drup> orbitz: the module with the accessors
<orbitz> nlucaroni: no, I want it at the module level
<Drup> You expect it to be available
<whitequark> nlucaroni: type x = Module.y = (original definition with more attributes) [@@deriving Json]
<orbitz> Drup: yes, or at least the underlying type has a featureful enough API that I can write one
<whitequark> there is a standardized interface for types
hhugo has quit [Quit: Leaving.]
<Drup> it's a big assumption.
<whitequark> because ocaml only accepts one particular syntax
<orbitz> Drup: not really, most types are pretty useless otherwise
<whitequark> there is no standardized interface for the serializers that orbitz describes
<orbitz> whitequark: but types are almsot always hidden
<whitequark> and I don't even see an emergent pattern among OCaml projects
<Drup> orbitz: I have enough counterexamples in my mind, but ok.
<whitequark> orbitz: if the type is hidden, it means you shouldn't use type-driven code generation on it
<whitequark> simple as that
<Drup> whitequark: well, there is companion_cube's thingy, but it's slightly too ivory tower (to use your own vocabulary) to be used. (and companion_cube doesn't really advertise it)
<orbitz> whitequark: I know, as I said i'm arguing for somepalce between type deriven and written by hand
<whitequark> I think a ppx_deriving module that generates GADTs for companion_cube's thing may be a good idea
<Drup> yeah
<whitequark> I just have nfc how to write it
<whitequark> can you give me the link again -_-'
<whitequark> I should bookmark that
troutwine_away is now known as troutwine
<Drup> orbitz: my opinion is more on the line "let's convince everyone to use the same type-based deriving library"
axiles has quit [Remote host closed the connection]
<Drup> instead of retropatching library that don't, then, just send them a trivial patch doing the deriving.
<companion_cube> this should be updated to handle sums and records better
<companion_cube> but it could be useful
<whitequark> I think the use case where you want a serializer for someone else's type is a real, but somewhat minor
<whitequark> and the manifest type thing handles it well enough
<bitbckt> I suppose it would be possible if OCaml had mirrors, or some-such reflection system.
<whitequark> I should add it to README
<bitbckt> though that's a whole other ball of wax.
<orbitz> I think doing these things at the type level is mostly wrong, but I don't have a solid alternative suggestion yet
<whitequark> orbitz: I think you want companion_cube's thing
<orbitz> whitequark: Bookmarked, I'll take a peek as soon as I can
<orbitz> thanks
<whitequark> oooh great, Obj.extension_name is in stdlib
<companion_cube> :s
<companion_cube> sounds cthulhu-ic
olauzon has quit [Quit: olauzon]
johnnydiabetic has joined #ocaml
<whitequark> # Obj.extension_name (Not_found);;
<whitequark> - : bytes = "Not_found"
<orbitz> What kind of black magic...
troutwine is now known as troutwine_away
<companion_cube> ôO
<whitequark> Obj is literally magic
ggole has quit [Ping timeout: 264 seconds]
hhugo has joined #ocaml
<bitbckt> huh. and Obj.extension_id, too.
philtor has quit [Ping timeout: 260 seconds]
<orbitz> Time for bed, night everyone!
johnnydiabetic has quit [Ping timeout: 255 seconds]
maattdd has joined #ocaml
Hannibal_Smith has quit [Quit: Sto andando via]
hausdorff has quit [Remote host closed the connection]
hausdorff has joined #ocaml
nlucaroni has left #ocaml [#ocaml]
hausdorff has quit [Ping timeout: 260 seconds]
oriba_ has joined #ocaml
philtor has joined #ocaml
Simn has quit [Quit: Leaving]
oriba has quit [Ping timeout: 260 seconds]
tormaroe has joined #ocaml
hausdorff has joined #ocaml
tautologico has joined #ocaml
tormaroe is now known as tormar
Kakadu has quit [Quit: Konversation terminated!]
englishm_ has quit [Remote host closed the connection]
englishm has quit [Quit: Leaving.]
englishm has joined #ocaml
jao has quit [Ping timeout: 272 seconds]
arjunguha has joined #ocaml
jonludlam has joined #ocaml
zpe has joined #ocaml
englishm has quit [Ping timeout: 240 seconds]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
eikke__ has quit [Ping timeout: 260 seconds]
eikke__ has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
maattdd has quit [Ping timeout: 272 seconds]
arjunguha has quit [Quit: Textual IRC Client: www.textualapp.com]
BitPuffin has quit [Ping timeout: 260 seconds]
eikke__ has quit [Ping timeout: 255 seconds]
troutwine_away is now known as troutwine
eikke__ has joined #ocaml
philtor has quit [Ping timeout: 240 seconds]
hausdorff has quit [Remote host closed the connection]
jwatzman|work has joined #ocaml
nojb has joined #ocaml
ollehar has quit [Ping timeout: 250 seconds]
hausdorff has joined #ocaml
<companion_cube> whitequark: are you sure Eq is similar to (==) and not (=) ?
<whitequark> (=) of course
<whitequark> ugh
<companion_cube> you should fix you readme
<companion_cube> aww, looks like deriving Ord doesn't make the type an instance of OrderedType
FreeArtMan has joined #ocaml
<companion_cube> becuase it's compare_foo and not just compare
hausdorff has quit [Remote host closed the connection]
<Drup> companion_cube: { suffix = "" }
<Drup> (until whitequark implemented the clever heuristic)
<nojb> I am trying to make Graphics_js.open_graph work with no success. I get a javascript error: "Graphics.open_graph: cannot open the window" Any ideas?
<whitequark> Drup: that doesn't work yet though
<Drup> nojb: the whole code ?
<Drup> whitequark: oh :D
<whitequark> Drup: for reasons which will be clear later
<companion_cube> my true concern is more that you'll have to tell explicitely that Foo.t is compared using Foo.compare
<nojb> test.ml: let _ = Graphics_js.open_graph " "
<whitequark> tomorrow I guess
troutwine is now known as troutwine_away
<nojb> compile with js_of_ocaml +graphics.js test.ml
<nojb> get test.js
<nojb> index.html: <html><head><script type="test/javascript" src="test.js"></script></head><body></body></html>
<Drup> nojb: ok, the documentation is not clear enough : don't do it like that.
<Drup> create an empty canvas in your index.html and use Graphic_js.open_canvas
<companion_cube> to quote Drup: "that's only 3 lines of code"
<nojb> Drup: ok, thanks - do I have to call open_graph at all ?
<whitequark> Drup: basically I want to implement Arg
<whitequark> and I sorta want to make the argument descriptions using GADT
<Drup> nojb: no.
<whitequark> but I feel like I will immediately regret that decision
<nojb> Drup: thanks, will try it
<Drup> whitequark: :D
<companion_cube> whitequark: for this, cmdliner looks really standard in OCaml
<whitequark> I loathe cmdliner's interface
<companion_cube> please focus your energy on more useful things! :D
<whitequark> well
<whitequark> maybe you have a point
<Drup> (and coming from him ... :D)
<Drup> whitequark: you don't like applicative functors ? :)
* companion_cube threatens Drup with a build system quadrarotaphilisation
<whitequark> Drup: hm?
<whitequark> I don't understand
<whitequark> ok you know what, nevermind, I almost haven't slept for almost 34 hours
<whitequark> that is likely the reason
<Drup> Cmdliner.t is an applicative functor
<Drup> (hence the "pure" and "lift" functions)
<Armael> you don't need to know any of that to use cmdliner
<Armael> actually
<Drup> let's say it helps, if you want to describe complex things
<Drup> just like knowing Lwt.t is a monad helps a bit
<flux> but is it, though
<Drup> (and by "knowing it's a monad" I mean "knowing the various idioms associated with the fact that it's a monad" :p)
<flux> if you have a value of type Lwt.t and use >> on it twice, it may behave strangely, iirc?
<flux> not sure though if the 'monad laws' have something to say on that
<flux> (but now some sleep ->)
<Drup> hum, non ?
<Drup> no*
<Drup> (not afaik, at least)
agarwal1975 has quit [Quit: agarwal1975]
englishm has joined #ocaml
englishm_ has joined #ocaml
Thooms has quit [Ping timeout: 245 seconds]
FreeArtMan has quit [Remote host closed the connection]
Eyyub has joined #ocaml
darkf has joined #ocaml
<nojb> ok, more problems with Graphics_js:
<nojb> I have the following files:
<nojb> test.ml:
<nojb> let _ =
<nojb> let d = Dom_html.window ## document in
<nojb> let c = Dom_html.createCanvas d in
<nojb> c ## width <- 100;
<nojb> c ## height <- 100;
<nojb> Graphics_js.open_canvas c;
<nojb> Graphics_js.lineto 100 100
<nojb>
<nojb> compiled into test.js with js_of_ocaml +graphics.js test.byte
<nojb> index.html:
<nojb> <!DOCTYPE html>
<nojb> <html lang="en">
<nojb> <head>
<nojb> <script type="text/javascript" src="test.js"></script>
<nojb> </head>
<nojb> <body>
<nojb> <noscript>Sorry, you need to enable JavaScript to see this page.</noscript>
<nojb> </body>
<nojb> </html>
<nojb>
<nojb> but I do not see anything when I load index.html in my browser ...
<nojb> (and no javascript errors either)
hausdorff has joined #ocaml
<Drup> you didn't inserted the canvas in your document.
<nojb> aha - how do I do that ?
<nojb> Ah wait, with Dom.appendChild, yes ?
<Drup> from memory, something like "Dom.appendChidl (d ## body) my_node"
<nojb> yeah, that must be it - thanks again !
<Drup> but, in your place, I would just put the canvas directly in the html, give it an id, and access it using getElementById
<nojb> I tried that , but I am not sure how to coerce the resulting element into a canvasElement...
<Drup> Js.coerce
<nojb> oh
<nojb> thanks - I'll try it out
tautologico has quit [Quit: Textual IRC Client: www.textualapp.com]
<nojb> Drup: sorry for the nagging, but after putting the appendChild call in there I get a javascript error: "'null' is not an object (evaluating bT.body.appendChild)" ... do you know why this happens ?
<Drup> put your script at the end of the file
<nojb> brilliant! it worked!
<nojb> thanks!
philtor has joined #ocaml
englishm1 has joined #ocaml
english__ has joined #ocaml
agarwal1975 has joined #ocaml
philtor has quit [Ping timeout: 250 seconds]
troutwine_away is now known as troutwine
englishm_ has quit [Ping timeout: 264 seconds]
englishm has quit [Ping timeout: 272 seconds]
philtor has joined #ocaml
tautologico has joined #ocaml
troutwine is now known as troutwine_away
hausdorff has quit [Remote host closed the connection]
tormar has quit [Ping timeout: 250 seconds]
hausdorff has joined #ocaml
mort___ has joined #ocaml
<hhugo> nojb: Graphics_js.open_graph should work but you might need to way the document to be ready.
<hhugo> Html.window##onload <- Html.handler (fun _ -> let _ = Graphics_js.open_graph ""; Js._false)
<Drup> hhugo: what does it do ? create a canvas and put it somewhere in the body ?
BitPuffin has joined #ocaml
madroach has quit [Ping timeout: 250 seconds]
jonludlam has quit [Remote host closed the connection]
mlaine has joined #ocaml
hausdorff has quit [Remote host closed the connection]
madroach has joined #ocaml
holomorph has left #ocaml [#ocaml]
mlaine has left #ocaml [#ocaml]
hausdorff has joined #ocaml
philtor has quit [Ping timeout: 240 seconds]
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
hausdorff has quit [Remote host closed the connection]
jwatzman|work has quit [Remote host closed the connection]
<hhugo> it opens a new window with window.open( … )
jwatzman|work has joined #ocaml
hausdorff has joined #ocaml
<hhugo> and insert a new canvas
parcs has quit [Remote host closed the connection]
<Drup> ok
parcs has joined #ocaml
philtor has joined #ocaml
dsturnbull has left #ocaml [#ocaml]
tobiasBora has quit [Quit: Konversation terminated!]