flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 4.01.0 http://bit.ly/1851A3R | http://www.ocaml.org | Public logs at http://tunes.org/~nef/logs/ocaml/
zarul has quit [Remote host closed the connection]
zpe has quit [Remote host closed the connection]
milosn has joined #ocaml
milosn_ has quit [Ping timeout: 245 seconds]
oriba has quit [Quit: oriba]
madroach has quit [Ping timeout: 264 seconds]
madroach has joined #ocaml
ygrek has joined #ocaml
talzeus has joined #ocaml
TDJACR has quit [Ping timeout: 260 seconds]
q66 has quit [Quit: Leaving]
ihm1 has joined #ocaml
ihm1 has quit [Client Quit]
ihm1 has joined #ocaml
Yang_ has joined #ocaml
ihm1 has quit [Quit: ihm1]
jpdeplaix has quit [Ping timeout: 245 seconds]
breakds has joined #ocaml
jpdeplaix has joined #ocaml
ygrek has quit [Ping timeout: 240 seconds]
yacks has quit [Ping timeout: 245 seconds]
ygrek has joined #ocaml
yacks has joined #ocaml
yacks has quit [Quit: Leaving]
chrisdotcode has quit [Ping timeout: 240 seconds]
ben_zen has quit [Ping timeout: 245 seconds]
chrisdotcode has joined #ocaml
csakatoku has joined #ocaml
Snark has joined #ocaml
ivan\ has quit [Ping timeout: 256 seconds]
Yoric has joined #ocaml
ulfdoz has joined #ocaml
ivan\ has joined #ocaml
ygrek has quit [Ping timeout: 264 seconds]
ulfdoz has quit [Ping timeout: 245 seconds]
<adrien> mornin
<adrien> g
Simn has joined #ocaml
wagle_ has joined #ocaml
breakds has quit [Remote host closed the connection]
Snark_ has joined #ocaml
Snark has quit [*.net *.split]
wagle has quit [*.net *.split]
djcoin has joined #ocaml
csakatok_ has joined #ocaml
mrvn_ has joined #ocaml
tov_ has joined #ocaml
whitequa1k has joined #ocaml
pr_ has joined #ocaml
csakatoku has quit [Ping timeout: 240 seconds]
habnabit has joined #ocaml
mrvn has quit [Ping timeout: 264 seconds]
whitequark has quit [Ping timeout: 264 seconds]
_habnabit has quit [Ping timeout: 264 seconds]
pr has quit [Ping timeout: 264 seconds]
vpm has quit [Ping timeout: 264 seconds]
cdidd has quit [Ping timeout: 264 seconds]
tov has quit [Ping timeout: 264 seconds]
tizoc has quit [Ping timeout: 264 seconds]
cdidd has joined #ocaml
tizoc has joined #ocaml
lopex_ has joined #ocaml
vpm has joined #ocaml
Snark has joined #ocaml
gasche_ has joined #ocaml
xenocons_ has joined #ocaml
lopex has quit [Ping timeout: 245 seconds]
skunkwerks has quit [Ping timeout: 245 seconds]
xenocons has quit [Ping timeout: 245 seconds]
lenstr has quit [Ping timeout: 245 seconds]
smondet has quit [Ping timeout: 245 seconds]
Snark_ has quit [Ping timeout: 245 seconds]
gasche has quit [Ping timeout: 245 seconds]
ccasin has quit [Ping timeout: 245 seconds]
brendan has quit [Ping timeout: 245 seconds]
lopex_ is now known as lopex
ccasin has joined #ocaml
ggherdov has quit [Ping timeout: 245 seconds]
LeNsTR|away has joined #ocaml
levi has quit [Ping timeout: 245 seconds]
lopex is now known as Guest40967
brendan has joined #ocaml
ttamttam has joined #ocaml
gour has joined #ocaml
Neros has quit [Ping timeout: 276 seconds]
ggherdov has joined #ocaml
thomasga has joined #ocaml
ontologiae_ has joined #ocaml
ygrek has joined #ocaml
ttamttam has quit [Quit: ttamttam]
ttamttam has joined #ocaml
yezariaely has joined #ocaml
levi has joined #ocaml
Guest40967 has quit [Changing host]
Guest40967 has joined #ocaml
ggherdov has quit [Changing host]
ggherdov has joined #ocaml
ontologiae_ has quit [Ping timeout: 264 seconds]
mika1 has joined #ocaml
kaka22 has joined #ocaml
<kaka22> hi guys
<kaka22> what is the best way to check if a list contains a particular value?
<flux> List.mem 42 [1; 4; 42]
<kaka22> this returns True/False, right?
<flux> yes (though it's called true/false in OCaml; I suppose it's an exception to the rule)
ontologiae_ has joined #ocaml
<kaka22> flux: i write this code, but ocaml complains:
<kaka22> if not (List.mem x mylist) then
<kaka22> what is wrong here?
<kaka22> .. Error: This expression is not a function; it cannot be applied ...
<kaka22> that is the error for above line of code
<Snark> the parenthesis
<Snark> hmmm... no, that is working...
<kaka22> so?
LeNsTR|away is now known as lenstr
lenstr has quit [Changing host]
lenstr has joined #ocaml
<flux> works for me(TM) :-) let x = 42 in let mylist = [42] in if not (List.mem x mylist) then Printf.printf "Yes!\n";;
<Snark> yes, I tried that too :-/
<flux> I think the only way that would not work would be that you have shadowed not
<flux> let not = 42
Kakadu has joined #ocaml
<kaka22> sorry i found the problem: i missed ; in the line above that code. ocaml compiler error is pretty useless
<kaka22> another question: on List.iter, i have code like this:
<kaka22> List.iter myfunc mylist
<flux> ok..
<kaka22> this is OK, but now i want to have "myfunc" with 1 argument, so i write code like this:
<kaka22> List.iter (myfunc x) mylist
<kaka22> is that alright?
<kaka22> myfunc is declared like:
<flux> sure, x is going to be myfunc's first argument and then the elements of mylist the second
<kaka22> let myfunc x list_member = ....
<kaka22> that is OK, isnt it?
<flux> yep
<kaka22> but then, i have the bug at the "List.mem" like:
<kaka22> Error: Unbound value x
<kaka22> i dont understand this error message :-?
<flux> we might communicate better if you put a full test case to a pastebin site :)
<kaka22> right, but the whole code is big, and i need sometime to extract out the relevant code ....
skunkwerks has joined #ocaml
<flux> unbound value x simply means you don't have x in current scope
skunkwerks is now known as dch
<flux> x;; in ocaml toplevel says the same error
<flux> maybe you have inadvertently truncated the function before the call to List.mem
<flux> an editor that automatically indents your code would probably show that easily
ollehar has joined #ocaml
<kaka22> hmm ok, then i have this question: how can i tell ocaml when my function terminates?
<kaka22> in C, i have {}
mort___ has joined #ocaml
<kaka22> this unbounded value x error might be due to ;; i put in the line above that List.mem check
<kaka22> so that might terminate the function, without my intention
<kaka22> but with single ;, i got error at List.mem line:
<kaka22> Error: This expression is not a function; it cannot be applied
<Kakadu> kaka22: in OCaml last expression in function body is it's result
<Kakadu> If you not sure you can wrap body into (...) or begin... end
<kaka22> kaka22: so that will be: let myfunc = begin ... end
<kaka22> ?
<Kakadu> very often you can avoid begin...end. You can use them if you are not sure how function body will be parsed
<kaka22> i guess i got the bug because i still write ocaml code like C code ....
<kaka22> so i have code like this:
<kaka22> printf "blah blah";
<kaka22> if not (List.mem xx yy) then (....)
<kaka22> and i got error:
<kaka22> Error: This expression is not a function; it cannot be applied
zarul has joined #ocaml
<kaka22> that is error at the second line above: if not ....
<kaka22> any idea?
<Kakadu> what column numbers are?
<kaka22> .... line 43, characters 41-404:
<Kakadu> what column 'if' starts?
<kaka22> that is after "(", i think
<Kakadu> If it is after '(' than code you provided is not useful
<kaka22> no, 41 is the column after "then", before "("
<Xuerian> I'm just watching and this hurts :D
<flux> kaka22, I think the key is what you have after the )
<Kakadu> maye you forgot ; after ')' ?
<flux> for example: if true then (Printf.printf "hello world") 42 would cause that
<Kakadu> maybe*
<kaka22> oh indeed ...
<kaka22> i missed ; after )
<kaka22> why i need ; after )??
<kaka22> so it should be: then (....);
<Kakadu> if you want to call a number of functions that return unit
<Kakadu> you write something like that
<Kakadu> let f () = f1(); f2(); f3(); f4
<Kakadu> ()
<Kakadu> Also you can write like
<Kakadu> let f () =
<Kakadu> let () = f1 () in
<Kakadu> let () = f2 () in
<Kakadu> let () = f3 () in
<Kakadu> f4 ()
<kaka22> thank guys!
<kaka22> still i am not quite sure when to use single semicolon, and when use double semicolon?
<flux> kaka22, you actually never need to use ;; in ocaml programs
<flux> kaka22, it is only for the benefit of using the toplevel
<flux> and telling it when to evaluate what you have written
<flux> kaka22, a program in ocaml is composed of phrases. a phrase is _either_ an expression _or_ a list of top-level statements.
<flux> expression is like Printf.printf "hello world" or let a = 4 in Printf.printf "a is equal to %d" a
<flux> a top-level statement is like let a = 42 (note there is no 'in', 'in' is only part of the expression form of 'let')
<flux> other top-level statements: type i = int module X = struct end open Unix
<flux> (actually top-level statement is maybe a misnomer, maybe a better name would be module-level statement)
<kaka22> toplevel indicates the ocaml interpretor, right?
<flux> I mean the topmost indentation level of the code
<flux> ie. not inside a function
<flux> or inside an expression
<Xuerian> where main goes D:
<flux> but as I said in parenthesis, you can put them inside other modules
<flux> module X = struct let a = 42 end
<kaka22> flux: ok it is clearer for me now, thanks!
wagle_ is now known as wagle
weie_ has joined #ocaml
weie has quit [Ping timeout: 240 seconds]
djcoin has quit [Quit: WeeChat 0.4.0]
djcoin has joined #ocaml
dsheets has quit [Ping timeout: 245 seconds]
yacks has joined #ocaml
kaka22 has quit [Quit: Leaving]
asmanur has quit [Read error: Operation timed out]
dsheets has joined #ocaml
asmanur has joined #ocaml
<gour> /j #compass
Obfuscate has quit [Ping timeout: 246 seconds]
Obfuscate has joined #ocaml
Yoric has quit [Ping timeout: 276 seconds]
weie has joined #ocaml
weie_ has quit [Ping timeout: 245 seconds]
tianon has quit [Ping timeout: 268 seconds]
beckerb has joined #ocaml
q66 has joined #ocaml
oriba has joined #ocaml
tianon has joined #ocaml
malo has joined #ocaml
<jyeo> does anyone know how to read cmt files?
<jyeo> it looks like some kind of binary file but i have no idea how to read it. >.<
<jyeo> do I need to include +compiler-libs?
<kerneis> jyeo: I think merlin uses .cmt, you could have a look at its implementation
<rks`> jyeo: you need to link with compiler libs yeah
<rks`> then you just use Cmt_format
<jyeo> rks`: how do I do that? I tried to do utop -I +compiler-libs but I can't open Cmt format
<rks`> err
<rks`> I don't know :)
<rks`> but I'd use findlib if I were you
<jyeo> hmmm k...
<rks`> ( #require "compiler-libs" )
<rks`> (utop should offer completion after #require "...)
<rks`> and then you should be able to open :)
<jyeo> thanks! got it
<jyeo> yup i did a #require "compiler-libs";;
mrvn_ is now known as mrvn
yacks has quit [Ping timeout: 276 seconds]
oriba has quit [Quit: oriba]
Guest40967 is now known as lopex
tom39341 has joined #ocaml
Yoric has joined #ocaml
oriba has joined #ocaml
yezariaely has quit [Ping timeout: 264 seconds]
<Kakadu> A question about camlp4 parsers
<Kakadu> I want to do specific action when stream has at least 2 elements and another one if it has only 1
<Kakadu> but if I write [< a; b >] above [< a >] 1st parser seems not backtracking and give error
Drup has joined #ocaml
<Kakadu> Can I express end_of_stream somehow
<Kakadu> ?
<Kakadu> or maybe I can do parser inside another parser?
<flux> hmm, if you mean the stream parsing extension, it doesn't do back tracking at all
whitequa1k is now known as whitequark
snearch has joined #ocaml
darkf has quit [Quit: Leaving]
<jyeo> I'm getting a Error: No implementations provided for the following modules:
<jyeo> Cmt_format referenced from get_types.cmx
<jyeo> Am I missing something?
<jyeo> I am trying to do a open Cmt_format in my code but I can't seem to link the compiler-libs
Neros has joined #ocaml
ollehar has quit [Ping timeout: 246 seconds]
Drup has quit [Ping timeout: 276 seconds]
csakatok_ has quit [Remote host closed the connection]
<jyeo> it's okay. i got it. :)
ben_zen has joined #ocaml
Yang_ has quit [Read error: Connection reset by peer]
Yang_ has joined #ocaml
Neros has quit [Ping timeout: 240 seconds]
Drup has joined #ocaml
yezariaely has joined #ocaml
_andre has joined #ocaml
Neros has joined #ocaml
oriba has quit [Quit: oriba]
rwmjones has quit [Ping timeout: 264 seconds]
ygrek has quit [Ping timeout: 264 seconds]
ollehar has joined #ocaml
djcoin has quit [Quit: WeeChat 0.4.0]
djcoin has joined #ocaml
<kerneis> gasche_: ping
ggole has joined #ocaml
rwmjones has joined #ocaml
cdidd has quit [Ping timeout: 264 seconds]
Neros has quit [Ping timeout: 240 seconds]
ttamttam has quit [Ping timeout: 240 seconds]
yacks has joined #ocaml
Yang_ has quit [Read error: Connection timed out]
Yang_ has joined #ocaml
walter|r has quit [Quit: Leaving]
snearch has quit [Quit: Verlassend]
yezariaely has quit [Quit: Leaving.]
djcoin has quit [Quit: WeeChat 0.4.1]
djcoin has joined #ocaml
ben_zen has quit [Ping timeout: 245 seconds]
ttamttam has joined #ocaml
talzeus has quit [Remote host closed the connection]
djcoin has quit [Quit: WeeChat 0.4.1]
<flux> it is sort of cool that it works nowadays: type t = true of int | false;; true 42;; (true : bool);;
<flux> I really should find some time to code ocaml..
<flux> sadly it doesn't infer (true : bool) from the arguments :-)
<flux> also it works like type t = true of int;; false = true;;
<flux> (but not true = false;;)
<flux> so it's a bit fragile..
<whitequark> uh
<whitequark> what?..
<flux> whitequark, the type-directed constructor name resolution
<whitequark> what's up with true/false?
<flux> they are just fun builtin constructor names
<whitequark> oh, I see
ollehar has quit [Read error: Operation timed out]
ollehar has joined #ocaml
davidbe has joined #ocaml
davidbe has quit [Remote host closed the connection]
davidbe has joined #ocaml
q66 has quit [Read error: Connection reset by peer]
q66 has joined #ocaml
Xom has joined #ocaml
breakds has joined #ocaml
malo has quit [Ping timeout: 268 seconds]
malo has joined #ocaml
breakds has quit [Quit: Konversation terminated!]
ollehar has quit [Ping timeout: 245 seconds]
djcoin has joined #ocaml
tane has joined #ocaml
zpe has joined #ocaml
djcoin has quit [Quit: WeeChat 0.4.1]
djcoin has joined #ocaml
Neros has joined #ocaml
gour has quit [Disconnected by services]
gour_ has joined #ocaml
smondet has joined #ocaml
Armael has quit [Ping timeout: 246 seconds]
Khady has quit [Ping timeout: 248 seconds]
Neros_ has joined #ocaml
Neros has quit [Ping timeout: 264 seconds]
NaCl has quit [Ping timeout: 248 seconds]
NaCl has joined #ocaml
NaCl has quit [Changing host]
NaCl has joined #ocaml
ollehar has joined #ocaml
nlucaroni has joined #ocaml
Neros has joined #ocaml
talzeus has joined #ocaml
Neros_ has quit [Ping timeout: 260 seconds]
tobiasBora has joined #ocaml
dsheets has quit [Ping timeout: 245 seconds]
<ontologiae_> hi
<ontologiae_> anyone has know a simple way to get the ast tree from an ast, in a toplevel ?
<ontologiae_> from a cmt
davidbe has quit [Remote host closed the connection]
weie has quit [Quit: Leaving...]
mort___ has left #ocaml []
gour_ is now known as gour
mika1 has quit [Quit: Leaving.]
ontologiae_ has quit [Ping timeout: 245 seconds]
ttamttam has quit [Quit: ttamttam]
weie has joined #ocaml
dsheets has joined #ocaml
Neros has quit [Ping timeout: 245 seconds]
Drup has quit [Ping timeout: 268 seconds]
malo has quit [Quit: Leaving]
Yoric has quit [Ping timeout: 245 seconds]
Neros has joined #ocaml
Kakadu has quit []
Drup has joined #ocaml
habnabit is now known as _habnabit
yacks has quit [Quit: Leaving]
dsheets has quit [Ping timeout: 264 seconds]
dlovell has joined #ocaml
Armael has joined #ocaml
ollehar has quit [Ping timeout: 260 seconds]
ollehar has joined #ocaml
ontologiae_ has joined #ocaml
<pippijn> has anyone got merlin to compile?
<pippijn> I did "opam install merlin" and it said:
<pippijn> File "src/chunk_parser.ml", line 448, characters 38-39:
<pippijn> Error: Syntax error
<pippijn> oh, I know..
<pippijn> my fault
iZsh has quit [Excess Flood]
iZsh has joined #ocaml
<rks`> :D
<rks`> pippijn: what was the problem?
<rks`> (or rather: the source of the problem)
ontologiae_ has quit [Read error: No route to host]
jgw25 has joined #ocaml
<jgw25> I'm doing some videos on simple OCaml. Here's the test one: https://vimeo.com/74728650 (Turn on HD)
<jgw25> Before I do thirty or forty, any comments are appreciated, so I can fix audio & video problems.
<jgw25> And, of course, content problems!
mcclurmc has joined #ocaml
djcoin has quit [Quit: WeeChat 0.4.1]
<gasche_> kerneis: asynchrony is futile
<gasche_> hm
<gasche_> I meant synchrony
<gasche_> asynchrony is the bomb
ygrek has joined #ocaml
<gasche_> (synchronicity?0
<adrien> sync/async :)
<adrien> synchronousness, even though that sounds like "bravitude" :)
* gour is reading ocaml't site tutorials and 'discovered' about ocaml's module signatures...cok
<gour> *cool
Yang_ has quit [Read error: Connection reset by peer]
Yang_ has joined #ocaml
dkg_ has joined #ocaml
<dkg_> i have a 2-tuple (a pair) in a variable named foo, and i want to refer to just the second part -- is there a simple way to refer to it or do i have to do something like (fun (a,b) -> b) foo ?
<ggole> snd pair
<ggole> Or let _, b = pair in ...
<ggole> jgw25: hmm, pen and paper is a pretty good medium for a video if your handwriting is neat enough.
<dkg_> ggole: thx
* pippijn is annoyed by menhir
<ggole> jgw25: video and audio seem pretty good. It might be worthwhile to get a thicker pen though.
<jgw25> Yes, I wondered about a thicker pen. It's ok here in full screen, but not in a window.
<pippijn> they don't have a source repository, so merging their changes back into my fork is a semi-annual effort, which so far always turned out to be re-doing my changes
ollehar1 has joined #ocaml
beckerb has quit [Ping timeout: 240 seconds]
osa1 has joined #ocaml
madroach has quit [Quit: leaving]
<osa1> does anyone here use LLVM bindings of OCaml? I just updated my LLVM installation with the latest HEAD (and reinstalled OCaml bindings also) but now I'm getting ld errors while compiling to native(and compilation to bytecode works but fails in runtime)
tobiasBora has quit [Ping timeout: 264 seconds]
dkg_ is now known as dkg
<dkg> Parse error: [fun_binding] expected after [ipatt] (in [let_binding])
<dkg> i'm having trouble understanding the above message
madroach has joined #ocaml
<adrien> rwmjones: but it's a JVM :D
<jpdeplaix> pippijn: ahahah. Did you saw my request on the menhir-list some days ago ? Francois did just answered to me (not to the list) and this will not happen soon « Maybe someday » :D
osa1 has left #ocaml []
ollehar has quit [Ping timeout: 245 seconds]
mcclurmc has quit [Quit: Leaving.]
<dkg> i get "Parse error: [match_case] expected after "function" (in [expr])" in the second line of https://paste.debian.net/hidden/ae220ece/ -- can someone explain what i'm doing wrong?
<dkg> i'm trying to write a function that returns another function
zpe has quit [Remote host closed the connection]
<Drup> dkg: sig is a key word
<Drup> you can't use it as an argument
<Drup> trust the coloration on this ;)
<mrvn> use signature or gpg_sig
<mrvn> Also ocaml automatically handles partial application: let sig_has_issuer issuer gpg_sig = match ...
<mrvn> returning a function like that would only make sense when you compute something once you get the issuer argument.
tobiasBora has joined #ocaml
<dkg> Drup: ah, thank you :)
Yoric has joined #ocaml
Khady has joined #ocaml
ygrek has quit [Ping timeout: 256 seconds]
tobiasBora has quit [Quit: Konversation terminated!]
Yoric has quit [Ping timeout: 240 seconds]
<pippijn> jpdeplaix: I didn't see (I'm not subscribed)
Yoric has joined #ocaml
<pippijn> jpdeplaix: he doesn't seem to be interested in merging my changes into his code
zpe has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
<pippijn> I think -bin-annot runs into an infinite loop here
jgw25 has quit [Quit: Page closed]
<whitequark> let's just fork menhir completely and for all
yacks has joined #ocaml
<rks`> pippijn: hm?
<pippijn> rks`: about what?
<rks`> -bin-annot
<pippijn> yes
<rks`> can I have some context?
<rks`> (please)
<pippijn> I killed the process after 5 minutes
<rks`> huhu
<rks`> what were you compiling?
<pippijn> I'll make a testcase
<dkg> i have two files: fingerprint.ml contains "type result { fingerprint: string ; keyid: string }" and defines a function from_packet that returns one of these. in keyMerge.ml, i'm trying to say "(from_packet pkt).keyid" to get a string, but ocaml tells me "Unbound record field label keyid"
<dkg> what am i doing wrong?
<jpdeplaix> dkg: it's « (from_packet pkt).Fingerprint.keyid »
<jpdeplaix> you have to name the module in which is the record field
Snark has quit [Quit: leaving]
zpe has joined #ocaml
<dkg> jpdeplaix: hm, ok, that's a bit confusing, but when i try it, the build does get farther along... but fails at the final ocamlopt part of the build process with :
<dkg> Error: No implementations provided for the following modules: Fingerprint referenced from keyMerge.cmx
<pippijn> rks`: ok
<rks`> why do you say ok?
<rks`> I didn't say anything, I'm waiting to see your test case :)
<pippijn> rks`: I'm uplodading (umts is slow)
<pippijn> uploading* (I#m lagging now9
* pippijn gives up
zpe has quit [Remote host closed the connection]
<pippijn> it's quite big, many files
<pippijn> I don't have time to reduce it
<pippijn> maybe it doesn't loop forever, but just takes more than 5 minutes
<jpdeplaix> dkg: how did you compiled that ?
<rks`> pippijn: but you're quite sure it's related to -bin-annot ?
<pippijn> rks`: cat reproduce.sh
<rks`> I'll have a look :)
<rks`> (I'll probably eat first though, so don't expect to ear back from me before a short while)
<pippijn> this is reproduce.sh:
<pippijn> ocamlbuild c_parser.cmx
<pippijn> cd _build
<pippijn> ocamlopt -bin-annot -c -o c_parser.cmx c_parser.ml
tobiasBora has joined #ocaml
<pippijn> so yes, I'm pretty sure
<dkg> jpdeplaix: the build system that i'm using is inherited from upstream; i did "make clean && make dep && make" -- this appears to run ocamldep, followed by a lot of ocamlc and ocamlopt invocations
<pippijn> ocamlbuild works fine
<dkg> jpdeplaix: i can pastebin a build log if that would be useful
<pippijn> adding -bin-annot doesn't work fine
<rks`> right.
<rks`> interesting
<dkg> jpdeplaix: build log: https://paste.debian.net/hidden/585dba19/
<jpdeplaix> dkg: what kind of « upstream build system » is this ? did you tried ocamlbuild ?
speredenn has joined #ocaml
jayprich has joined #ocaml
<dkg> jpdeplaix: no, i have not tried ocamlbuild
thomasga has quit [Quit: Leaving.]
<dkg> the upstream is https://bitbucket.org/skskeyserver/sks-keyserver/, which appears to use GNU Make
<jpdeplaix> dkg: I'd advise you to try ocamlbuild, but the compilation problem seems to be related to the order of the files during linking
<jpdeplaix> mmh are you forking or making a patch for this ?
<dkg> i'm patching
<dkg> i'm really really hoping to not fork
<dkg> even if i could afford the time to maintain an isolated fork, the nature of sks (global internet-wide peered gossiping infrastructure) would make a fork disastrous
<dkg> jpdeplaix: the link order was what i needed, thanks!
<dkg> that did it :)
<dkg> i'm slowly starting to map the concepts i'm familiar with to their counterparts (or pseudo-counterparts) in the ocaml world. your pointers were very helpful, thanks.
ollehar has joined #ocaml
darkf has joined #ocaml
darkf has quit [Changing host]
darkf has joined #ocaml
darkf has quit [Read error: Connection reset by peer]
darkf has joined #ocaml
ollehar1 has quit [Ping timeout: 245 seconds]
<jpdeplaix> dkg: you're welcome
<kerneis> gasche_: I just heard you might be around; is the info reliable?
<kerneis> RTT is not a problem if space-time trajectories cross in the end
ben_zen has joined #ocaml
Yang__ has joined #ocaml
Yang_ has quit [Ping timeout: 245 seconds]
so has quit [Ping timeout: 268 seconds]
so has joined #ocaml
ggole has quit []
dch has left #ocaml []
Yoric has quit [Ping timeout: 264 seconds]
speredenn has quit [Quit: Leaving]
deltaluca has joined #ocaml
<deltaluca> Shorter way to write: List.fold_left (fun f g -> (fun x -> g (f x))) (fun x -> x) anyone? :P
zpe has joined #ocaml
<darkf> deltaluca: (fun f g x -> g (f x)) for one
<deltaluca> right. thanks
pkrnj has joined #ocaml
tani has joined #ocaml
tane has quit [Ping timeout: 245 seconds]
<kerneis> also, define once and for good composition and identity
<kerneis> they, it's nothing more than List.fold_left (g o f) id
<kerneis> oh no, I'm so wrong
<kerneis> sorry
<kerneis> List.fold_left (o) id
<kerneis> even shorter in fact
tdammers has joined #ocaml
<nlucaroni> ... and you wouldn't need the parens around 'o'.
<kerneis> hmm, I would probably not call it o in fact
<kerneis> and it might be backwards in that case, you probably need fold_right
<nlucaroni> o isn't infix so i doubt you would as well.
<rks`> kerneis: https://github.com/def-lkb/merlin/wiki/vim-from-scratch it's a work in progress, but if you have any comment to make I'd appreciate it
_andre has quit [Quit: leaving]
<nlucaroni> I haven't played with merlin but it looks nice. I'll give this a shot later.
<rks`> :)
<nlucaroni> I've bene using ocp-indent and ocamlspotter, and wildmenu for "completion".
<deltaluca> kerneis, not quite
<deltaluca> it'd be List.fold_left (flip o) id
<rks`> nlucaroni: ocp-indent... with vim?
<rgrinberg> rks`: i can confirm that i use ocp-indent with vim as well
<rgrinberg> works good
<nlucaroni> yeah, with vim.
<rks`> rgrinberg: what do you mean by "works good"? do you have "automatic" indentation?
<rks`> (i.e. when I hit ENTER will it indent the line properly?)
<rks`> (or when I hit "tab" as in emacs)
<rks`> or how does it work?
<nlucaroni> highlight and auto-indent, but it isn't smart.
<rgrinberg> rks`: I do
<rks`> hmm
<nlucaroni> rgrinberg; those aren't smart indentation, but for indenting selected text.
<def-lkb> at one point a I had "smart" indentation with a custom build of ocp-indent, but I did not maintain it
<def-lkb> I will give it another try if I have more spare time
<jpdeplaix> rks`: is that merlin now manages 4.01 and 4.00 in the same branch ?
<rgrinberg> def-lkb: Yes I remember that it broke with ocp-indent 1.2 i believe
<rks`> nlucaroni: yes, that's what I thought.
<rks`> jpdeplaix: yes, it does since... well, yesterday
<jpdeplaix> good :)
<def-lkb> selected at compile time though
<rgrinberg> nlucaroni: oh my bad I hadn't noticed actually
deltaluca has left #ocaml []
<nlucaroni> the setting in vim with some old ident/ocaml config works 90%+ of the time for me.
<kerneis> def-lkb: we still need :helptags for the opam version
<rks`> kerneis: I believe you were talking to me
<rks`> and... that is true
<jpdeplaix> def-lkb: why macros was not sufficient ?
<def-lkb> jpdeplaix: sorry ?
<kerneis> hmm, sorry indeed
<def-lkb> :P
<jpdeplaix> def-lkb: I'm looking at the code and I'm seeing the usage of git submodules instead of just add some macros like here: https://github.com/ocsigen/deriving/commit/48d3fb8393cc75f669853c8278e393848fe1dfad
dezzy has quit [Read error: Connection reset by peer]
dezzy has joined #ocaml
<def-lkb> jpdeplaix: we need an efficient workflow for maintaining two typers
<def-lkb> jpdeplaix: this setup allows nifty things like cherry-picking from one to the others, easily synchronizing with upstream typer, etc.
jayprich has quit [Quit: jayprich]
Yoric has joined #ocaml
Yang_ has joined #ocaml
gour has quit [Quit: WeeChat 0.4.1]
Yang__ has quit [Ping timeout: 260 seconds]
Simn has quit [Quit: Leaving]
tani has quit [Quit: Verlassend]
emmanuelux has joined #ocaml
<kerneis> rks`: for vim newbies, you should explain what <localleader> is (or give its default value at least); maybe in the 'basic config' TODO at the top
ollehar has quit [Quit: ollehar]
<rks`> I wasn't sure if it was necessary to explain that, but it makes sense ok
<rks`> (and no, I didn't plan on including it in the first part)
<rks`> I'll update with that tomorrow (and with the :helptags too)
<adrien> actually I didn't know about it
<adrien> well
<adrien> I had seen mentions of it but I wasn't using localleader
Drup has quit [Quit: Leaving.]
Yoric has quit [Quit: Instantbird 1.5a1pre -- http://www.instantbird.com]
rwmjones has quit [Ping timeout: 240 seconds]
<kerneis> same for me before merlin
<kerneis> hence the remark
<kerneis> good night everyone
<def-lkb> good night
<rks`> good night, thank you :)
ihm1 has joined #ocaml
rwmjones has joined #ocaml
pkrnj has quit [Ping timeout: 245 seconds]
zpe has quit [Remote host closed the connection]
thomasga has joined #ocaml
demonimin has quit [Ping timeout: 246 seconds]
demonimin has joined #ocaml
tristero has quit [Quit: tristero]
stomp has quit [Ping timeout: 245 seconds]
thomasga has quit [Quit: Leaving.]
stomp has joined #ocaml
chrisdotcode_ has joined #ocaml
chrisdotcode_ has quit [Remote host closed the connection]
chrisdotcode has quit [Ping timeout: 276 seconds]
rwmjones has quit [Ping timeout: 248 seconds]
tristero has joined #ocaml
zpe has joined #ocaml
rwmjones has joined #ocaml
zpe has quit [Ping timeout: 276 seconds]
weie has quit [Read error: Connection timed out]
weie has joined #ocaml
dsheets has joined #ocaml
Neros has quit [Quit: No Ping reply in 180 seconds.]
Neros has joined #ocaml
cdidd has joined #ocaml
ollehar has joined #ocaml
zpe has joined #ocaml
chrisdotcode has joined #ocaml
ohama has quit [Read error: Operation timed out]
zpe has quit [Ping timeout: 256 seconds]
tobiasBora has quit [Quit: Konversation terminated!]
ohama has joined #ocaml
ollehar has quit [Ping timeout: 260 seconds]
zpe has joined #ocaml
zpe has quit [Ping timeout: 248 seconds]