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/
n0v has quit [Read error: Connection reset by peer]
n0v has joined #ocaml
ollehar has quit [Ping timeout: 252 seconds]
<flux> drup, but easy to reimplement. let my_raise x = raise x ;)
<whitequark> you could conceivably say that you want all code be in CPS, then you can "implement" raise
<whitequark> with the same signature, even
<mrvn> but then you need to pass an exception continuation too
<whitequark> type ('a, 'b) cont = ('a -> 'b, exn -> 'b)
<whitequark> er
<whitequark> type ('a, 'b) cont = ('a -> 'b * exn -> 'b)
<whitequark> or something like this.
<mrvn> whitequark: now you only need to (re)implement the exn type
<whitequark> mrvn: soon that will be possible :p
<whitequark> when open-types is merged
<whitequark> mrvn: could you help me out with libzmq? I want to implement the missing parts for getting the pubkey of other party, but you seem to know the best way to structure it already
<mrvn> only in theory. Haven't had time to figure out how the code actualy looks like
<mrvn> n8
<flux> whitequark, cool, so ocaml finally gets dynamic typing?-)
<Drup> no
<whitequark> flux: no, ocaml gets extensible variants
<whitequark> like exn
<whitequark> the concept of open-types seems to be extremely confusing for some reason
<Drup> :)
<flux> right, and exn is pretty much a dynamic type. you write code that deal with exn, and you cannot possibly know what values it may have.
squiggnet_ has joined #ocaml
<_obad_> so wait... would there be a mechanism to extend an existing function's definition when you extend an open type?
squiggnet has quit [Quit: ZNC - http://znc.in]
<whitequark> no
squiggnet_ is now known as squiggnet
<_obad_> so what cool things can one do with this?
<Drup> mostly, implement custom weird exceptions
<_obad_> the benefit seems marginal?
<Drup> except when you need it :)
<whitequark> Drup: that would be useful for my SSA IR, back when I needed it
<whitequark> make it a module and define custom instructions elsewhere
<Drup> won't you solve that better with polymorphic variants ?
<mrvn> Drup: polymorphic variants have no namespace
<mfp> Drup: did you find a solution to the let%lwt + eyes bleeding issue?
zzing has joined #ocaml
<Drup> mfp: what is the eyes bleeding issue ? :D
<mrvn> _obad_: a few days ago there was a nice example of extending GADTs with open types to make an universal type equality.
<mfp> the hypothesized effect of repeated let%lwt on ...
<mrvn> _obad_: helpfull for universal containers
squiggnet has quit [Quit: ZNC - http://znc.in]
<_obad_> mrvn: can't you implement that with references and anonymous thunks though?
<Drup> mfp: let%lwt is probably going to stay that way
<Drup> mfp: you will get used to it ;)
<mfp> I seem to remember there was a let! proposal in mantis?
<Drup> the ! semantic is different in ocaml, so not sure if it's gonna be accepted as it
<_obad_> wasn't there some proposal for something like: begin%lwt v1 <-- expr1; v2 <-- expr2; v3 <--- expr3 end%lwt
<mfp> ooh
<Drup> _obad_ that's different
studybot_ has quit [Read error: Connection reset by peer]
<Drup> I expect to have a different library with a do notation
<Drup> (or computational expressions, as F# call them)
* mfp meanwhile reading on :he conceal
<Drup> so we can have something like begin%monad(Lwt) ... end
<_obad_> and what would ... look like
<Drup> probably this <--
<whitequark> Drup: uhhh, let's not have begin%monad(Lwt)
<whitequark> it's horrendously verbose
<_obad_> whitequark: I agree about %monad(...) being fugly
<Drup> whitequark: do you have other propositions ?
<whitequark> let%lwt as usual?
<Drup> whitequark: orthogonal
<Drup> I'm talking about a general do notation library for monads
<whitequark> begin%lwt would perform sequencing
<whitequark> ok
<_obad_> can't we have some kind of annotation to define shorthands
<whitequark> not interested in it, I guess
<_obad_> I don't remember the syntax but [@@lwt=monad(lwt)] and then you can go begin%lwt ... end
<_obad_> or [@@myCustomMonad=monad(lwt,option=blah)] ... begin%myCustomMonad ... end%myCustomMonad
squiggnet_ has joined #ocaml
<_obad_> in other words you put one annotation to configure the syntax extension for the remainder of the file
<Drup> probably not this way, but yes, it should be doable
squiggnet_ is now known as squiggnet
<Drup> (not this way, because you need something that indicate the extension after the @@ ;))
<Drup> (and it would probably be a % anyway
<_obad_> cool. so we could have something like @@...t=lwt... and then let%t = x in let%t = y in ... as I was suggesting yesterday
<mfp> what's the plan for ppx vs camlp4? is the former supposed to replace the latter quickly, or will they coexist (can they on the same source?)
<Drup> mfp: they can exist on the same source, and they are probably going to coexist
<Drup> except that camlp4 is not in the compiler anymore
<mfp> ic
<Drup> _obad_ no, this [@@foo=bar] is not a default stuff, it's something the library need to understand
<Drup> and it's not going to be in lwt's ppx
<Drup> and tbh, for code readability, it's terrible.
<whitequark> [@@foo=bar] is not even syntax that is accepted
<whitequark> you need an expression or item
<whitequark> not =bar
<Drup> ( [@@extend foo=bar] )
<_obad_> so wait is there syntax for annotations that is accepted?
<_obad_> I didn't mean to suggest exact syntax btw
<mfp> _obad_: I was half joking above, but if it's a purely cosmetic issue the solution might indeed be in the editor
<Drup> _obad_ everything that is parsable is accepted, but nothing is supported by default.
<Drup> ppx is pure syntax, it's up to the ppx rewrite to do something with it
<Drup> mfp: I consider your solution saner =)
<_obad_> ok but you need to modify the front-end parser to support attributes and present them to the extension in the standard ast
Rotacidni has joined #ocaml
<_obad_> I thought that was accepted
<Drup> _obad_ yes, it's in trunk
<_obad_> K I'll check it out before making further stupid comments :)
<whitequark> does camlp4 even know how to forward the attributes?
dapz has joined #ocaml
<HoloIRCUser2> Drup: why can't attribute payloads be as arbitrary strings?
<whitequark> they can: [@@foo "bar"]
HoloIRCUser2 is now known as _obad_andro
<Drup> there is too many _obad_s in this channel
<Drup> it's like gremlins, after midnight, they start to multiply them-self.
<Drup> it's design to write syntax extensions for ocaml, not arbitrary DSLs
<Drup> (campl4 is intended for that)
<_obad_andro> I'm sorry for the bother. Xmpp doesn't have that problem though.
<Drup> use a bouncer =)
araujo has quit [Ping timeout: 255 seconds]
<_obad_andro> How about [@@@monad Lwt.def = "X"] then let℅X = ...
divyanshu has joined #ocaml
<Drup> I would use [% ... ] for that
<whitequark> what's up with this odd obsession to lose two characters?
<whitequark> in exchange for forcing everyone else to think harder to understand your code
<_obad_andro> And monad would be a generic extension that would work with Lwt or Fut or whatever, pro used it follows some conventions
tlockney_away is now known as tlockney
<_obad_andro> whitequark: it's two characters but on a very frequent construct.
<Drup> is it ?
<Drup> I mean, I use it, but not all that much
<whitequark> shorten let to l, fun to f
<whitequark> also probably should add a bunch of operators like APL
* whitequark shrugs
<Drup> and anyway
<_obad_andro> Yeah if you use lwt... You bind all the time.
<Drup> I use combinators more
<Drup> I don't know about you, but I don't write lots of code, I spend more time reading it. and typing speed is clearly not my limitating factor.
<Drup> if typing speed is so much a limitating factor, you must think really really fast :O
<_obad_andro> Drup: well it's a free country ain't it...
<_obad_andro> It affects reading speed as well. I use a strict 80 column limit for example.
<whitequark> *facepalm*
<Drup> yes it does, %t is slower for anyone else but you because they are not used to it :D
<Drup> (and for you, it's the same in fact, because the brain doesn't work by linear scan, so it doesn't matter)
<_obad_andro> Come on, five letters is not the same as seven. Plus, it's good
tautologico has quit [Quit: Connection closed for inactivity]
studybot_ has joined #ocaml
<_obad_andro> practice to have extensions that use a user configurable % suffix.
<_obad_andro> What if i want to use two versions of lwt in the same module?
<Drup> two versions of lwt ?!
<_obad_andro> Drup: point is, extensions should allow the user to override their suffix through floating annotations to permit the use to use shorthands if they so desire. Don't you ever use module abbreviations?
<Drup> _obad_ you're free to defined a ppx for that, and be careful to apply it before other ppxs
<Drup> -d
<Drup> I'm certainly not going to include that in lwt's ppx, and I'm certainly not going to be the only one with this opinion
<_obad_andro> Hmm that's an idea... [@@@ppxsubst "t"="lwt]
<whitequark> let's just stop discussing it already
<Drup> whitequark: :D
<whitequark> I can't think of a less productive way to spend time
<Drup> whitequark: try to imagine a more obvious operator than >> to make it clear it's a syntax extension :)
<whitequark> Drup: I already think we should do sequencing with begin%lwt and bury >>
<Drup> not a bad idea
<_obad_andro> these seemingly trivial things do have an impact on user acceptance though. some of us are trying to promote ocaml usage in the industry.
<whitequark> they do not. industry happily uses Java
<_obad_andro> that's overgeneralizing a bit
<Drup> whitequark: I will finish the easy part and will do a pull request so that we can have a discussion with the maintainers about the complicated parts ;)
<whitequark> Drup: agreed
nikki93 has quit [Remote host closed the connection]
<Drup> whitequark: If you are interested, I already opened a ticket to discuss js_of_ocaml's and eliom's ppxs
<whitequark> where?
<whitequark> oh, 12 days ago
<whitequark> Alain's suggestion sounds great
<whitequark> while you could say it's ad-hoc, but so is the entire ppx concept. it literally exists for defining syntax ad-hoc to regular one
<Drup> I agree
<Drup> in my opinion, we should forbit % as an operator and allow to attach it everywhere
<whitequark> you could say that Lisp's syntax is the extreme variant of this relaxation
<Drup> forbid*
<whitequark> hmm, that's backwards-compat breaking
<Drup> yeah, that's why it's not going to happen
<Drup> but it would be nice
tobiasBora has quit [Quit: Konversation terminated!]
q66 has quit [Quit: Leaving]
<Drup> well, I don't know about nice, but it would be "the right thing to do"™ :)
vladsot has joined #ocaml
nikki93 has joined #ocaml
<_obad_2_> jesus reading those tickets it appears that there is going to be a profusion of ppx extensions. that's going to cause clashes and build problems. I think a set of conventions should be defined so that syntax extensions can coexist peacefully.
<whitequark> that is the whole idea behind ppx. camlp4 extensions aren't capable of coexisting
<Drup> the syntax defined in those tickets are compatible
<Drup> what is the issue ?
<_obad_2_> what about name clashes?
<_obad_2_> also, is there a rule that says that syntax extensions should not touch undecorated nodes?
<_obad_2_> there will be order and activation issues I think.
<Drup> ppx can touch everything :)
<Drup> and yes, ppx are not commutative
<_obad_2_> see... and then you would have to be able to specify, for each file, which ppx extensions and their order.
<Drup> but they are composables
<_obad_2_> ocamlbuild tags are not ordered though
<_obad_2_> so there needs to be an agreed-upon convention for activating, deactivating and specifying the order of extensions using e.g. floating annotations. maybe a meta-extension?
<whitequark> I guess ocamlbuild will have to be fixed
<_obad_2_> that would be on a per-file basis. so in your whole project you could activate the smallest set containing all your needed extensions, and then override them ona per-file basis.
rgrinberg has quit [Quit: Leaving.]
<whitequark> it's not an issue with ocaml compiler; ocamlc allows you to define order perfectly well
<_obad_2_> and you could have some renaming annotations.
<whitequark> it's a buildsystem issue.
<whitequark> what you suggest is too complex and fragile.
<_obad_2_> yes but build systems do matter... software is too complex these days to be buildable with simple invocations to ocamlc/ocamlopt
<whitequark> as I've said: build systems will have to be fixed.
rgrinberg has joined #ocaml
<_obad_2_> what's wrong with a standard set of annotations to define syntax extensions in source files?
<_obad_2_> that way the semantics would be more explicit and not depend on out-of band tags / makefiles / oasis flags / whatever
<Drup> it's not idiomatic in ocaml to have pragmas
vladsot has left #ocaml []
<_obad_2_> it's not idiomatic to have %extension points
<Drup> well, it is now.
<_obad_2_> I tell you that shit's gonna explode in our faces
<Drup> if you want to design a new build system like ocamlbuild but using pragmas .. go on.
<_obad_2_> no I don't want to touch the build systems
<_obad_2_> what I want is to define standard annotations that well-behaved syntax extensions will read to re-configure themselves
<_obad_2_> I mean [@@@floating "annotations"]
<Drup> "well-behaved syntax extensions"
<Drup> totally prevent stuff to explode.
<_obad_2_> just like well-behaved software packages... ./configure && make && sudo make install
<whitequark> hahaha
<whitequark> you clearly have never tried to actually maintain a distribution
<Drup> I don't find the mantis ticket for "let!"
<_obad_2_> ok how about this. rule (1) a well-behaved syntax extension (WBX) SHALL read and obey floating annotations of the form [@@@well-behaved ...] ; rule (2) if a @@@well-behaved annotation exists, then the WBX SHALL NOT do anything unless it is activated from the well-behaved annotation
fraggle_ has quit [Read error: Connection reset by peer]
<Drup> are you in a W3C committee ? :)
<whitequark> clearly some kind of committee
<_obad_2_> no, SHOULD I apply to be in one?
<Drup> I haven't told you the worse, in fact
<Drup> ppx are executables.
<Drup> I mean, full blown executables that can do anything.
<_obad_2_> yeah... they could launch sensible-browser and fetch an XML schema
<Drup> or rm -rf your home.
<whitequark> I was thinking "do rm / -rf", but this is considerably worse
<_obad_2_> hmm... looks like ocamlc only accepts one -ppx
<whitequark> sounds like a bug
<whitequark> are you trying it on 4.02.0dev+trunk?
<_obad_2_> and shouldn't -ppx cat work?
<_obad_2_> 4.01.0
<_obad_2_> debian 4.01.0-3
<whitequark> try dev+trunk.
<_obad_2_> is the github mirror ok?
<_obad_2_> I mean... is it up-to-date for that purpose
<whitequark> opam switch 4.02.0dev+trunk
<Drup> yes, the github mirror is ok
<_obad_2_> whitequark: thanks :) getting used to all that opam goodness
<_obad_2_> back in my days we had to write a letter to inria to get a copy. and then we would write another letter to the FSF to get a copy of gcc.
<Drup> your days are before my birth :p
<_obad_2_> just joking I would just download the tarball over my 38400 baud link
<_obad_2_> multiple -ppx args accepted by 4.02.0+dev4-2014-04-03
<whitequark> is there a less horrible way to get an int64 from its binary serialization than to pluck out bytes from a string one by one?
<Drup> ooh
<Drup> () is a constructor
<Drup> (I couldn't find it in the constant category, I was confused)
<whitequark> hm, extlib plucks
<whitequark> I guess I could always make a cext if I really need it
<Drup> "type foo = ()" <- it works :D
<whitequark> um, yeah?
<whitequark> # type foo = () | true | false;;
<whitequark> type foo = () | true | false
<whitequark> # true;;
<whitequark> - : foo = true
<Drup> I knew about true and false already
<Drup> you can do magic stuff
<_obad_2_> I was expecting the -ppx argument to be a unix-style filter, but it's given input and output temporary file names.
<_obad_2_> all that shit because of windows.
<Drup> weren't you talking about converting industrial users previously ?
<Drup> :]
<whitequark> whoa, type x = true of int;; works
<_obad_2_> also trying to convert those to swich to linux :)
<Drup> whitequark: even better
<whitequark> lol
<Drup> whitequark: "type foo = true of bool"
<Drup> then "true true"
<whitequark> Drup: won't work
<Drup> and behold, magic
<whitequark> true false, however...
<Drup> try it.
<whitequark> wtf
<Drup> (also know as constructor disambiguation)
<whitequark> this is confusing
<Drup> (example by nicoo)
<_obad_2_> ocamlc -ppx 'sensible-browser http://www.w3.org/1999/xhtml;cp' foo.ml
<Drup> poor foo.ml
divyanshu has quit [Quit: Textual IRC Client: www.textualapp.com]
* whitequark feels dirty
<Drup> whitequark: define "i" as of_int" and + and <<<
<Drup> it may not be a lot more clean philosophically, but at least it's going to be visually clean
<_obad_2_> is there a compiler-libs in opam?
<_obad_2_> trying to compile frisch's example
<Drup> _obad_ it's distributed with the compiler
<_obad_2_> find ~/.opam -name ast_mapper.cmo didn't return squat though
<_obad_2_> is it in a library
<whitequark> Drup: no, I actually like the ladder pattern
<whitequark> it's the allocation I see behind it that bothers me so much
<_obad_2_> got it -I +compiler-libs
<whitequark> like, it's... 22 dword allocations per a *single int64 value*
<Drup> whitequark: huum, maybe not
<Drup> whitequark: check the asm
<whitequark> _obad_2_: -package compiler-libs.common
<_obad_2_> whitequark: yeah opam hadn't installed ocamlfind after I switched
araujo has joined #ocaml
araujo has quit [Changing host]
araujo has joined #ocaml
<Drup> whitequark: but I've seen some stuff on trunk to reduce allocations in this kind of arit expressions
<Drup> whitequark: oh, btw, look at last day commit log in trunk, you will like it
<whitequark> what the *hell* does it do
<whitequark> well, yes, it eliminates the allocations
<Drup> don't ask me, I'm completely unable to read asm :D
<whitequark> it's -dlinear
<Drup> no, I mean, mentally unable
<Drup> x)
<whitequark> oh cool, some optimizations
<Drup> (at least real world asm)
<Drup> (I can cope with idealize cute asm)
<whitequark> it may be the right thing to do after all
<_obad_2_> whitequark: why don't use a big (string, int64) hashtable with all values?
<whitequark> oh, even constant propagation
<whitequark> _obad_2_: are you joking?
<_obad_2_> whitequark: what do you think? ;)
<Drup> whitequark: so, what was the "hell" for ?
<whitequark> that should have been... three instructions at most
<whitequark> instead I see the compiler masturbating
<whitequark> LLVM's instcombine *excels* at removing this weird kind of crap
<whitequark> well, doesn't matter, I could easily enough make it generate better code if I ever want
<whitequark> no structural changes needed
<Drup> huh ?
<whitequark> do you see all the shifts?
<whitequark> what is needed is one left shift and one logical or
<Drup> huum, ok
<whitequark> it appears to be clearing the high half of the register for some reason
<whitequark> which is beyond me
<whitequark> but at least the alloc is dead, that would be the hard part
<_obad_2_> Drup: cloned master from https://github.com/ocaml/ocaml.git but compilerlibs/ is empty; what branch should I use?
<Drup> trunk
<whitequark> Drup: the code is decent except for that, actually; I would've expected worse
<Drup> whitequark: the compiler usually do the obvious stuff you expect from him. just no magic :)
<_obad_2_> well I'm already on trunk actually, at 89441430c5c92f651f379ce59b60ce00b8fb0ff0 apr. 26 and compilerlibs/ is empty... :(
<whitequark> well, translating a left shift into a single left shift is no magic
<whitequark> _obad_2_: yes, compile it.
<_obad_2_> whitequark: oh ok it's under parsing. sorry. I was looking for the mli since alain's example doesn't compile
<whitequark> it has an example which is written for trunk
<_obad_2_> thanks!!
maurer has quit [Read error: Operation timed out]
maurer has joined #ocaml
ThatTreeOverTher has joined #ocaml
<ThatTreeOverTher> Hi guys, I'm having issues with loading the LLVM library in OCaml: http://pastebin.ca/raw/2705720
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<whitequark> ThatTreeOverTher: where did you get LLVM?
<Drup> whitequark: error position in ppx is a tricky thing.
<ThatTreeOverTher> whitequark, LLVM or the bindings?
<whitequark> ThatTreeOverTher: they come from the same place
<ThatTreeOverTher> LLVM came from Arch Linux's pacman
<ThatTreeOverTher> I installed llvm-ocaml from OPAM then pacman
<whitequark> hrm... hard to say without looking closer. what version is it?
<ThatTreeOverTher> "llvm-ocaml-3.4-1"
<whitequark> also, since LLVM tends to assert when it doesn't like something, using it from toplevel is not a good idea. it's too easy to lose all your work
<ThatTreeOverTher> I wish I knew what that meant :)
<whitequark> what do you not understand?
<ThatTreeOverTher> what does "using it from toplevel" mean and why do "asserts" affect my work when I do so?
<whitequark> using it from toplevel means using it from the interactive ocaml interpreter
<whitequark> i.e. the ocaml command, or utop
<ThatTreeOverTher> ah, I'm using ocaml-top, the editor with an embedded interpeter
<whitequark> "asserts" means that LLVM checks internal consistency all the time and if you pass the wrong arguments, it will abort the entire process
<whitequark> without warning
<whitequark> so you better use it in batch mode
dapz has joined #ocaml
<ThatTreeOverTher> what does "batch mode" mean? and I'm using an editor with an embedded interpreter, I won't lose my work
<whitequark> you probably will lose all unsaved changes
<whitequark> batch mode means that you should just save the source to a file and run it
dapz has quit [Client Quit]
<ThatTreeOverTher> ignoring my choice of editor for a moment, do you know why I'm getting this error?
dapz has joined #ocaml
<whitequark> because the bindings you built have toplevel support broken
<whitequark> it's a bug in the LLVM buildsystem. I *think* I have fixed it. perhaps something else broke it again, or perhaps my fix was wrong
<ThatTreeOverTher> so what can I do about this?
<whitequark> nothing really
<ThatTreeOverTher> meaning it's impossible for me to run any OCaml code that creates LLVM bytecode?
<whitequark> no, it's impossible to run it from toplevel
<ThatTreeOverTher> so what can I do to run OCaml code that creates LLVM bytecode?
<whitequark> I've already told you. save your code to a file, compile that file and run the result.
<Drup> ThatTreeOverTher: "ocamlbuild -use-ocamlfind -package llvm foo.native" with foo your main module
<Drup> (add the other relevant packages, of course)
<ThatTreeOverTher> Drup, unfortunately I'm getting a Syntax error
<ThatTreeOverTher> on line 8, characters 0-2
<Drup> yes, remove the # pragmas
<whitequark> ThatTreeOverTher: fyi: I've checked the archlinux package and it appears that LLVM is built in a way that permits to use it from toplevel
<whitequark> report a bug against llvm-ocaml in archlinux, I guess
<_obad_2_> https://gist.github.com/berke/11337168 first attempt at using annotations to control ppxes
<Drup> please; use %%
<Drup> @@@ is not intended for that
<ThatTreeOverTher> Drup, I removed the # pragma on the first line and I still have a syntax error
<_obad_2_> drup: you talking to me?
<Drup> yes
<ThatTreeOverTher> Drup, never mind
<_obad_2_> drup: where is the syntax for %%% described?
<ThatTreeOverTher> Drup, whitequark: thanks, batch mode without pragmas works perfectly
<whitequark> awesome
<Drup> _obad_ I said "%%"
<_obad_2_> oh my bad
<_obad_2_> Fatal error: exception File "parsing/pprintast.ml", line 1139, characters 26-32: Assertion failed
<Drup> :D
<_obad_2_> | Pstr_extension _ -> assert false
<_obad_2_> someone was lazy?
<whitequark> or you are creating invalid AST
<_obad_2_> I'm returning it wholesale
<_obad_2_> oh wait
<_obad_2_> no it also fails with cp;
<whitequark> what is the source?
<_obad_2_> it's in the comment
<_obad_2_> replace @@@ with %%
<whitequark> oh, nevermind, it's easy. extensions are supposed to remove all %nodes
<whitequark> so there's no printer for them
<Drup> whitequark: it shouldn't raise an assert failed, though
<_obad_2_> that's not very friendly...
<_obad_2_> I mean, if I invoke -dsource it should still work
<Drup> the error message is sensible
<whitequark> well, ideally it would just print
<_obad_2_> yeah
<Drup> ("Unknown extension node")
<whitequark> no, just print it back
<whitequark> it's for -dsource
jao has quit [Ping timeout: 265 seconds]
<_obad_2_> and anyway it does print [@@@] attributes
zzing has left #ocaml []
<_obad_2_> actually for what I wanna do I need to use [@@]; I want something that all extensions can look at.
<_obad_2_> so I'm proposing [@@ppx ext_1;ext_2;...;ext_n] at the beginning to explicitly enable extensions, where ext_i is [<id> "="] <id> <arg1> ... <argn>
<Drup> there is a mailing list, go on :)
<_obad_2_> example: [@@ppx getenv; t = monad Lwt; ifdef "IFDEF"]
tautologico has joined #ocaml
<_obad_2_> meaning: enable extension getenv; extension monad with argument Lwt, aliased as "t"; extension ifdef with argument "IFDEF"
<_obad_2_> if a [@@ppx] node appears, all extensions that do not appear explicitly must be disabled
<whitequark> extensions already accept arguments at command line.
<whitequark> and you cannot reorder them with your thing anyway
<_obad_2_> the whole point is to allow per-file configuration without having to dick around in build stuff
<_obad_2_> build systems = nightmare
<_obad_2_> with this approach, just make sure all used extensions are in the chain, then configure them per file.
<_obad_2_> the reordering thing is true...
<tautologico> you're thinking all that so that you can type let%t instead of let%lwt ? :)
<_obad_2_> looks like this might end up as a meta-extension after all
<whitequark> so you didn't solve any existing problem, but want to impose a standard on all extension authors *and* users.
<_obad_2_> no I'm thinking ahead
<whitequark> can't wait to use this.</sarcasm>
<_obad_2_> assume you're using lib1 and lib2, each using their own extensions
<_obad_2_> you bring them together into a common source tree
<whitequark> each will have their nodes prefixed by library name
<_obad_2_> now you have to adjust build flags on a per-file basis
<whitequark> that is all.
<_obad_2_> that assumes they only work on nodes having attributes
<_obad_2_> they are free to do other things...
<whitequark> well, they shouldn't.
<tautologico> yeah
<_obad_2_> well fact is they will end up doing stuff. people will just use it.
<tautologico> if extensions start to mess around with unadorned AST nodes, then all hope is lost
<Drup> tautologico: that's going to happpen if you want to keep a lightweitgh syntax
<whitequark> excellent. if people will realize that this doesn't work, they will complain to extension author, and the extension will be fixed or abandoned.
<Drup> cf the two links for eliom and js_of_ocaml I gave earlier
<tautologico> Drup: I didn't see them
<_obad_2_> the invisible hand of the free software marketplace?
<whitequark> you could put it so
<tautologico> I prefer to have lightweight syntax for my extensions, but I also have to consider that my users will want to use my extension with other extensions
<whitequark> absolutely nothing stops the extension authors from ignoring your protocol either.
<_obad_2_> whitequark: true
<_obad_2_> but that's like saying : nothing prevents people from buying products without CE / UL labels
<_obad_2_> so there is no point in having those standards
<whitequark> there actually is
<whitequark> products without certification can't be sold
<_obad_2_> not true for UL I think
<whitequark> I don't think I've ever heard of anyone not buying product X because it doesn't have an UL label
<whitequark> I don't think most people even *know* what it means
<_obad_2_> ok fine but there are other labels and other contexts.
philtor has quit [Remote host closed the connection]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
<ThatTreeOverTher> whitequark, I'm not quite understanding what's wrong here http://pastebin.ca/raw/2705741
<whitequark> 1) use define_function 2) use builder_at_end context (entry_block addfunc)
<ThatTreeOverTher> whitequark, I'm still getting an error after making those changes: http://pastebin.ca/raw/2705744
<whitequark> ThatTreeOverTher: it is a trivial error. I will suggest finding it yourself, as you probably don't want to ask the channel each time you get one.
<ThatTreeOverTher> whitequark, I'm learning the language, and I need help. I'll need less help after I've come to understand a little more, but as of now this channel is my only lifeline. I don't quite get it, as I'm providing build_add with the two llvalues that are i32_type, the name of the value, and the builder, but it says I apply the function to too many arguments still.
<whitequark> you forgot ;
<whitequark> at the end of the line with build_add
<ThatTreeOverTher> why would I need a semicolon?
<ThatTreeOverTher> oh I see
<ThatTreeOverTher> well now my application compiles but segfaults
<whitequark> this means you have a Release build of LLVM; you need to configure LLVM with --enable-debug.
<whitequark> errr --enable-asserts
<ThatTreeOverTher> so I suppose I have to uninstall the LLVM package and build it myself with --enable-asserts on?
<whitequark> after you do, it will die with a somewhat more readable error
<whitequark> yes
<whitequark> I don't know what is the proper way to do it on arch
<ThatTreeOverTher> pacman doesn't want to let me remove llvm without removing llvm-ocaml
<Drup> ThatTreeOverTher: use abs for that
<ThatTreeOverTher> isn't abs like yaourt?
<Drup> abs is a repository, yaourt is an overlay over pacman
<Drup> so, no.
<ThatTreeOverTher> it appears to be doing something, cool
<ThatTreeOverTher> why does it say llvm[1]: Compiling Errno.cpp for Release build ?
<ThatTreeOverTher> do I need to manually configure it to have --enable-asserts?
<Drup> yes, modify the pkgbuild
<ThatTreeOverTher> should I bother enabling "debug-runtime" and "expensive-checks"?
<whitequark> no
<ThatTreeOverTher> i stopped the compilation in the middle with Ctrl-C and now it refuses to compile
<tautologico> why I can't switch to 4.02.0dev+trunk on this machine? is it because it's using OS X 10.7?
<whitequark> ThatTreeOverTher: make distclean.
<tautologico> oh, it works
<whitequark> Drup: sooo I need to make this xform: https://gist.github.com/whitequark/194ad6c6ccf89d9c3b9b
<whitequark> I bet it's going to be a PITA
<Drup> whitequark: your thingy seem like the perfect use case for deriving, you know ?
<ThatTreeOverTher> whitequark, how long do you suppose llvm will take to build? should I make a cup of tea or go to bed?
<Drup> I hope you launched it with -j
<ThatTreeOverTher> you say that like you assume you know what I'm doing :)
<ThatTreeOverTher> i've used -j before but where would it go in this case?
<Drup> whitequark: that's going to be enough for today^W tonight.
<Drup> well, it's day again already here >_>
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<Drup> the code for for%lwt is clearly not by biggest achievement in term of code clarity, so I'm probably going to refactor it after sleeping :)
<Drup> my
<Drup> ThatTreeOverTher: there is an option in makepkg to modify the -j option when running make
<Drup> it's somewhere in the article about makepkg on the wiki :)
<ThatTreeOverTher> I just changed it manually across the pkgbuild, seems to work fine ;)
racycle__ has quit [Quit: ZZZzzz…]
maattdd has joined #ocaml
<whitequark> Drup: oh cool, you're an Lwt committer
<whitequark> (deriving) true, but does deriving currently even exist?
<Drup> s4re
<Drup> oups
<Drup> sure*
<Drup> it's still camlp4 based for now
<whitequark> ThatTreeOverTher: on my notebook i7 it takes about 10 minutes with --enable-backends=x86_64 --disable-optimizations --enable-debug
<ThatTreeOverTher> tea it is then
<Drup> emphasising on *for now*
<whitequark> Drup: Show.show<t> ಠ_ಠ
<Drup> :D
<Drup> (whitequark: I'm not really a lwt commiter, mostly an ocsigen one. but lwt happen to be in ocsigen :p)
<whitequark> ugh, the insides of deriving are disgusting
<whitequark> and it's undocumented too
<whitequark> fuck that
<Drup> yeah
<Drup> it's not pretty
<Drup> I hope to prettify/rewrite it by switching it to ppx
<whitequark> you could use ocaml-ppx_protobuf as the motivating example, then :p
<whitequark> it's complex enough to stress all the paths
<Drup> probably, yes
<Drup> going to do js_of_ocaml and eliom first, because they're easier
Kakadu has joined #ocaml
ThatTreeOverTher has quit [Ping timeout: 265 seconds]
avsm has joined #ocaml
maattdd has quit [Ping timeout: 276 seconds]
ThatTreeOverTher has joined #ocaml
clan has quit [Quit: clan]
rgrinberg has quit [Quit: Leaving.]
<xenocons> Drup: thought of another example of yield <> return, you can use multiple yields
<xenocons> [ for i in 0..2 do yield! [1;2;1;3]; yield i+1; yield i+1; yield i+4];;
<xenocons> [1; 2; 1; 3; 1; 1; 4; 1; 2; 1; 3; 2; 2; 5; 1; 2; 1; 3; 3; 3; 6]
<whitequark> and what's the point?..
<xenocons> whitequark: we were discussing the diff between yield and return ages ago
<xenocons> (i realise like 6 hrs has past since that discussion ;p)
<whitequark> nono, I remember that
<whitequark> I don't see any point in list comprehensions honestly, given you have proper closures
<xenocons> oh, point was that yield <> return
<whitequark> ahh
<whitequark> well, you're defining a coroutine basically
<xenocons> not saying its good\bad (infact most of the time perf isnt favourable for me so i abandon comprehensions)
<whitequark> half a coroutine, since it cannot receive values from outside
<xenocons> right
<whitequark> you could do exactly same using a closure and a mutable cell in ocaml
<whitequark> since yield is a keyword and not an API entry point (like in Ruby)
<xenocons> right, essentially you could define it yourself
<xenocons> but would it really be of much benefit
<whitequark> exactly
<xenocons> i do find something that yields 'desireable' elements to be useful though, but 'choose' is just as appropraite
<xenocons> i think ocaml has something similar (im sure)
<whitequark> List.filter
<xenocons> similar enough i guess
<whitequark> well, Enum.filter, if you insist on using generators
<whitequark> but if you want to start from lists, yea
<xenocons> [1;2;3;4] |> List.choose (fun x -> if x < 3 then Some x else None);; = [1;2] same result as filter, except filter can be written more succinctly
<xenocons> List.filter ((<) 3) [1;2;3;4] i guess
<whitequark> exactly
<xenocons> only difference is if you wish to utilise something like >>= maybe
<xenocons> where choose can be useful i guess
<whitequark> [1;2;3;4] |> List.filter ((<) 3) ?
<whitequark> or do you mean using the option monad
<whitequark> ?
<xenocons> yeah option monad
<xenocons> guess you open Option in ocaml to get it?
<whitequark> nope
<whitequark> ocaml doesn't really have monads in stdlib at all
<xenocons> ahh ok
<whitequark> it also doesn't have typeclasses so that is another problem
<xenocons> yeah, but not *too much* of a problem
<whitequark> I disagree :/
<xenocons> you like type classes? or you think monads less useful without
<whitequark> the hoops you need to jump through to use arithmetics or indexing in ocaml are ridiculous
<xenocons> e.g. the +. vs + thing?
<whitequark> .() for arrays, .[] for strings and .{} for... idfk, something else
<xenocons> + in ocaml not a polymorphic function
<whitequark> yes, +., +/, Int32/64.add, and so on
<xenocons> ah right yeh
<xenocons> it is a hurdle... however you end up writing less type signatures
<whitequark> I write them anyway in .mlis
<xenocons> ah
<xenocons> any reason?
<xenocons> tbh i found an annoying problem in ocaml where you can open 2 namesspaces that have the same function
<xenocons> and not realise that you are using the wrong 1 hehe
<whitequark> hm well, people usually write documentation in mlis and ascribe phantom types there
<xenocons> sometimes type sigs help resolve that ambiguity
<xenocons> ah
<xenocons> right
<whitequark> so all publicly visible modules always have mlis
rgrinberg has joined #ocaml
<whitequark> it's great practice
<xenocons> yeh, it sounds so
rgrinberg has quit [Quit: Leaving.]
<whitequark> Drup: your ppx code is... mildly disgusting, but at least I can understand it without drugs. which is not true when talking about camlp4
<whitequark> I suppose quotations would make it much more clear, but we're not there yet
<whitequark> it's funny, I actually wanted to implement the {foo||foo} thing in the language I've been developing. I wonder how well would it fare in ocaml
<xenocons> hehe, looking at rust its really ocamly
<whitequark> rust is great
<xenocons> yeah digging it
<xenocons> wish it'd hurry up and prod ready
Simn has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
Anarchos has joined #ocaml
wwilly has joined #ocaml
<wwilly> bonjour
eizo has joined #ocaml
<Anarchos> salut wwilly
clan has joined #ocaml
osnr has joined #ocaml
axiles has joined #ocaml
NoNNaN has quit [Ping timeout: 272 seconds]
tautologico has quit [Quit: Connection closed for inactivity]
NoNNaN has joined #ocaml
claudiuc has quit [Remote host closed the connection]
nikki93_ has joined #ocaml
nikki93 has quit [Ping timeout: 252 seconds]
yacks has quit [Ping timeout: 265 seconds]
yacks has joined #ocaml
ggole has joined #ocaml
ollehar has joined #ocaml
wwilly has quit [Remote host closed the connection]
wwilly has joined #ocaml
avsm has quit [Quit: Leaving.]
tane has joined #ocaml
rand000 has joined #ocaml
clan has quit [Quit: clan]
avsm has joined #ocaml
avsm has quit [Client Quit]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
arrays has joined #ocaml
maattdd has joined #ocaml
araujo has quit [Quit: Leaving]
maattdd has quit [Ping timeout: 240 seconds]
maattdd has joined #ocaml
arrays has quit [Quit: Page closed]
divyanshu has joined #ocaml
ruzu2 has joined #ocaml
ruzu has quit [Ping timeout: 252 seconds]
studybot_ has quit [Remote host closed the connection]
<_obad_2_> I get: findlib: [WARNING] Interface topdirs.cmi occurs in several directories: /home/obad/.opam/4.02.0dev+trunk/lib/ocaml, /home/obad/.opam/4.02.0dev+trunk/lib/ocaml/compiler-libs ... ideas?
nojb has joined #ocaml
<nojb> define a gadt by type _ t = I : int -> int t | S : char -> char t
<nojb> and now: type any_t = U : 'a t -> any_t;;
ruzu2 has quit [Read error: Connection reset by peer]
<nojb> I would like to define the function map_any : ('a t -> 'b) -> any_t -> 'b by fun (U x) -> f x but it does not type check
<nojb> how to make it work ?
maattdd has quit [Ping timeout: 240 seconds]
ruzu has joined #ocaml
<nojb> sorry, that should be [fun f (U x) -> f x] obviously
divyanshu has quit [Quit: Computer has gone to sleep.]
tobiasBora has joined #ocaml
ruzu has quit [Read error: Connection reset by peer]
<ggole> I don't think that is sound.
ruzu has joined #ocaml
<_obad_2_> I get: findlib: [WARNING] Interface topdirs.cmi occurs in several directories: /home/obad/.opam/4.02.0dev+trunk/lib/ocaml, /home/obad/.opam/4.02.0dev+trunk/lib/ocaml/compiler-libs ... ideas?
<_obad_2_> sorry...
<_obad_2_> wrong window
maattdd has joined #ocaml
ruzu has quit [Read error: Connection reset by peer]
ruzu has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
<ggole> nojb: what are you trying to do there?
angerman has joined #ocaml
<nojb> ggole: just trying to understand gadts.. Suppose that you have a gadt like ['a t] above and you want to stuff objects of type ['a t] for different ['a]s inside a, say, Hashtbl.t; You should be able to do this after wrapping them up inside a universal type like [any] above. And you should be able to use these elements as argument of functions which have type ['a. 'a t -> 'b]. Now you might want to write a higher order function that
<nojb> takes one such function and returns the corresponding function any -> 'b. But this requires some care evidently...
<ggole> The problem with wrapping things in an existential that way is that you "forget" what the type of the GADT is
<mrvn> nojb: you need 'a t -> 'a
shinnya has joined #ocaml
<mrvn> nojb: and your any needs a constructor for every 'a you want to store.
<nojb> mrvn: why?
<mrvn> Because you need to match on the constructor to get the type.
<ggole> My GADT-fu is pretty weak, but it seems to be that the usual approach to "this element can be any leg of the GADT" is builders rather than existentials
<ggole> Basically, heterogeneous lists
<mrvn> The problem is to extract an element of a specific type out of the hashtable you need runtime type information. 'type any = Any: 'a -> any' does not provide that.
<nojb> mrvn: yes, except that I do not want to *extract* the underlying element, simply pass it to a function that is equipped to handle elements of *any* such type.
<nojb> just to be clear: the following works:
<mrvn> nojb: no, not any but every
<mrvn> nojb: any such type would be 'a
<nojb> right
<nojb> so the following works:
<nojb> type 'a t = I : int -> int t | S : string -> string t
<nojb> let f : (type a) a t -> int = function I n -> n | S s -> String.length s;;
<nojb> type any = U : 'a t -> any;;
<nojb> let g (U x) = f x;;
<nojb> so that I can do g (U 12) => 12
<nojb> and g (U "Hello") => 5
<mrvn> f gives me a syntax error
<nojb> sorry
<ggole> let f : type a . a t -> ...
<nojb> write
<nojb> right
<nojb> sorry about that
<nojb> so one can do
<nojb> let h = Hashtbl.create 3;;
<mrvn> # g (U (I 12));;
<mrvn> - : int = 12
<nojb> yes
<nojb> sorry about the typos
<nojb> so you can see how it works
<nojb> Hashtbl.add h 1 (U (I 12));;
<nojb> g (Hashtbl.find h 1) => 12;;
<nojb> So one can definitly do it this way...
<nojb> My question was about how to write the type of a function that produces [g] from [f]
<mrvn> The problem is that 'a t needs to declare every possible type.
<nojb> mrvn: what do you mean ?
<mrvn> val make : ('a t -> int) -> (any -> int)?
<nojb> yes
<mrvn> nojb: In an universal container I want to put in every possible type. Not just those listed in the 'a t type.
divyanshu has joined #ocaml
divyanshu has quit [Client Quit]
<mrvn> # let make f = function (U x) -> f x;;
<mrvn> Error: This expression has type a#4 t but an expression was expected of type a#4 t
divyanshu has joined #ocaml
<mrvn> The type constructor a#4 would escape its scope
<nojb> right I do not understand that type error
<ggole> When you match against a GADT, the associated type variables can't be part of the return type
<ggole> You run into this problem with type any : 'a t -> any, because the 'a is such a type variable
<nojb> ggole: I can't see how 'a is part of the return type of [make] ... can you explain ?
<ggole> I might not have phrased that very well
<ggole> The 'a is passed to f, so it "escapes" the limited scope
<ggole> "Return type" is more confusing than helpful, sorry.
<mrvn> but why is that a problem?
<nojb> ggole: ok, but it works if [f] is defined globally instead of being passed as a parameter (see the example above with [f] and [g])
<ggole> It's a soundness problem.
<mrvn> looks like GADT functions are no longer first class.
<ggole> They're first class, just confusing and hard to work with.
<mrvn> nojb: consider this: let h : type a . a t -> a = function I n -> n | S s -> s;;
<mrvn> let make f = function (U x) -> f x;;
<mrvn> val make : type a . (a t -> a) -> (any -> a)
<mrvn> nojb: How should that type well?
<mrvn> ggole: can you give an example that is unsound where the return type does not contain a "type a"?
<ggole> Good question.
<mrvn> ggole: I can't think of anything where you can construct g explicitly but which would be unsound through a higher level function.
<ggole> References, maybe
<mrvn> ggole: should already fail when you build the g by hand. But maybe there could be cases where by hand gives an error but through higher level succeeds.
q66 has joined #ocaml
q66 has quit [Changing host]
q66 has joined #ocaml
avsm has joined #ocaml
<mrvn> The problem with GADTs is that a lot of the time you have to match the GADT even if all branches of the match are identical. The match is just there so the type inference can verify each type manually.
avsm has quit [Quit: Leaving.]
<mrvn> This works: let make () = function (U x) -> match x with | I i -> f (I i) | S s -> f (S s);;
<mrvn> This fails: let make f = function (U x) -> match x with | I i -> f (I i) | S s -> f (S s);;
<mrvn> How do I have to annotate f to show that it is a GADT function?
<_obad_2_> sorry to interrupt.. in 4.02 when I go module P = Printf it doesn't show the module signature anymore. is this a bug?
<mrvn> in the toplevel or ocamlc -i?
<_obad_2_> toplevel
<ggole> I don't see anything in the changelog about it
<ggole> Ask about it on the mailing list, I guess.
dsheets has joined #ocaml
shinnya has quit [Ping timeout: 240 seconds]
divyanshu has quit [Ping timeout: 240 seconds]
darkf has quit [Quit: Leaving]
divyanshu has joined #ocaml
ollehar has quit [Ping timeout: 252 seconds]
Thooms has joined #ocaml
avsm has joined #ocaml
<adrien> ah, nice
<_obad_2_> only expressions are implemented... if anyone wants to collaborate, just ask me. or fork it.
angerman has quit [Quit: Gone]
avsm has quit [Ping timeout: 265 seconds]
keen_____ has quit [Ping timeout: 276 seconds]
araujo has joined #ocaml
araujo has quit [Changing host]
araujo has joined #ocaml
keen_____ has joined #ocaml
ivan\ has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
ivan\ has joined #ocaml
tani has joined #ocaml
divyanshu has quit [Ping timeout: 252 seconds]
tane has quit [Ping timeout: 252 seconds]
avsm has joined #ocaml
angerman has joined #ocaml
avsm has quit [Ping timeout: 255 seconds]
ollehar has joined #ocaml
racycle__ has joined #ocaml
testcocoon has quit [Quit: Coyote finally caught me]
testcocoon has joined #ocaml
Nuki has joined #ocaml
avsm has joined #ocaml
fantasticsid has joined #ocaml
avsm has quit [Ping timeout: 252 seconds]
pminten has joined #ocaml
cantstanya has quit [Quit: k]
eizo has quit [Ping timeout: 240 seconds]
<whitequark> hm, camlp4 is built as part of trunk again?
<adrien> the sources are off the trunk
Rotacidni has quit [Ping timeout: 264 seconds]
fantasticsid has quit [Ping timeout: 240 seconds]
<whitequark> but it *is* built again
<adrien> packaging?
<whitequark> hm? I mean, that's good
<whitequark> it means I don't have to spend hours trying to make type_conv work again
<adrien> it's definitely the packaging
<whitequark> oh, you mean opam?
<adrien> I believe it's a poor idea to do so
rgrinberg has joined #ocaml
<adrien> I understand the concerns but it won't get us any better
nojb has quit [Ping timeout: 255 seconds]
<whitequark> wtf, trying to install camomile segfaults on trunk
Arsenik has joined #ocaml
<whitequark> ah, no, I was wrong, camlp4 is not built. I had it installed locally.
<whitequark> and opam tried to reinstall it when I did the switch
<adrien> heh :)
<whitequark> hm, what's wrong with this?
<whitequark> pvb_pat = Pat.var { txt="reader"; loc=!default_loc };
<whitequark> Error: Syntax error
<adrien> =!
<whitequark> oh?
<adrien> dunno why
<whitequark> I see
<adrien> that's what the toplevel told me
<ggole> It would be nice to have something more informative than "Syntax error"
<ggole> ocamlyacc seems unlikely to be updated though
<adrien> menhir!
<adrien> and a free highlight for def-lkb
rgrinberg has quit [Quit: Leaving.]
<whitequark> hm, how do I signal an error from a ppx ext?
elfring has joined #ocaml
avsm has joined #ocaml
<elfring> Are you interested to improve a class library?
<_obad_2_> whitequark: you mean with location info? looks like Ast_mapper.run_main uses Location.report_exception
<whitequark> ah, great. thanks
<_obad_2_> so I guess one would Location.register_error_of_exn for one's own exception
tautologico has joined #ocaml
dapz has joined #ocaml
<jpdeplaix> whitequark: ok. Thanks for the information.
pminten has quit [Remote host closed the connection]
marr has joined #ocaml
waneck has quit [Ping timeout: 265 seconds]
<Nuki> Bonjour, j'ai une petite question à propos des types fantômes. J'en utilise pour un petit exercice personnel. Le soucis, qui n'en est pas réellement un, c'est que j'ai une fonction qui doit extraire des information d'un seul des constructeur de mon. Donc dans la signature, j'ai utilisé [< truc ] pour garantir à la compilation qu'on ne puisse lui donner qu'une seule portion des données (excusez le terme hasardeux), malheureusement,
<_obad_2_> et donc?
<tautologico> malheureusement...
<Nuki> Ah oui, désolé, limite de taille, je l'oublie chaque fois
<Drup> Nuki: #ocaml-fr pour les questions en francais
<Nuki> Ah désolé
<whitequark> google translate does a really nice job doing fr→en
<Nuki> (Sorry, I didn't knwo ocaml-fr :)
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dapz has joined #ocaml
dapz has quit [Client Quit]
maattdd has quit [Ping timeout: 240 seconds]
dapz has joined #ocaml
ollehar has quit [Ping timeout: 252 seconds]
ollehar has joined #ocaml
<ThatTreeOverTher> whitequark, I now get assertions... could you help me understand them? I have: http://pastebin.ca/raw/2706776
angerman has quit [Quit: Gone]
* whitequark sighs
<ThatTreeOverTher> :9
<whitequark> first, compile your OCaml code while passing -g to ocamlopt
<whitequark> second, run it under gdb and when it fails, tell gdb to print backtrace ("bt")
<whitequark> then you will see at which line it fails
<tautologico> it seems a problem in the type of your function
<ThatTreeOverTher> whitequark, how do I do the first thing? I'm not quite sure I understand
<ThatTreeOverTher> i have: ocamlbuild -use-ocamlfind -package llvm dropletc.native
<whitequark> add "true: debug" to your _tags
<whitequark> add "true: debug" to your _tags file
maattdd has joined #ocaml
struktured has joined #ocaml
angerman has joined #ocaml
inr has quit [Ping timeout: 245 seconds]
inr has joined #ocaml
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
eizo has joined #ocaml
avsm has quit [Quit: Leaving.]
<nickmeharry> Looks like I'm not the only one with compilation touble this morning.
<nickmeharry> Anybody know how to pass a multi-word argument to the linker from ocamlbuild?
<nickmeharry> Specifically, I'm trying to get it to take -framework Cocoa without mangling it.
<adrien> I'm going to make your eyes cry
<adrien> -cflags -ccopt,-Wall,-ccopt,-Wextra,-ccopt,-O2 -lflags yypkg/win.o,-cclib,-link,-cclib,-static,-cclib,-link,-cclib,-static-libgcc,-cclib,-link,-cclib,-v,-cclib,-llzma \
<adrien> to be fair you can probably quote what is after -ccopt and -cclib
<adrien> actually
<adrien> what do you want to do exactly?
<nickmeharry> I'm trying to use OcamlSDL on OSX.
<nickmeharry> That brought up an error something like NSInternalInconsistencyException
<nickmeharry> I exhausted most of my leads on that.
<nickmeharry> Most of the responses I could find for that were on Haskell.
<nickmeharry> The one OCaml related post was unanswered.
<adrien> you want to pass that option when building or when using ocamlsdl?
<nickmeharry> I'm pretty sure I need it when building.
<nickmeharry> When I try to build natively, I don't get the pretty exception. Instead, I get a bunch of symbols being undefine.d
<nickmeharry> A bunch of them started with _CF, so I figured including Cocoa would include the CoreFoundation stuff.
<adrien> but hmmm
<adrien> ocamlsdl uses ocamlbuild to build?
<nickmeharry> No, I'm using corebuild, which is a thin wrapper around ocamlbuild.
<nickmeharry> Well, actually I don't know what ocamlsdl uses.
<adrien> ah
<nickmeharry> I installed it via opam.
<adrien> corebuild is probably not what you should use for ocamlsdl
<adrien> well, more than merely probably
<adrien> and why not keep the existing build system?
<nickmeharry> I guess I don't know what I should be using then.
tlockney is now known as tlockney_away
<nickmeharry> Considering that ocamlbuild is in the official docs, I figured that part shouldn't be too much of a problem.
<nickmeharry> Here's the errors I get when compiling it: http://pastebin.com/SqwgB8Up
<adrien> if you want to replace the build system in ocamlsdl, oasis would be the way to go
<adrien> but the path of least resistance is to use the build system that currently exists in ocamlsdl
<nickmeharry> I'm not building ocamlsdl itself, I'm just trying to use it.
<nickmeharry> It installed just fine via opam.
jao has quit [Ping timeout: 252 seconds]
<adrien> ah, ok, I had misunderstood that bit
<nickmeharry> Yeah, sorry. I should've stated my problem better.
<adrien> as for corebuild specifically, it will only be useful if you want to use Core
<nickmeharry> Which I plan on using once I get this project off the ground.
<adrien> call ocamlbuild/corebuild with:
<adrien> -lflags -cclib,-framework,-cclib,Cocoa
<nickmeharry> Thank you, that did it.
<nickmeharry> So I guess that rather than pass strings with spaces, just comma seperate everything.
<adrien> can you try:
<adrien> -lflags -cclib,"-framework Cocoa"
<adrien> ?
<adrien> and actually
<adrien> -lflag "-cclib -framework Cocoa"
<adrien> that last one won't work
|jbrown| has quit [Remote host closed the connection]
<nickmeharry> I think that's what I tried earlier, but I'll double-check.
<nickmeharry> ocamlopt: unknown option `-cclib -framework Cocoa'.
<adrien> ok, thanks
<nickmeharry> That was the second one.
<nickmeharry> The first one gives me "ocamlopt.opt: don't know what to do with Cocoa."
<adrien> ok, thanks a lot; I think there's a nicer way to write these but I can't remember
<nickmeharry> Well, it's working now.
<nickmeharry> I'll figure out some makefile magic to automagically add the prefixes to pass stuff to the linker/compiler/whatever.
<nickmeharry> Thanks a lot.
<adrien> you can put that in the _tags file for ocamlbuild
<adrien> not sure of how it should look like though
<whitequark> adrien: I've migrated a few of my projects to oasis but I'm starting to doubt its value
<whitequark> so far the main thing it provides is version constraint checking
<whitequark> everything else is simpler to do manually
<tautologico> once you know a lot about how to customize ocamlbuild
<tautologico> otherwise the declarative style of oasis is easier to learn
<tautologico> well, I suppose you can use other build systems too...
<adrien> whitequark: you've tried doing C bindings?
<whitequark> adrien: sure
<adrien> with .h files in your source?
<adrien> I already know you haven't
<adrien> because it doesn't work with bare ocamlbuild
<whitequark> no .h files, no
<whitequark> but I'm not arguing for bare ocamlbuild
<adrien> and do you do all the things needed to have it packageable?
<whitequark> recently did that for ocaml-sodium
<whitequark> it's... not hard
<whitequark> the maintainer argued that OASIS-less solution is simpler and more elegant. I implemented it and had to agree: it is
<adrien> can you link me to that for ocaml-sodium?
ontologiae has joined #ocaml
<adrien> oasis works without a posix shell and thus is way closer to work on windows
<adrien> doesn't depend on gnu make either
HoloIRCUser has joined #ocaml
<adrien> (well, I think so)
cantstanya has joined #ocaml
<adrien> recently it let me override a poor value of ext_dll in ocamlbuild's config
<adrien> in the ocaml-sodium Makefile, ${} should be replaced with $()
avsm has joined #ocaml
<adrien> works but it's supposed to be ()
_obad_andro has quit [Ping timeout: 255 seconds]
<adrien> the cmx rule is wrong
<adrien> if a mli exists, it has to be built before the ml file
<adrien> so the cmx rule should depend on cmi
<adrien> same for cmo
<adrien> there is no rule to build .cmxs files
<adrien> using $(CC) in a Makefile is a fairly bad idea
<adrien> well, and having it default to "cc" or "gcc" that is
<adrien> should be "ocamlc" for most cases
<adrien> but for that last one I'm not sure what is the use of the %.so rule
<adrien> ah
<adrien> the .so should be built with ocamlmklib
<adrien> the main .a file is usually a byproduct of the creation of the .cmxa
<adrien> now going to bed
<adrien> all these are things oasis will do properly and build system reinventions won't
Anarchos has joined #ocaml
tlockney_away is now known as tlockney
tlockney is now known as tlockney_away
wwilly has quit [Remote host closed the connection]
<tautologico> it seems harder to agree on things in ocaml-land
<tautologico> haskell people use cabal (even though it has well-known weak spots) and that's it
<adrien> oasis' startup time can be a large part of the build process
<adrien> for haskell you're going to wait half an hour for the files to compile anyway
<whitequark> adrien: you're looking at the wrong ocaml-sodium
<whitequark> it's extremely simple
axiles has quit [Ping timeout: 265 seconds]
<whitequark> I'm not arguing for Makefiles either, btw. they're horrible
Asmadeus has quit [Ping timeout: 264 seconds]
<ggole> They're standard, which does have its advantages.
<ggole> (Unfortunately.)
Asmadeus has joined #ocaml
<whitequark> ocamlbuild is, too
* ggole wonders what the computing world would look like without network effects
nikki93_ has quit [Remote host closed the connection]
tlockney_away is now known as tlockney
<jpdeplaix> 22:19:50 adrien | oasis' startup time can be a large part of the build process // not anymore
<jpdeplaix> (with compiled_setup_ml)
<Simn> Speaking of makefiles, is there a better way of listing module dependencies in a way that both bytecode and native compilation is supported than what we're doing here? https://github.com/HaxeFoundation/haxe/blob/development/Makefile#L117
<Simn> We define MODULE_EXT to be either cmx or cmo, but it seems really crude like this.
eizo has quit [Ping timeout: 240 seconds]
lostcuaz has joined #ocaml
angerman has quit [Quit: Gone]
<whitequark> not use makefiles? :)
jonludlam has joined #ocaml
<HoloIRCUser> Makefiles simply cannot depend on directory contents, nor on dynamically changing dependency graphs.
<ggole> There's a tool for listing dependencies, ocamldep, but I can't remember enough about it to say whether it would be of use in that situation.
HoloIRCUser is now known as _obad_grrrr
Submarine has quit [Quit: Leaving]
<ggole> The ocamldep(1) command scans a set of OCaml source files... and outputs dependency lines in a format suitable for the make(1) utility... Dependencies are generated both for compiling with the bytecode com‐ piler ocamlc(1) and with the native-code compiler ocamlopt(1).
<mrvn> makefiles can generate dynamic dependencies on the fly.
<_obad_grrrr> Dependency generation tools don't cut it when you have multi stage dependencies e.g meta programming. Ocamlbuild does it right because it maintains a dynamically updatable dependency graph.
<ggole> Probably still beats typing all that shit by hand.
<mrvn> that's just a matter of making the tools complex enough
<whitequark> but makefiles simply aren't
<mrvn> makefiles are turing complete
<_obad_grrrr> You have to generate deeps and then either reinvoke make or include the generated files, that kind of thing doesn't work well.
<mrvn> or use secondary expansion
<Simn> IIRC the original makefile was created with the ocamake tool years ago.
<Simn> We just update it by hand since then.
<whitequark> mrvn: turing completeness is irrelevant
<mrvn> whitequark: turing completeness means you can do anything in make that you can do in any other language.
<whitequark> I know
<_obad_grrrr> Been there done that.... Buildroot does a lot of that and it's unreadable and very error prone.
<ggole> Let's write our build system in assembly. It's turing complete, too.
<whitequark> in OISC assembly.
<ggole> Yeah, simulators are probably available.
<Drup> in brainfuck, it's even more interesting.
<whitequark> you won't believe me if I said that OISC is quite commercially successful
<whitequark> Drup: take a look at what OISC is :p
<_obad_grrrr> Automake isn't too bad. The Linux kernel makefiles are very good, but they are are too intimately tied to the config system....
<ggole> Portions of x86 are OISC-like, I hear.
<whitequark> yes, the page fault handler is
<Drup> tautologico: I still don't understand how haskell people can bear cabal's package management
<Drup> it's so terrible ...
<_obad_grrrr> Good luck counting the $$$s when using secondary expansion. It's*horrible*.
<tautologico> yeah, cabal's dependency resolution (actually cabal-install) is bad, among other things
<tautologico> but it's the standard, so people use workarounds when they need them
<Drup> tautologico: well, afaik, the workarounds are "use the new sandbox feature in order that, when it blows, it blows only in the sandbox"
<Drup> I haven't found any good solution to any cabal issue which was not "just nuke everything and reinstall"
<tautologico> :)
Nuki has quit [Remote host closed the connection]
nikki93 has joined #ocaml
struktured has quit [Ping timeout: 240 seconds]
waneck has joined #ocaml
clan has joined #ocaml
Arsenik has quit [Remote host closed the connection]
tobiasBora has quit [Quit: Konversation terminated!]
struktured has joined #ocaml
squiggnet has quit [Read error: Connection reset by peer]
elfring has quit [Quit: Konversation terminated!]
studybot_ has joined #ocaml
squiggnet has joined #ocaml
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
nikki93 has quit [Remote host closed the connection]
tlockney is now known as tlockney_away
Simn has quit [Quit: Leaving]
ikaros has joined #ocaml
Kakadu has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
tani has quit [Quit: Verlassend]
HoloIRCUser has joined #ocaml
nikki93 has joined #ocaml
_obad_grrrr has quit [Ping timeout: 276 seconds]
ollehar has quit [Ping timeout: 252 seconds]
ollehar has joined #ocaml
dapz has joined #ocaml
Thooms has quit [Quit: WeeChat 0.3.8]
ikaros has quit [Quit: Ex-Chat]
jbrown has joined #ocaml
avsm has quit [Quit: Leaving.]
nikki93 has quit [Remote host closed the connection]
rand000 has quit [Quit: leaving]
nikki93 has joined #ocaml
ggole has quit []
nikki93 has quit [Remote host closed the connection]
rgrinberg has quit [Quit: Leaving.]
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
racycle__ has quit [Read error: Connection reset by peer]
racycle has joined #ocaml
dapz has joined #ocaml
shinnya has joined #ocaml
dapz has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
jonludlam has quit [Read error: Operation timed out]
darkf has joined #ocaml
dapz has joined #ocaml
mdenes has quit [Quit: WeeChat 0.4.2]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
studybot_ has quit [Ping timeout: 252 seconds]
ontologiae has quit [Ping timeout: 240 seconds]
madroach has quit [Ping timeout: 252 seconds]
madroach has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
struktured has quit [Remote host closed the connection]
ahill-89 has joined #ocaml
marr has quit [Ping timeout: 252 seconds]
struktured has joined #ocaml
rgrinberg has joined #ocaml
studybot_ has joined #ocaml