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
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
sheijk has joined #ocaml
angerman has joined #ocaml
Nuki has quit [Remote host closed the connection]
angerman has quit [Ping timeout: 264 seconds]
everyonemines has quit [Quit: Leaving.]
<Promit> i have a list in ocaml - i want to do a pairwise iteration over this list
<Promit> IOW i want to take the cross product of the list against itself and then iterate over those pairs
<Promit> is there some neat trick using the standard lib functions or do i have to write this up
<Promit> i think i meant cartesian product, not cross product
<Promit> and now that i have the correct word, stackoverflow has the answer :D http://stackoverflow.com/questions/10893521/how-to-take-product-of-two-list-in-ocaml
angerman has joined #ocaml
<Promit> written by someone i know, too. that's random.
angerman has quit [Ping timeout: 255 seconds]
q66 has quit [Quit: Leaving]
nikki93 has quit [Remote host closed the connection]
nikki93 has joined #ocaml
<Drup> note that if you just want to do a pairwise iteration, you shouldn't actually construct the list
<Promit> oh?
ebzzry has quit [Read error: Connection reset by peer]
<Drup> because List.concat is costly
<Promit> oh, you mean the function he gave does the iteration
<Promit> so i can skip the concat and just replace the inner fn
ebzzry has joined #ocaml
amiller has quit [Ping timeout: 240 seconds]
yroeht2 has quit [Ping timeout: 240 seconds]
sheijk has quit [Ping timeout: 255 seconds]
sheijk has joined #ocaml
patronus_ has joined #ocaml
acieroid` has joined #ocaml
pippijn_ has joined #ocaml
sgnb` has joined #ocaml
LU324_ has joined #ocaml
<Drup> or just List.iter
<Drup> let pair_iter f l = List.iter (fun x -> List.iter (f x) l) l
pippijn has quit [Ping timeout: 240 seconds]
<Drup> (note that the function f here takes two arguments, not a couple, you can adapt it easily to take a couple instead)
acieroid has quit [Read error: Connection reset by peer]
testcocoon has quit [Ping timeout: 240 seconds]
petterw has quit [Ping timeout: 240 seconds]
jlouis has quit [Ping timeout: 240 seconds]
LU324 has quit [Ping timeout: 240 seconds]
msch has quit [Ping timeout: 240 seconds]
sgnb has quit [Ping timeout: 240 seconds]
patronus has quit [Ping timeout: 240 seconds]
jlouis_ has joined #ocaml
amiller has joined #ocaml
petterw has joined #ocaml
<Promit> i see, neat
<Promit> that's what i had in mind originally
<Promit> roughly speaking
msch has joined #ocaml
tnguyen has quit [Quit: tnguyen]
testcocoon has joined #ocaml
nikki93 has quit [Remote host closed the connection]
shinnya has quit [Ping timeout: 240 seconds]
aqz has joined #ocaml
ontologiae has quit [Ping timeout: 265 seconds]
nicoo_ has joined #ocaml
nicoo has quit [Ping timeout: 255 seconds]
Averell has quit [Ping timeout: 255 seconds]
zebr has quit [Ping timeout: 255 seconds]
Averell has joined #ocaml
Eyyub has quit [Ping timeout: 276 seconds]
Averell has quit [Excess Flood]
studybot has quit [Read error: Connection reset by peer]
Averell has joined #ocaml
zebr has joined #ocaml
tnguyen has joined #ocaml
divyanshu has joined #ocaml
sheijk has quit [Ping timeout: 258 seconds]
sgnb`` has joined #ocaml
_tca_ has joined #ocaml
yastero has quit [Ping timeout: 240 seconds]
cthuluh has quit [Ping timeout: 240 seconds]
penryu has quit [Ping timeout: 240 seconds]
_tca has quit [Ping timeout: 240 seconds]
Khady has quit [Ping timeout: 240 seconds]
gargawel has quit [Ping timeout: 240 seconds]
rwmjones has quit [Ping timeout: 240 seconds]
Fullma has quit [Ping timeout: 240 seconds]
wwilly has quit [Ping timeout: 240 seconds]
willb1 has quit [Ping timeout: 240 seconds]
araujo has quit [Ping timeout: 240 seconds]
martintrojer has quit [Ping timeout: 240 seconds]
zarul[afk] has joined #ocaml
cthuluh has joined #ocaml
_tca_ is now known as _tca
gargawel has joined #ocaml
Derander has quit [Ping timeout: 276 seconds]
ivan\ has quit [Ping timeout: 276 seconds]
j0sh has quit [Ping timeout: 276 seconds]
zarul has quit [Ping timeout: 276 seconds]
tristero has quit [Ping timeout: 276 seconds]
j0sh has joined #ocaml
Derander has joined #ocaml
sgnb` has quit [Remote host closed the connection]
_tca has quit [Changing host]
_tca has joined #ocaml
_tca has quit [Changing host]
_tca has joined #ocaml
Zerker has joined #ocaml
yastero has joined #ocaml
ivan\ has joined #ocaml
martintrojer has joined #ocaml
nikki93 has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
Eyyub has joined #ocaml
wwilly has joined #ocaml
Fullma has joined #ocaml
Khady has joined #ocaml
rwmjones has joined #ocaml
willb1 has joined #ocaml
tristero has joined #ocaml
studybot has joined #ocaml
studybot_ has joined #ocaml
studybot_ has quit [Read error: Connection reset by peer]
araujo has joined #ocaml
penryu has joined #ocaml
studybot has quit [Ping timeout: 255 seconds]
Zerker has quit [Quit: Colloquy for iPad - Timeout (10 minutes)]
studybot has joined #ocaml
studybot_ has joined #ocaml
studybot has quit [Ping timeout: 250 seconds]
sheijk has joined #ocaml
sheijk has quit [Ping timeout: 245 seconds]
studybot_ has quit [Read error: Connection reset by peer]
nikki93 has quit [Remote host closed the connection]
nikki93 has joined #ocaml
jpdeplaix has quit [Ping timeout: 240 seconds]
yroeht2 has joined #ocaml
Eyyub has quit [Ping timeout: 276 seconds]
studybot has joined #ocaml
divyanshu has joined #ocaml
studybot_ has joined #ocaml
studybot has quit [Ping timeout: 252 seconds]
tautologico has quit [Quit: Connection closed for inactivity]
sheijk has joined #ocaml
jpdeplaix has joined #ocaml
sheijk has quit [Ping timeout: 240 seconds]
fantasticsid has joined #ocaml
yacks has joined #ocaml
zarul[afk] has quit [Remote host closed the connection]
zarul has joined #ocaml
zarul has joined #ocaml
jao has quit [Ping timeout: 252 seconds]
fantasticsid has quit [Ping timeout: 255 seconds]
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
Eyyub has joined #ocaml
divyanshu has quit [Client Quit]
sheijk has joined #ocaml
fantasticsid has joined #ocaml
sheijk has quit [Ping timeout: 252 seconds]
Rotacidni has quit [Quit: Leaving]
apolly has quit [Ping timeout: 240 seconds]
Eyyub has quit [Ping timeout: 258 seconds]
xaimus has quit [Ping timeout: 245 seconds]
divyanshu has joined #ocaml
samebchase has quit [Ping timeout: 264 seconds]
samebchase has joined #ocaml
xaimus has joined #ocaml
studybot_ has quit [Read error: Connection reset by peer]
studybot has joined #ocaml
siddharthv_away is now known as siddharthv
studybot_ has joined #ocaml
studybot has quit [Ping timeout: 250 seconds]
sheijk has joined #ocaml
yacks has quit [Ping timeout: 252 seconds]
sheijk has quit [Ping timeout: 258 seconds]
studybot_ has quit [Read error: Connection reset by peer]
<whitequark> "strace is banned in France, where it is classified as a cracking tool (it can trace plain-text I/O).
<whitequark> is... is that true? :D
<gasche> that's probably an over-interpretation
<gasche> we do have stupid laws about tools designed to crack DRMs
fraggle_laptop has quit [Ping timeout: 265 seconds]
fraggle_ has quit [Ping timeout: 265 seconds]
<whitequark> I found the source and it appears to be pure parody, but, yeah, I'm not surprised
<whitequark> (is there a word for "when reality is worse than The Onion" ?)
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
fraggle_laptop has joined #ocaml
fraggle_ has joined #ocaml
racycle has quit [Quit: ZZZzzz…]
Submarine has joined #ocaml
axiles has joined #ocaml
Promit has quit [Ping timeout: 255 seconds]
ggole has joined #ocaml
sheijk has joined #ocaml
rgrinberg1 has quit [Quit: Leaving.]
sheijk has quit [Ping timeout: 240 seconds]
yacks has joined #ocaml
araujo has quit [Quit: Leaving]
zpe has joined #ocaml
angerman has joined #ocaml
Eyyub has joined #ocaml
<adrien> as usual the laws are fairly broad
<adrien> and lots are left to interpretation
<adrien> so far it's been mostly properly applied I think
<adrien> and strace definitely is a cracking tool; I use it to debug the most opaque codes, i.e. mines :P
<whitequark> god forbid someone uses gdb *gasps*
<whitequark> flux: no, I mean a single word, like "schadenfreude"
<flux> maybe in some future notthenion will be the word ;)
yacks has quit [Remote host closed the connection]
studybot has joined #ocaml
<gasche> I'm about to merge format+gadts
* adrien is proud: he recently debuggued C code without symbols by reading registers
<whitequark> \o/
<adrien> gasche: woah
<adrien> gasche: so we need to duck for cover
<gasche> something like that
<gasche> "Surprise attack of 6-parameters GADTs! Find the closest basement!"
* adrien need to afk quick in order to destroy the network at the office before anyone gets in and opposes
<adrien> hmm
<adrien> looks like I'm going for the same approach as most ocaml maintainers :P
Eyyub has quit [Ping timeout: 258 seconds]
eikke__ has joined #ocaml
angerman has quit [Quit: Bye]
sheijk has joined #ocaml
sheijk has quit [Ping timeout: 240 seconds]
nicoo_ is now known as nicoo
Simn has joined #ocaml
ygrek has joined #ocaml
Averell is now known as Averell
q66 has joined #ocaml
q66 has joined #ocaml
q66 has quit [Changing host]
sgnb`` has quit [Read error: Connection reset by peer]
Submarine has quit [Remote host closed the connection]
sgnb has joined #ocaml
ddosia has joined #ocaml
sheijk has joined #ocaml
AltGr has joined #ocaml
Eyyub has joined #ocaml
claudiuc has joined #ocaml
* whitequark has implemented the first ever protocol with ppx_protobuf: https://github.com/whitequark/cylinder/blob/master/lib/block.ml
sheijk has quit [Ping timeout: 276 seconds]
WraithM has quit [Ping timeout: 264 seconds]
ikaros has joined #ocaml
acieroid` is now known as acieroid
Eyyub has quit [Ping timeout: 276 seconds]
<companion_cube> whitequark: looks really great...
<companion_cube> so ppx_protobuf doesn't have any dependency?
madroach has joined #ocaml
<whitequark> companion_cube: only ppx_tools, compile-time
<whitequark> (for metaquotation)
<companion_cube> you look very productive :)
<whitequark> well, I now have nothing better to do than sit and churn out code :p
<whitequark> relevant: I know quite some companies that heavily (i.e. with money) encourage the employees to work from Thailand or Bali
<whitequark> sounds like paradise, right? well, turns out, after a week it's so incredibly boring that you're going to be productive simply because there is absolutely nothing else to do
<companion_cube> not sure coding is the only thing you have to do there
<companion_cube> oh :D
<companion_cube> so I fell for the cliché
<whitequark> (in the words of said employees as well...)
<whitequark> hmmm, I want ppx_optcomp
<whitequark> and I want it to be able to do things like: [1; 2; if%optcomp ocaml_version >= (4, 02, 0) then 3]
<NoNNaN> and rewrite autotools in ocaml ;p
<whitequark> no, just replace pa_optcomp for whatever people are doing with pa_optcomp right now
<whitequark> I'm mainly interested in choosing different codepaths depending on platform
<whitequark> e.g. inotify/kqueue/fsevents
<nicoo> gasche: Good choice in desktop environment ;)
<companion_cube> gasche: congrats
<companion_cube> (for format+gadt)
maattdd has joined #ocaml
<nicoo> companion_cube: This was merged ?
<nicoo> \o/
<companion_cube> working on it apparently
Kakadu has joined #ocaml
<pollux> hi
<pollux> is there any help (other than the manual) on use-runtime/make-runtime options of ocamlc ?
sheijk has joined #ocaml
ygrek has quit [Remote host closed the connection]
ygrek has joined #ocaml
<ggole> Sigh, circular build
<ggole> Time to randomly guess what the problem is again.
<companion_cube> :/
sheijk has quit [Ping timeout: 255 seconds]
<companion_cube> it's among the modules listed in the error
<ggole> It's in... toplevel.top!
<ggole> Not helpful.
<ggole> Basically I get to permute toplevel.mltop blindly until it works.
jlouis_ is now known as jlouis
<ggole> Hmm, the problem was that some code cleanup moved a Foo-qualified function call from outside Foo to inside it
<ggole> So I was a little unfair there
<ggole> Although the error message could be better.
<ggole> Maybe that's ocaml{c,opt}'s fault
ontologiae has joined #ocaml
rand000 has joined #ocaml
maattdd has quit [Ping timeout: 264 seconds]
sheijk has joined #ocaml
sheijk has quit [Ping timeout: 240 seconds]
choeger_tu has joined #ocaml
<whitequark> jpdeplaix: your patch is being reviewed
<whitequark> jpdeplaix: by the way, wouldn't the all-local target for bindings/ocaml do exactly what you want for build target to do?
<def-lkb> whitequark: why would this break nonpure code ?
<whitequark> def-lkb: would you argue that my snippet *should* return 2?
<def-lkb> Wow, code is executed twice?!
<whitequark> YES
<def-lkb> (It returns 1 on my utop that's why I got confused)
<def-lkb> Ok, this is really weird :|
<whitequark> it's probably some change in trunk
<whitequark> jpdeplaix: oh nevermind the last comment, I see you want to avoid ocamldoc
<whitequark> oh whoa, I just noticed that stackmaps, initially introduced in LLVM for on-stack replacing JITs, are also suitable to write out OCaml GC frames
<whitequark> this is really great, because it would allow to not spill everything around calls to caml_alloc (that would obviously kill performance)
maattdd has joined #ocaml
nikki93 has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 276 seconds]
sheijk has joined #ocaml
fantasticsid has quit [Ping timeout: 252 seconds]
<eikke__> is 'bytes' just an alias for 'string' in 4.02, or is there some implicit conversion somehow?
<whitequark> unless you pass -safe-string, it's an alias
<eikke__> ah, thanks
choeger_tu has left #ocaml [#ocaml]
Thooms has joined #ocaml
_andre has joined #ocaml
wwilly has quit [Remote host closed the connection]
wwilly has joined #ocaml
sheijk has quit [Ping timeout: 265 seconds]
<jpdeplaix> whitequark: thanks ! :)
<jpdeplaix> whitequark: by the way, doing ppx_optcomp would be very useful I think
<whitequark> well, duh!
<whitequark> there's just so many useful things and only as much hours in the day
<Drup> jpdeplaix: planed
<companion_cube> I'd like a ppx_yolo too, please
<jpdeplaix> :D
<companion_cube> so I can replace -> assert false with -> [@@yolo]
<whitequark> jpdeplaix: btw, even if the patch isnt accepted, it's no big deal: with the amount of churn in the ocaml bindings, you could as well include it through ocaml
<whitequark> companion_cube: well, go write it
<companion_cube> maybe I should :D
<whitequark> it's like 10 lines
<companion_cube> I'll follow your guide
<companion_cube> not now, but maybe this evening
<whitequark> I just wrote it, in fact. 148 characters. would *almost* fit in a tweet
<companion_cube> aww
<companion_cube> so cute :D
<whitequark> 119!
<Drup> ##ppx_int_140char
<whitequark> Ast_mapper.({default_mapper with expr=fun m->function[%expr[%yolo]]->[%expr assert false]|e->default_mapper.expr m e})
<Drup> #*
<Drup> companion_cube, you know what to tweet :D
ontologiae has quit [Ping timeout: 240 seconds]
<jpdeplaix> whitequark: what do you mean by « include it through ocaml » ?
<companion_cube> Drup: ^^
<companion_cube> whitequark: oh, does ppx use an extension to parse its own files?
<companion_cube> I mean, [%expr [%yolo]] is a pattern?
<Drup> companion_cube: no, but ppx_tools provide one
<companion_cube> oh I see
<whitequark> companion_cube: -ppx 'ocamlfind ppx_tools/ppx_metaquot'
<Drup> which is similar to camlp4 quotations
<whitequark> or even #ppx in utop (not in ocaml toplevel yet)
<whitequark> Drup: arguably that's not at all similar
<Drup> it's a quotation with anti quotations
<whitequark> camlp4 allows arbitrary strings, [% requires valid ocaml code
<Drup> oh
<Drup> right.
<whitequark> and the antiquotations have to be valid OCaml ASTs instead of arbitrary strings
<Drup> well, you're just saying that it's clean
<Drup> :)
<Drup> the intent is the same
<companion_cube> is there work on ocamlfind to integrate ppx extensions?
<companion_cube> anyway that's pretty neat
<Drup> gerd and alain are fighting about it
<whitequark> fighting?
<companion_cube> looks like Alain is fighting with most other people :D
<Drup> I mean, discussing about the order in which ocamlfind should load ppxs :p
<whitequark> oh.
<whitequark> aren't camlp4 exts order dependent as well?
<Drup> yes
<whitequark> so isn't that solved already?
<Drup> apparently not
eikke__ has quit [Ping timeout: 276 seconds]
eikke__ has joined #ocaml
<companion_cube> whitequark: what would a rule that require introducing a new variable look like with ppx_metaquot?
<companion_cube> say, we have [%% id] that is expanded into (fun x -> x)
<whitequark> let gensym = let i = ref 0 in fun () -> incr i; Printf.sprintf "__ppx_ext_%d" i
<whitequark> let open Ast_convenience in let v = gensym () in [%expr fun [%p pvar v] -> [%e evar v]]
<Drup> (I concur)
<whitequark> it's not exactly perfect but so far we only have this
<whitequark> companion_cube: also, [%% is for structure items, [% is for expressions
<companion_cube> hmm right
<companion_cube> Ast_convenience provids a gensym? ok
<whitequark> it doesn't
<whitequark> it provides evar/pvar
<companion_cube> I thought there would be some internal Gensym already provided by the system
<whitequark> you could also just use Ast_helper.Exp.var/Pat.var instead
siddharthv is now known as siddharthv_away
<whitequark> companion_cube: I would send a PR to ppx_tools
<whitequark> or even open a mantis bug
<companion_cube> :D
<companion_cube> first I need to use it
<companion_cube> I actually have something that could use ppx
<companion_cube> (oh surprise, it's related to serialization)
<whitequark> oh?
<companion_cube> it's for generating serializers of course
<whitequark> serializers to *what*
ygrek has joined #ocaml
<Drup> serializers, UNITE
<Drup> (into deriving)
eikke__ has quit [Ping timeout: 258 seconds]
studybot has quit [Remote host closed the connection]
<whitequark> Drup: I look into the horror that is ppx_protobuf's AST matching code
<whitequark> and I realize I don't want to write deriving all by myself
<Drup> :D
<companion_cube> whitequark: heh, it's a kind of generic structure
eikke__ has joined #ocaml
<whitequark> hm, I have seen that code somewhere
<whitequark> in some paper?
<wwilly> bonjour
<companion_cube> whitequark: a blog post
<companion_cube> o/ wwilly
<companion_cube> whitequark: so I'll try to write a ppx extension that generates sources/sinks for types
<whitequark> sounds great
rand000 has quit [Ping timeout: 245 seconds]
<jpdeplaix> whitequark ?
<whitequark> jpdeplaix: hm?
<jpdeplaix> 13:35:45 jpdeplaix | whitequark: what do you mean by « include it through ocaml » ?
<whitequark> through opam
Thooms has quit [Ping timeout: 255 seconds]
ruzu has quit [Remote host closed the connection]
<jpdeplaix> oh yes, of course. At least, llvm.3.4 already uses it.
ontologiae has joined #ocaml
<Drup> whitequark: any quick way to find all the loop headers blocks of a function in llvm ?
sheijk has joined #ocaml
<whitequark> Drup: not from C API
<Drup> good old graph walking it will be then
<whitequark> grmbl, how do you make a toplevel with oasis?
<Drup> I think instead of an AST, I will define an ocamlgraph "view" of an llvm function
* whitequark has a weird distaste for ocamlgraph
<Drup> and the I will throw all ocamlgraph algorithms at it, and it will be fabulous.
<Drup> (I'm not really sure it does what you want)
<whitequark> well I built one like that
<whitequark> but utop doesn't see any modules
<whitequark> I did pass -linkall even
<whitequark> ohhh, you need access to .cmis at runtime
<whitequark> this is really stupid
<Drup> even with ocamlmktop ?
<whitequark> hmmm, I haven't tried ocamlmktop, not sure how to make it work with oasis
<Drup> not sure either.
pippijn_ is now known as pippijn
<whitequark> oh, and ocamlmktop apparently doesn't solve the cmi issue
<whitequark> why can't it just embed the cmis into the executable?.. this is absurd
<flux> yeah, it seems the way. also should support embedding an additional .ocamlinit.
<whitequark> I just wrote Topdirs.dir_directory "./_build/lib"; in the top.ml and it worked
dvvrd has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
remy2 has joined #ocaml
remy2 is now known as remyzorg
divyanshu has quit [Client Quit]
_andre has quit [Quit: leaving]
_andre has joined #ocaml
darkf has quit [Quit: Leaving]
shinnya has joined #ocaml
ollehar has joined #ocaml
<Drup> whitequark: is the only way to know the successors of a block (according to control flow graph) is to look in the instruction for jumps ?
<whitequark> yes
* Drup is sad.
<whitequark> oh, hm, wait
<Drup> I was hopping I could just provide an abstract interface answering the ocamlgraph one, but calling llvm's operation directly
<whitequark> yes, seems about right
<Drup> hoping*
<whitequark> why can't you do that?
<Drup> because "get_successors" is going to be horribly inefficient ?
<whitequark> pattern-match the Llvm.terminator block
<whitequark> horribly inefficient?
<whitequark> looking at the terminator is what LLVM itself does internally
<Drup> oh, so it will only be in the terminator ?
<whitequark> of course
studybot has joined #ocaml
<Drup> oh, fine then.
<whitequark> where else would you have control flow in SSA?
studybot has quit [Read error: Connection reset by peer]
olauzon has joined #ocaml
<whitequark> you'll still have some overhead due to stubs, but it's not all that horrible
studybot has joined #ocaml
<Drup> huum, right, I tend to forgot some of SSA's constraints sometime
<ggole> I'm disabling warning 31 and it is printed anyway ಠ_ಠ
<ggole> wtf
<whitequark> (my imaginary LLVM backend would fix that!)
<Drup> what is the issue with stubs ?
<def-lkb> did you estimate the feasibility of such a backend ?
<whitequark> def-lkb: I wrote a proof of concept
<whitequark> so I think the answer is "yes"
studybot has quit [Read error: Connection reset by peer]
<whitequark> Drup: well, you have an OCaml trampoline in Llvm, then you have a C trampoline in llvm_stubs.c, then you have an LLVM-C trampoline in Core.cpp, then you finally have the useful code
<def-lkb> :), and the PoC was positive? do ocaml and llvm match reasonably well? :)
studybot has joined #ocaml
<Drup> whitequark: oh, right
<whitequark> def-lkb: it's feasible, but requires work
<Drup> whitequark: yeah, binding spageti, sure
<whitequark> def-lkb: and it requires a *lot* of *incredibly boring* work in order to integrate it upstream
<whitequark> (without that it would barely be useful)
<def-lkb> in llvm upstream?
divyanshu has joined #ocaml
<ggole> ocamlbuild doesn't pass flags to ocamlmktop?
<whitequark> in ocaml upstream mainly
<Drup> whitequark: what would be the changes for ocaml upstream ?
<whitequark> def-lkb: the changes to llvm seem to be insignificant and likely to be accepted, based on my past experience
studybot_ has joined #ocaml
<whitequark> (a new calling convention and some minor fiddling with stack/GC maps)
<ggole> gasche: ping
<Drup> oh, you are talking about the ocaml llvm backend, yes, I know about that :p
<whitequark> def-lkb: there's also registering new library functions to allow it to lift allocations into stack allocs
<whitequark> in OCaml however you need to seriously rectify its usage of Cmm, where it basically scoffs at its own conventions
<whitequark> Cmm is... dynamically weakly typed, so to say, and translating it to strongly statically typed LLVM IR exposes quite a lot of inefficiencies
<def-lkb> I guess this work would benifit other backends too? So in the long term, it may be worth deserving some attention.
<whitequark> and worst of all, it affects ABI
<whitequark> def-lkb: unlikely
<whitequark> at least I wouldn't motivate it like that
studybot has quit [Ping timeout: 240 seconds]
<def-lkb> there is a lot of stuff in the compiler needing some cleanup, just to ease further extensions, maintenance and so on.
<def-lkb> (but as gasche usually says, "it ain't broke, don't fix it", so there is always a tension…)
Thooms has joined #ocaml
metasyntax has joined #ocaml
topher has joined #ocaml
<ggole> Sigh
<ggole> The ocamlbuild docs aren't *quite* the worst I've seen, but they make a strong showing.
<def-lkb> :D
<ggole> How do you pass a flag to ocamlmktop?
<Drup> I don't know if it's better (as I haven't read it) but at least, it tries harder
<whitequark> ggole: have you seen the source of ocamlmktop?
<whitequark> I will paste it right here:
<whitequark> let args = Ccomp.quote_files (List.tl (Array.to_list Sys.argv)) in
<whitequark> exit(Sys.command("ocamlc -I +compiler-libs -linkall ocamlcommon.cma ocamlbytecomp.cma ocamltoplevel.cma " ^ args ^ " topstart.cmo"))
<whitequark> what you need to do is to compile a regular executable and just pass it -require compiler-libs.toplevel -linkall.
<Drup> whitequark: there is a "pred" operation in ocamgraph signature ... é_è
<whitequark> Drup: you can iterate uses of the blocks
<Drup> hum ?
<whitequark> Llvm.iter_uses
<whitequark> some of them will be terminators of predecessors
<Drup> oh, nice.
<whitequark> there is also the blockaddress operation, and functions use blocks as well
<ggole> whitequark: all I need to do is pass a flag to ocamlmktop
<whitequark> ggole: ahem
<whitequark> have you read what I have replied?
<Drup> (whitequark: I will ask you to read my stuff at the end, because I have a slightly idea of what I'm doing, but not much :D)
<whitequark> Drup: sure
<whitequark> ggole: or do you mean you want to do it via ocamlbuild?
<whitequark> then it's the same as for everything else, myocamlbuild.ml
dvvrd has quit [Ping timeout: 240 seconds]
<ggole> Back into the docs then.
<ggole> It's insane that I have to write ocaml code to pass a fucking flag.
<whitequark> dispatch After_rules -> flag ["ocaml"; "link"; "toplevel"] (A"-flag") | _ -> ()
<whitequark> here, I did it for you
<ggole> Sigh, if I'm going to use this junk I should really learn it properly
<ggole> (Thanks though.)
<gasche> ggole: I won't have time today to look at your issue, sorry
<ggole> gasche: OK, another time then.
topher has quit [Ping timeout: 240 seconds]
<eikke__> does ocaml have anything like 'open MyModule hiding (a, b)' (without writing out a full signature & 'casting' the original module to whatever you need & opening that one)
<Drup> no :(
<eikke__> feared so. grrr.
<whitequark> open MyModule [@@hiding a, b] ? :P
<whitequark> although, that's probably impossible to do syntactically, or nearly so
<nicoo> whitequark: I can't soo how to do that without typing first
<companion_cube> open must die :>
<nicoo> Ah, ok
* nicoo was too slow.
<nicoo> companion_cube: global open*
<whitequark> nicoo: well you could load the .cmi in the extension
<companion_cube> nicoo: yes
<nicoo> whitequark: How would I produce the cmi in the first place ? :]
<companion_cube> the open statement
<companion_cube> the only good open is for opening packs :)
<whitequark> nicoo: the compiler will
<whitequark> though... ocamldep executes over transformed code too
araujo has joined #ocaml
<whitequark> so it's a problem
<nicoo> whitequark: Yup :>
<nicoo> And imagin my code can't typecheck *without* the hiding
<whitequark> exactly
<whitequark> perhaps... we could teach the compiler itself what @@hiding means?
<whitequark> I wonder what is the policy for such changes
<Drup> whitequark: or just introduce a new keyword
<nicoo> whitequark: Then, why not introduce a full blown keyword ?
<whitequark> Drup: that seems to be nearly impossible
<whitequark> nicoo: because keyword may break user code
<Drup> no need for @@ silliness if it's in the compiler
<whitequark> but [@@hiding] cannot
<nicoo> whitequark: Ah, indeed
<ggole> That would break anything using hiding as an identifier
<Drup> huuum
<whitequark> and the maintainers have decided against adding contextual keywords
<Drup> that's a shame.
<whitequark> btw, a data point: since C# 1.0 no non-contextual keywords were added into the language
<eikke__> the 'hiding' in 'open Foo hiding (...)' cant ever be used now, isn't it?
<ggole> Wonder if you could use other constructs (although that would be quite ugly)
<ggole> open Foo "hiding" [a; b]
<whitequark> ugh no
<ggole> open Foo `Hiding ... etc
<Drup> ggole: please don't
* ggole nods
<companion_cube> open Foo --- Yolo.(`Including Bar)
<nicoo> ggole: Ewwwwwwwwwwwwwwwwww
<ggole> New syntax is a problem
WraithM has joined #ocaml
<ggole> Hey, it works for Javascript
<ggole> That's a pretty high bar, right?
* whitequark slaps ggole around a bit with a large trout
<companion_cube> :D
<ggole> Let's have "use dynamic"; turn the type checker off.
<ggole> OK, I'm done.
<whitequark> lol
<Drup> ggole: there is actually such mode in haskell.
<companion_cube> open RecTypes;;
<whitequark> open Unsafe;;
<Drup> whitequark: where is the definition of "TerminatorInst" ? I don't find it :(
<whitequark> what do you mean by "definition" ?
<Drup> hum, more like "the list of subclasses"
<whitequark> yep, covered
<Drup> (why isn't OpCode.t a nice poly variant with elegant subtyping to handle this ? :D)
dant3 has quit [Ping timeout: 252 seconds]
<whitequark> a poly variant with fifty cases isn't nice
<whitequark> and there's a high chance the binding is older than poly variants
<Drup> why ?
<whitequark> because of incomprehensible errors
<Drup> it's not recursive
<whitequark> hm, correct.
<Drup> you won't have incomprehensible errors
maattdd has quit [Ping timeout: 255 seconds]
<Drup> poly variants are hairy when there is recursivity + subtyping.
dant3 has joined #ocaml
alinab has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
<whitequark> argh, I really want ocp-index
<whitequark> let's try to figure out what's wrong with ocp-build again
<Drup> whitequark: you have the same issue than me ?
<whitequark> it's broken on trunk
<Drup> ok, so the reason for that is simple
<Drup> https://github.com/ocaml/opam-repository/issues/2006 read that, you will understand
<Drup> (and probably facepalm, too)
<whitequark> ugh.
lostcuaz has joined #ocaml
<whitequark> oh, ocp-index doesn't actually depend on anything external
<whitequark> I'll just fork it and rip out ocp-build
<companion_cube> ah, Bunzli, always so moderate :D
<companion_cube> "At least it makes it clear you don't seem to be interested in having more ocp-build users. "
<Drup> whitequark: can't you slap a makefile on ocp-build instead ? :3
<whitequark> I concur that the current situation with ocp-build is extremely user-ohstile
<Drup> it's ridiculous.
<whitequark> Drup: I'm not interested in investing time into looking how someone's yet another NIH-induced build tool works
<whitequark> I would rather burn it with a flamethrower
<Drup> I think someone proposed a makefile for ocp-index already
<Drup> the patch was rejected
<companion_cube> careful now, whitequark is going to burn half the OCaml ecosystem
<whitequark> I'll just slap an _oasis over it for now
<Drup> companion_cube: hide, you are not going to be spared if he starts to burn all reinventions :3
<companion_cube> that's what I was implying
<companion_cube> hmm so oasis -> ocamlbuild -> ocp-build
<whitequark> -> ocp-build ?
maattdd has joined #ocaml
<companion_cube> whitequark: to build ocp-build*
<companion_cube> now you just need to make an ocp-build backend for oasis, and the loop will be closed ^^
<whitequark> why does it use ocp-build AND autocrap?
<whitequark> ಠ_ಠ
<companion_cube> autocrap, what a nice project name
<whitequark> hmmm, it depends on some stuff from ocp-indent
* whitequark casts `cp'
* companion_cube feels that whitequark is inches away from renaming ocp-build into ocp-crap
<whitequark> what a marvellous idea
<Drup> whitequark: no, add a build system for ocp-indent too !
<whitequark> hahahaha, "add a build system"
<whitequark> fine, fine
<Drup> <3
<companion_cube> nocp-indent
<companion_cube> nocp-build
<whitequark> ocp-y-u-no-build
WraithM has quit [Ping timeout: 264 seconds]
<whitequark> clearly, this is the only possible way to refer to that project from now on.
<Drup> (I fear that you will need to extract some stuff from typerex)
<companion_cube> don't forget jenga-nestreet
<whitequark> Drup: doesn't seem like so, based on dependencies
<nicoo> whitequark: Should we submit a package rename to opam-repository ?
<whitequark> nicoo: definitely
<Drup> lefessant will not like it x)
<Drup> -t
<nicoo> Drup: So?
<companion_cube> "fork that builds for the whole community"
<Drup> nicoo: oh nothing, it's going to be fun :D
<companion_cube> "fork that builds outside of ocp"
<kerneis> isn't there any OCamlPro employee on #ocaml?
<Drup> kerneis: AltGr is one
<Drup> thomasga is an ex-one
<kerneis> and hnrgrgr
<nicoo> Drup: I definitely should wait for Trolldi for the PR
<Drup> indeed, but he's not touching build systems :p
<whitequark> Trolldi?
<AltGr> I sense some trolls lurking
<nicoo> whitequark: French tradition. Friday is trollday
<Drup> kerneis: but honestly, only lefessant is (sometimes) working on ocp-build
<kerneis> whitequark: "di" is the suffix for week days in French
<whitequark> oh
<whitequark> but it's monday
<nicoo> kerneis: Except for Dimanche (Sunday)
<nicoo> whitequark: Yes. Such a long wait.
<AltGr> Is there problems apart from the bytecode/4.02 compatibility issue ?
<Drup> AltGr: my bug report ?
<Drup> I have still no idea what's going on.
<whitequark> AltGr: there is a problem, it's called "it doesn't [REDACTED] build"
<whitequark> and if it was only due to changes in Typedtree or whatever, I'd already have fixed it and sent a PR
<AltGr> ok. Let's get rid right away of the bytecode compatiblity, blob and bootstrap philosophical issues, I won't comment on that
<AltGr> #2006 seems to be a problem with the package. In what setup does it fail ?
<AltGr> latest opam-repo ocp-build is a virtual package; ocp-build is actually included in package typerex
<Drup> AltGr: If you want me to provide more informations, just tell me what
<AltGr> sure: I'm investigating but couldn't reproduce so far
<whitequark> just do opam switch 4.02.0dev+trunk; opam install typerex
<Drup> whitequark: not the same bug
<whitequark> oh
<AltGr> (sorry for the confusion, and if I lost track of the original issue with the discussion going on on #2006)
<whitequark> ah, so AltGr politely told me above that he isn't going to fix the trunk issue
<whitequark> well, whatever, I'm almost done with OASIS conversion anyway.
<AltGr> incompatibility with 4.02 is known
<Drup> AltGr: yeah, it spiralled off topic quite quickly :p
Nuki has joined #ocaml
tane has joined #ocaml
<whitequark> why does ocaml_4/compat.ml list some functions that aren't present in *any* version of OCaml? ಠ_ಠ
divyanshu has quit [Ping timeout: 252 seconds]
<def-lkb> whitequark: it's forward compatibility, in case they are introduced in a future release
ygrek has quit [Ping timeout: 240 seconds]
<AltGr> Drup: can't access your pastebin anymore :/ (https://github.com/ocaml/opam-repository/issues/2006#issuecomment-42212466)
<Drup> whitequark: I don't find how to call "TerminatorInst.getSuccessor"
<AltGr> thanks
<whitequark> Drup: operand/num_operand
<whitequark> Drup: operand/num_operands*
<whitequark> then you have to Llvm.classify_value and pick the blocks
<Drup> I see
<Drup> it's a bit ...
<Drup> unsafe.
<whitequark> oh?
<whitequark> well
<whitequark> set_operand surely is
<Drup> and low level
<AltGr> I see: the real error is Unix_error(No such file or directory, lstat, /home/gabriel/.opam/4.01.0/lib/ocp-indent/ocp-indent) -- dangling symlink ?
<whitequark> Drup: low level it is. the OCaml bindings were never intended for *reading* code
<Drup> whitequark: :(
<Drup> AltGr: ...
<Drup> I didn't though about that
<AltGr> the message actually comes from the error at uninstall, which calls 'ocp-build uninstall'
<whitequark> by the way, if you have any improvements, just send them to me
<whitequark> I can commit changes to OCaml code without waiting for anyone else
remyzorg has quit [Quit: WeeChat 0.4.3]
<AltGr> so it's actually a but in ocp-build scanning function *and* a bug in opam error reporting :$
<whitequark> i.e. if you manage to add a generic, well-designed high-level interface for reading IR, I'll be happy to include it
rand000 has joined #ocaml
<Drup> multi bug \o/
<Drup> strike <3
<whitequark> a combo!
<AltGr> Sorry for not realising earlier
<Drup> AltGr: not your fault
<Drup> whitequark: I will probably try to design something when I have a good grasp of the whole API
<Drup> (which is clearly not the case right now)
<AltGr> on ocp-build: I think we need to let people cool down a little bit before we do anything
WraithM has joined #ocaml
<Drup> AltGr: I just checked, I don't have anything in ".opam/4.01.0/lib/ocp-indent/ocp-indent"
tlockney_away is now known as tlockney
<Drup> (I don't even have a directory ".opam/4.01.0/lib/ocp-indent"
<AltGr> no link to it ?
<Drup> no
demonimin has quit [Remote host closed the connection]
<AltGr> hm
<Drup> ocp-indent-lexer/ ocp-indent-lib/ ocp-indent-utils/
<AltGr> ah
<Drup> but no ocp-indent
<AltGr> there must be a stale META in $(opam config var lib)
<Drup> and anyway, why is ocp-indent involved ?
<whitequark> it uses lexer from ocp-indent
<AltGr> it's not referred to by ocp-build, that's for certain
<Drup> but ... ocp-indent needs ocp-build
<AltGr> whitequark, ocp-index does, not ocp-build
<Drup> what sort of circular madness is that ?
<whitequark> right
<AltGr> it's NOT referred to by ocp-build
<Drup> oh
<Drup> sorry
<Drup> misread
<AltGr> :)
<Drup> indeed
<Drup> there is a bunch of META in lib
<Drup> lot's of ocp-* metas
<AltGr> META.ocp-indent by chance ?
<Drup> indeed
<Drup> should I remove them ?
<AltGr> that would be the culprit
<AltGr> only if there is no corresponding directory
<Drup> but no ocp-foo is installed right now
<Drup> there shouldn't be any in theory ...
<AltGr> ok, you can remove them then
<Drup> still not working
<Drup> ahah :D
tobiasBora has joined #ocaml
demonimin has joined #ocaml
<AltGr> I knew that ringed a bell
<Drup> oh, I missed some stuff
<Drup> huum
<AltGr> I'm sure it's fixed in the unreleased version, I'll do what I can to have it published
<Drup> it seems to be working
<Drup> it works ! \o/
<AltGr> cool... sorry for the trouble
<Drup> AltGr: so, why does this stuff was here in the first place ?
<AltGr> ocamlfind gives two alternatives: mylib/META or (mylib/ AND META.mylib)
<AltGr> the latter is confusing when you expect to remove the library by removing the directory
<AltGr> it was a leftover from a previous installation
<Drup> I see
<Drup> (the fact that opam doesn't keep track of the file it installed is still, imho, a design flaw)
<whitequark> I now see the actual failures due to 4.02. fortunately, easy to fix
<AltGr> whitequark, you know there was already a Makefile.simple right ?
<whitequark> didn't notice it
Eyyub has joined #ocaml
WraithM has quit [Ping timeout: 255 seconds]
<AltGr> Drup: it's planned; but there is no perfect solution, either you leave all the work to the packagers, or you dynamically check and lose a lot in portability / performance
<AltGr> we chose a compromise between ease of adoption / packaging and reliability
<Drup> AltGr: was there a fondamental issue with the usual technique used by other package manager (use DESTDIR, basically)
<AltGr> and you have all the tools you need to properly declare files to install/remove (using .install files)
<AltGr> ocaml isn't DESTDIR compatible :(
<Drup> AltGr: well, the issue is when the install stuff change
<gasche> AltGr: it should be in trunk
<AltGr> cool
<gasche> and it was done because someone reported the bug on mantis
<Drup> AltGr: I must have thee different version on the emacs interface for ocp-indent
<Drup> all in different places
Thooms has quit [Ping timeout: 264 seconds]
<Drup> \O/
<companion_cube> yay !!
<Drup> commit message "Jacques forgot a crucial detail" <3
<def-lkb> gasche: what is -no-naked-pointers for?
<companion_cube> decency
<def-lkb> gasche: dropping the pagetable ?
jao has joined #ocaml
<gasche> it's Mark's work, you should ask him directly
jao has quit [Changing host]
jao has joined #ocaml
<gasche> I understood that's the plan, though it's not actually dropped, only maybe used less often
<gasche> (it's disabled by default anyway)
<gasche> (so it shouldn't be visible in 4.02 unless you explicitly ask for it at configure-time)
<def-lkb> ok, I wasn't aware of the current state of this project (and of this flag)
Thooms has joined #ocaml
jwatzman|work has joined #ocaml
WraithM has joined #ocaml
WraithM has quit [Ping timeout: 240 seconds]
<whitequark> whee, sublime-ocp-index works
<AltGr> whitequark: yet OASIS...
<whitequark> once again, rage-driven development proves itself an indispensable methodology.
<whitequark> AltGr: I sent a PR without OASIS changes too
<AltGr> cool, thanks !
<whitequark> I honestly don't care what build system do you use as long as it 0) works 1) doesn't require my attention
racycle has joined #ocaml
<whitequark> that being said, I so far don't see any reason to not use OASIS. mapping of *.ocp files to OASIS was practically something that could be done with sed
tobiasBora has quit [Ping timeout: 265 seconds]
<AltGr> sure, there's nothing particularly fancy in the build process
Thooms has quit [Quit: WeeChat 0.3.8]
boogie has joined #ocaml
ontologiae has quit [Ping timeout: 245 seconds]
Eyyub has quit [Ping timeout: 252 seconds]
nikki93 has joined #ocaml
<AltGr> in any case, really appreciate the contributions
<AltGr> Be sure not to underestimate "something that could be done with sed" though :D
<whitequark> well, there's probably some problem that ocp-build solves which OASIS does not
<whitequark> but so far I don't see it...
manizzle has quit [Ping timeout: 276 seconds]
<whitequark> why was it created?
nikki93 has quit [Remote host closed the connection]
<companion_cube> whitequark: it would be nice to have ocp-build as a backend to oasis actually
<companion_cube> because _oasis files are pretty much as good descriptions of a project as possible
Kakadu has quit [Ping timeout: 240 seconds]
<adrien> sed adepts are welcome for the ocaml compiler
<adrien> mostly looking for masochists to translate whatever was written in sed years ago and without comments into something human
<AltGr> I won't enter the debate any further, but I do find ocamlbuild to be highly unsatisfactory (and I have used it _a lot_). Not sure either adding a layer on top of it is the best solution.
Submarine has joined #ocaml
<AltGr> adrien, haha
<AltGr> might give it a go, but I really don't have time right now
<whitequark> AltGr: I wonder if you would like _oasis file that generates ocp-build descriptions
<adrien> AltGr: I don't think anyone would contradict you about ocamlbuild
<adrien> where people start thinking differently is whether it can be improved or not
<adrien> can and will
tlockney is now known as tlockney_away
<adrien> and I actually wouldn't call oasis a layer on top of it but I see your point
<adrien> imho oasis _fixes_ stuff in ocamlbuild
<adrien> and probably that part of the myocamlbuild.ml that oasis generates should go straight into ocamlbuild
<adrien> and that alone makes ocamlbuild in a much better shape
<adrien> whitequark: oasis can be multi-build-system
<whitequark> hmm, perhaps the ocamlbuild split would help here
<whitequark> adrien: I know, hence the question
<adrien> except noone wrote a backend that isn't ocamlbuild
<adrien> that also means oasis is heavily biaised toward ocamlbuild
<adrien> and part of the criticism it gets is clearly inherited from ocamlbuild
<adrien> that said it builds ocaml projects correctly (in the sense that it builds things the way they are supposed to be built)
shinnya has quit [Ping timeout: 240 seconds]
<whitequark> we have too many build systems and not enough demolition systems. let's build a demolition system
<adrien> again, sed ;p
ollehar has quit [Ping timeout: 240 seconds]
<whitequark> "Unfortunately, as you probably already know, sed" ?
rgrinberg has quit [Quit: Leaving.]
<companion_cube> ocp-shred
<ggole> dd makes a pretty good build system.
<ggole> You can build big things full of zeros very easily.
<companion_cube> AltGr: oasis isn't a frontend to ocamlbuild, it just happens to use it
rgrinberg has joined #ocaml
<AltGr> Alright ; but my point stands on the reason why ocp-build was created, we don't have a really satisfactory build system at the moment
<AltGr> Also, native windows compatibility, or so I was told
<AltGr> until we do have one, it's good to have different solutions
tani has joined #ocaml
<adrien> AltGr: oasis definitely works on windows
<adrien> native
<adrien> only real issue is an issue in the stdlib
<adrien> and it's not a big concern in practice (although it makes builds quite a lot slower)
<adrien> and I'm also doing cross-compilation with oasis
<adrien> and it works well
<adrien> what might not work is the additions to the oasis bits
<whitequark> adrien: do you have any pointers on cross-compilation with oasis?
<whitequark> I'm really interested in that
<adrien> (exactly like with autotools as I told on the ML not that long ago)
<adrien> whitequark: half the work is getting a proper ocamlfind.conf file
<adrien> what I have now works but isn't very cute
<adrien> but shouldn't be too much work to clean
<adrien> then there's pretty much nothing to do
tane has quit [Ping timeout: 240 seconds]
<adrien> and issue that might arise with 4.02 is that ocamlbuild uses ocamlfind to build myocamlbuild.ml
<adrien> and since ocamlfind has been set to use the cross-compiler, it will beak
<adrien> break*
<whitequark> that seems likely
<adrien> but since oasis shows you the ocamlbuild invocation, you can copy it and pass -without-ocamlfind or something like that
<adrien> one thing I had to "fix" recently was ocamlbuild's value for "ext_dll"
<adrien> was .so (since you re-use the host's ocamlbuild)
<adrien> but oasis allows you to overwrite that eaily
<adrien> -override ext_dll .dll
<adrien> pretty much it
WraithM has joined #ocaml
<adrien> then problems are usually project-specific
Nuki has quit [Remote host closed the connection]
tlockney_away is now known as tlockney
<adrien> (I said you'd re-use the host's ocamlbuild; you could build one that is specific to your cross-compilation target and with the right values but I see that as a kludge and not a solution)
<adrien> (but thinking about it now, the split of ocamlbuild from the distribution requires that the output of ocaml's configure be accessible outside of the compiler, preferably in a nice format; it would then be enough to have one such data store per configuration)
<AltGr> Time to go; bye !
AltGr has left #ocaml [#ocaml]
maattdd has quit [Ping timeout: 240 seconds]
<adrien> (although I tend to hate qmake's approach which is to create a file per configuration but with ocaml the file would be provided by the compiler)
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
maattdd has joined #ocaml
rand000 has quit [Ping timeout: 250 seconds]
<Drup> whitequark: ocp-build solve two issues of ocamlbuild : it's fast and the description language is not insane.
<Drup> (I didn't say it was sane either, but at least it's better)
<whitequark> Drup: I compare it with oasis though
<Drup> the issue is that, as soon as you have slightly not regular stuff with oasis, you will need to fiddle with ocamlbuild
zpe has quit [Ping timeout: 252 seconds]
<adrien> oasis' coverage is fairly good though
<Drup> *cough*
<whitequark> ah
<Drup> Docflags ?
<Drup> *cough cough*
* whitequark isn't really annoyed by ocamlbuild
<adrien> docwhat?
<adrien> documentation you mean?
<whitequark> I mean, it's way better than makefiles
<Drup> whitequark: that's not hard.
<adrien> heard that word sometimes but no idea what it means
<whitequark> Drup: I guess I have low standards
<Drup> (and ocp-build is really fast)
<Drup> it parallelizes properly and has a low overhead.
<adrien> (and Drup prefers to avoid discovery at runtime ;-) )
<Drup> (no kidding)
<adrien> (saying that because it's actually what the issues boils down to)
<Drup> (indeed :p)
manizzle has joined #ocaml
philtor has joined #ocaml
sheijk has quit [Ping timeout: 265 seconds]
Thooms has joined #ocaml
WraithM has quit [Ping timeout: 240 seconds]
<companion_cube> hm btw whitequark, why do I need to install camlp4 for your introduction to ppx?
<Drup> companion_cube: utop
<companion_cube> opam install camlp4 ocamlfind oasis ← don't see no utop :p
nicoo_ has joined #ocaml
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<whitequark> companion_cube: oasis
<whitequark> uses type_conv
<whitequark> uses camlp4
<companion_cube> ah
<companion_cube> :/
<Drup> oh, right, type_conv ..
<whitequark> it's kinda ironic
<adrien> oasis uses type_conv?
<whitequark> I don't even know why, but it pulls a whole bunch of dependencies
nikki93 has joined #ocaml
nicoo has quit [*.net *.split]
tnguyen has quit [Ping timeout: 255 seconds]
Eyyub has joined #ocaml
nicoo_ is now known as nicoo
maattdd has quit [Ping timeout: 258 seconds]
ygrek has joined #ocaml
ygrek has quit [Remote host closed the connection]
Kakadu has joined #ocaml
zpe has joined #ocaml
manizzle has quit [Remote host closed the connection]
<companion_cube> whitequark: did you have to pin utop to have it compile on 4.02 ?
<whitequark> yes
<whitequark> in fact, I contributed the patch that made it compile...
<companion_cube> does it still work with the current state of the compiler? :s
Eyyub has quit [Ping timeout: 255 seconds]
<ggole> Sigh, screwed by type constructor arity once again
ontologiae has joined #ocaml
<whitequark> companion_cube: it does
<whitequark> ggole: in modules?
<ggole> It's Set.Make again
<ggole> Of course
<whitequark> ok
igitoor has quit [Ping timeout: 245 seconds]
<whitequark> let's implement mrvn's proposal
<whitequark> module ['a] = Set.Make(sig type 'a t end)
<whitequark> or how was it
philtor has quit [Ping timeout: 265 seconds]
zarul has quit [Ping timeout: 258 seconds]
<whitequark> sounds like a fairly trivial addition to typechecker
ontologiae has quit [Ping timeout: 265 seconds]
pango has joined #ocaml
<adrien> gasche: I can't believe you find bootstrap not awful to do :)
<ggole> It would be nice not to have to work around the type checker
<Drup> whitequark: there is no such thing as a "fairly trivial addition to typechecker"
<Drup> that works for any non trivial typechecker
<whitequark> gasche: I was about to say that
<whitequark> errr Drup ^
igitoor has joined #ocaml
bjorkintosh has quit [Ping timeout: 240 seconds]
<whitequark> but I mean, it could be worse
<whitequark> \o/ Gerd replied to my musings about findlib and ppx
<adrien> gasche: haha, saw you "temporary bootstrap" :D
Eyyub has joined #ocaml
<Drup> whitequark: oh, where ? what is the answer ?
<whitequark> via email
<whitequark> well, -syntax should just look first for preprocessor = ..., then for ppx =, and pass the appropriate option
<whitequark> nothing too complex
<whitequark> I'll implement it when I have time
igitoor has quit [Changing host]
igitoor has joined #ocaml
WraithM has joined #ocaml
tnguyen has joined #ocaml
manizzle has joined #ocaml
tnguyen has quit [Ping timeout: 255 seconds]
sheijk has joined #ocaml
<ggole> Obj.magic to the rescue
Eyyub has quit [Ping timeout: 240 seconds]
maattdd has joined #ocaml
sheijk_ has joined #ocaml
tobiasBora has joined #ocaml
divyanshu has joined #ocaml
sheijk has quit [Ping timeout: 255 seconds]
philtor has joined #ocaml
rand000 has joined #ocaml
bjorkintosh has joined #ocaml
chris2 has quit [Ping timeout: 240 seconds]
<jpdeplaix> Drup: if ocamlbuild is separated from trunk, there will be a lot of improvements and it can catch up with ocp-build (and other build systems)
<rks`> jpdeplaix: how can you be so sure?
<rks`> it's easy to list things that need to be done
<rks`> harder to get the manpower
ikaros has quit [Quit: Ex-Chat]
<rks`> ("noshit" right)
<jpdeplaix> hhugo and gildor seem very enthusiasts
<jpdeplaix> (as well as avsm)
<companion_cube> Failure("Ast_mapper: unknown magic number")
<companion_cube> meh :(
<whitequark> companion_cube: hmm? seems like an odd error
<whitequark> show me your compiler invocation
<smondet_> hi I was reading JsStreet's blog post (https://blogs.janestreet.com/better-namespaces-through-module-aliases/), it says that an aliased module will be linked-in only if actually used, but a module that has toplevel code (like `let () = bouh ()`), will it be linked-in or dropped?
<whitequark> and make sure you use the right ocamlc version to invoke ppx
<companion_cube> ocamlfind ocamlopt -package compiler-libs.common -linkpkg ppx_mapper.ml -o ppx_mapper
ontologiae has joined #ocaml
<companion_cube> ocamlc -dsource -ppx ppx_mapper foo.ml
<companion_cube> oh man, it was ./ppx_mapper
<whitequark> yep
<companion_cube> the error message is cryptic...
<Drup> smondet_: probably linked
<Drup> at least it's how it's working right now
<whitequark> companion_cube: PR6413
edwin3 has joined #ocaml
<companion_cube> wow, thanks
<companion_cube> (although I'd think you'd put it on github)
<whitequark> eh? Ast_mapper is part of ocaml, not ppx_tools
<companion_cube> the github mirror of ocaml :)
Arsenik has joined #ocaml
<whitequark> though in hindsight, modifying the error message does not actually require recompiling the compiler and verifying that it works
<whitequark> I could as well send a PR
<whitequark> hang on
<whitequark> done
chris2 has joined #ocaml
<whitequark> although in hindsight again, merging a PR via GH is probably more bothersome for maintainers than just changing the damn string
<whitequark> I think I need to sleep.
tani has quit [Quit: Verlassend]
_andre has quit [Quit: leaving]
divyanshu has quit [Quit: Computer has gone to sleep.]
tnguyen has joined #ocaml
<Drup> whitequark: can I apply iter_uses on the underlying value of a block ?
<whitequark> on any llvalue
<Drup> ok
<whitequark> it's... less type-unsafe than you think
axiles has quit [Remote host closed the connection]
<whitequark> really, it's just that constructors verify invariants with asserts
<Drup> well, verifying invariants with asserts answer my definition of type unsafety :p
alinab has joined #ocaml
<Drup> whitequark: for answer, what is happening if I ask for the operands of a basic block, or a function ?
<Drup> for example* ~_~
<ggole> Module code is so bureaucratic and unflowing :/
<whitequark> oh.
<whitequark> that'll explode.
<Drup> exactly.
<whitequark> well
<Drup> whitequark: similarly, if I want to retrive the operand of an instruction
<whitequark> LLVM doesn't use exceptions, and annotating every single call with Error_or is insane
<Drup> I will have to cast all over the place
<whitequark> so there's not really a way to fix this
<Drup> sure there is
<whitequark> what is it?
<Drup> make a type "function" instead of having it a llvalue would be a start.
<whitequark> there are a lot of invariants which cannot be statically checked.
<Drup> and make sure that the call that should return a basicblock actually return a basic block, not a llvalue
<whitequark> LLVM has literally thousands of assertions
Arsenik has quit [Remote host closed the connection]
<Drup> whitequark: in C++ type system, I have no doubt about it.
<whitequark> no, in OCaml one as well
<whitequark> I mean, imagine OCaml without exceptions
<Drup> I'm not talking about exceptions.
<whitequark> LLVM doesn't use C++ exceptions because they're shit. that's the source of the problem you're observing.
<ggole> One advantage of making everything a value is that you can reuse the same code for numbering, etc
<whitequark> Drup: what I mean is that LLVM doesn't have any machinery to recover from an invariant violation
<Drup> ggole: the disadvantage is that your code explode all the time.
<whitequark> you can fix *some* of that with types
<Drup> whitequark: I'm still not talking about that
<whitequark> but not everything and probably not even most things
<ggole> Drup: it's C++, recovering from exploding is half the fun
<whitequark> Drup: having everything as llvalue is absolutely necessary, because there's a lot of operations generic for all llvalues
<whitequark> use-def tracking, for one
<Drup> whitequark: welcome to polymorphism.
<whitequark> it *may* be possible to make some crazy concoction with phantom types, but so far I've not seen something that would work
<ggole> I ran into that, actually
lostcuaz has joined #ocaml
lostcuaz has quit [Max SendQ exceeded]
<whitequark> someone (I think jpdeplaix?) had an experimental wrapper which added phantom types
<whitequark> it seemed horrible to me and I believe it was unable to handle some valid cases
<Drup> whitequark: and even without polymorphism, having cast for those specific operations is ok
<ggole> I had a design where control flow instructions and value producing instructions were different types, and it sucked
<Drup> whitequark: because downcasting is not an issue
<Drup> upcasting is.
<ggole> Then I tried to do it with GADTs
<ggole> And that was worse
<Drup> whitequark: transforming something into llvalue is safe
<Drup> the other way is not
<whitequark> let's say that I'm not convinced that by adding moar types to the LLVM OCaml API would make it better
<Drup> so every function should return the most specific type possible
<ggole> Then I just said fuck it and added some assertions, and that was OK. Apparently the LLVM people think the same way.
<whitequark> because while I agree that it's beneficial in theory, so far I've not seen a scheme that I consider better
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
<Drup> ggole: gadt is a specific tool to solve specific problems, if you try to apply it randomly, it doesn't work :)
<whitequark> your thing will probably require me to write a lot more junk to upcast everything everywhere
<whitequark> I'd rather have assertions and a testsuite (you'd need a testsuite anyway)
<Drup> whitequark: internally of the API ? yes
<Drup> externally ? no.
<whitequark> what's the signature of iter_uses?
<whitequark> in your scheme
<ggole> Drup: it's very close to the same problem
<Drup> the same, since it works on all llvalue
<whitequark> what's the signature of, say, create_basic_block ?
<whitequark> (though, it returns llbasicblock right now)
<Drup> :)
<ggole> You want to be able to say "this is an int instruction" and "this is a control flow instruction" and then, where GADTs kill you, "this is an 'a instruction"
<Drup> whitequark: my first change would be to create a type "llfunction" and replace all the "llvalue" by "llfunction" when appropriate
<ggole> Then you could type things like you want, and still have a sane interface for iter_uses.
<whitequark> anyway. the API is horrible, but changing it into a different kind of horrible doesn't help
<Drup> (on top of being safer, it would make the api a lot safer to understand)
<Drup> a lot easier*
<whitequark> hrm, it would also distance it from what LLVM exports...
* whitequark sighs
<whitequark> it's night and I'm going to sleep
<Drup> good night :)
<whitequark> o/
zpe has quit [Ping timeout: 245 seconds]
lostcuaz has joined #ocaml
tautologico has joined #ocaml
<Drup> jpdeplaix: can you link to your llvm overlay ?
<companion_cube> good night whitequark
<jpdeplaix> Drup: which overlay ? For the phantom types ?
<Drup> yeah
<jpdeplaix> it was just an experiment. I don't have any public repository for this
<jpdeplaix> (it didn't work very well)
lostcuaz has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
racycle has quit [Ping timeout: 258 seconds]
racycle has joined #ocaml
malo has joined #ocaml
Eyyub has joined #ocaml
ggole has quit []
shinnya has joined #ocaml
smondet_ is now known as smondet
Thooms has quit [Quit: WeeChat 0.3.8]
wwilly has quit [Remote host closed the connection]
nikki93 has quit []
nikki93 has joined #ocaml
WraithM has quit [Ping timeout: 240 seconds]
edwin3 has quit [Remote host closed the connection]
fraggle_laptop has quit [Remote host closed the connection]
avsm has joined #ocaml
zpe has joined #ocaml
divyanshu has joined #ocaml
tlockney is now known as tlockney_away
zpe has quit [Ping timeout: 265 seconds]
rand000 has quit [Quit: leaving]
divyanshu has quit [Ping timeout: 265 seconds]
ollehar has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
jao has quit [Ping timeout: 276 seconds]
ollehar has quit [Client Quit]
tlockney_away is now known as tlockney
olauzon has quit [Ping timeout: 240 seconds]
Eyyub has quit [Ping timeout: 240 seconds]
Submarine has quit [Quit: Leaving]
tobiasBora has quit [Quit: Konversation terminated!]
Eyyub has joined #ocaml
tizoc has quit [Quit: Coyote finally caught me]
tizoc has joined #ocaml
divyanshu has joined #ocaml
tizoc has quit [Client Quit]
tizoc has joined #ocaml
zarul has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
darkf has joined #ocaml
tlockney is now known as tlockney_away
ontologiae has quit [Ping timeout: 240 seconds]
Nuki has joined #ocaml
maattdd has quit [Ping timeout: 276 seconds]
Simn has quit [Quit: Leaving]
avsm has quit [Quit: Leaving.]
madroach has quit [Ping timeout: 252 seconds]
madroach has joined #ocaml
Eyyub has quit [Ping timeout: 258 seconds]
pyon has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
lostcuaz has joined #ocaml
lostcuaz has quit [Client Quit]
lostcuaz has joined #ocaml
ontologiae has joined #ocaml
tautologico has quit [Quit: Connection closed for inactivity]
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
divyanshu has quit [Client Quit]
Eyyub has joined #ocaml
eikke__ has quit [Ping timeout: 250 seconds]
q66 has quit [Quit: Leaving]
tautologico has joined #ocaml