adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | Upcoming OCaml MOOC: https://huit.re/ocamlmooc | OCaml 4.03.0 release notes: http://ocaml.org/releases/4.03.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
wtetzner has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
silver has quit [Quit: rakede]
LiamGoodacre has quit [Ping timeout: 240 seconds]
wtetzner has quit [Remote host closed the connection]
shinnya has quit [Ping timeout: 260 seconds]
al-damiri has joined #ocaml
fluter has quit [Ping timeout: 250 seconds]
fluter has joined #ocaml
wtetzner has joined #ocaml
wtetzner has quit [Remote host closed the connection]
<Heasummn> I'm stuck, not in terms of syntax, but in terms of logic
govg has quit [Ping timeout: 240 seconds]
SilverKey has joined #ocaml
kushal has quit [Quit: Leaving]
SilverKey has quit [Quit: Halted.]
wtetzner has joined #ocaml
wtetzner has quit [Remote host closed the connection]
Nahra has quit [Read error: Connection reset by peer]
Nahra has joined #ocaml
fluter has quit [Ping timeout: 250 seconds]
cross has quit [Ping timeout: 276 seconds]
cross has joined #ocaml
<Heasummn> How can I pass flags to menhir using an oasis build?
<Heasummn> I want to enable incremental building, so I want to pass --table to menhir
alpen has quit [Ping timeout: 258 seconds]
fluter has joined #ocaml
alpen has joined #ocaml
fluter has quit [Ping timeout: 250 seconds]
MercurialAlchemi has joined #ocaml
tmtwd has joined #ocaml
rossberg_ has quit [Ping timeout: 264 seconds]
alpen has quit [Ping timeout: 258 seconds]
alpen has joined #ocaml
kushal has joined #ocaml
ygrek has quit [Ping timeout: 244 seconds]
alpen has quit [Ping timeout: 258 seconds]
rossberg_ has joined #ocaml
seangrove has quit [Ping timeout: 250 seconds]
alpen has joined #ocaml
govg has joined #ocaml
emmanueloga has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 244 seconds]
struk|desk has quit [Read error: Connection reset by peer]
al-damiri has quit [Quit: Connection closed for inactivity]
pierpa has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
Heasummn has quit [Ping timeout: 240 seconds]
hay207 has quit [Quit: Konversation terminated!]
MercurialAlchemi has joined #ocaml
hay207 has joined #ocaml
ygrek has joined #ocaml
bruce_r has quit [Ping timeout: 264 seconds]
SilverKey has joined #ocaml
tmtwd has quit [Ping timeout: 240 seconds]
lyxia has quit [Ping timeout: 252 seconds]
Simn has joined #ocaml
lyxia has joined #ocaml
bruce_r has joined #ocaml
lol-icon is now known as dong-le
mcc has quit [Quit: Connection closed for inactivity]
fluter has joined #ocaml
cr4ven has quit [Ping timeout: 244 seconds]
tmtwd has joined #ocaml
cr4ven has joined #ocaml
darkf has quit [Quit: Leaving]
<gasche> to pass menhir flags through ocamlbuild, use (-menhir "menhir --table") on the command-line on (flag ["menhir"; "ocaml"] (A "--table");) in myocamlbuild.ml
<gasche> s/command-line on/command-line or/
copy` has quit [Quit: Connection closed for inactivity]
tmtwd has quit [Ping timeout: 250 seconds]
kushal has quit [Ping timeout: 276 seconds]
pitastrudl has quit [Remote host closed the connection]
dexterph has joined #ocaml
AltGr has joined #ocaml
pitastrudl has joined #ocaml
zpe has joined #ocaml
freehck has joined #ocaml
ontologiae has joined #ocaml
tojom has joined #ocaml
Anarchos has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
kushal has joined #ocaml
ia0 has quit [Quit: reboot]
ia0 has joined #ocaml
tojom has left #ocaml [#ocaml]
ygrek has quit [Ping timeout: 250 seconds]
zpe has quit [Remote host closed the connection]
Submarine has quit [Remote host closed the connection]
zpe has joined #ocaml
infinity0 has quit [Ping timeout: 244 seconds]
infinity0 has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
tane has joined #ocaml
mcspud has quit [Ping timeout: 250 seconds]
Muzer has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
mcspud has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
sdothum has joined #ocaml
troydm has quit [Ping timeout: 244 seconds]
<ia0> is there a module in the stdlib that does struct type t = int let compare = Pervasive.compare let hash x = x let equal x y = x = y end ?
<mrvn> no
silver has joined #ocaml
mpenet has joined #ocaml
infinity0 has quit [Ping timeout: 244 seconds]
infinity0 has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
tani has joined #ocaml
tane has quit [Ping timeout: 244 seconds]
_andre has joined #ocaml
infinity0 has quit [Remote host closed the connection]
kaustuv has joined #ocaml
infinity0 has joined #ocaml
<ia0> mrvn: ok thanks!
<flux> however, I think many libraries do come with that, I'm just guessing Batteries has module Int that does that
kakadu has joined #ocaml
Anarchos has joined #ocaml
tani has quit [Quit: Verlassend]
tane has joined #ocaml
zpe has quit [Remote host closed the connection]
k1000 has quit [Ping timeout: 240 seconds]
ggole has joined #ocaml
<kakadu> Folks, I want to expose printing functions for my type to be used in `Printf.printf "%a"` and in `Format.printf "%a"`. How should I name them to be synchronized with everybody?
<kakadu> or maybe I should expose only `out_channel -> t -> bytes` and `formater -> t -> bytes`..?
clog has quit [Ping timeout: 250 seconds]
<ggole> For a type Module.t, Module.output, or for a longer name Module.output_name
<mrvn> same way ppx deriving does
<Drup> Kakadu: you expose only pp of type "Format.formatter -> t -> unit"
zpe has joined #ocaml
<kakadu> thanks, that make sense
<kakadu> Maybe I should always use Format module where I use Printf.................
k1000 has joined #ocaml
zpe has quit [Ping timeout: 265 seconds]
struk|desk has joined #ocaml
wolfcore has quit [Ping timeout: 244 seconds]
sepp2k has joined #ocaml
zpe has joined #ocaml
wolfcore has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
fraggle_ has joined #ocaml
elfring has joined #ocaml
govg has quit [Ping timeout: 276 seconds]
agarwal1975 has joined #ocaml
infinity0 has quit [Ping timeout: 244 seconds]
two_wheels has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<elfring> How much did the implementation change for the handling of key words like "match argument with" and "function" during OCaml evolution?
infinity0 has joined #ocaml
dhil has quit [Quit: Quit]
wtetzner has joined #ocaml
two_wheels has joined #ocaml
<ggole> Pattern matching compilation has gone through a few changes. (And function is just sugar for pattern matching.)
infinity0 is now known as Guest18573
Guest18573 has quit [Killed (weber.freenode.net (Nickname regained by services))]
infinity0 has joined #ocaml
kushal has quit [Quit: Leaving]
kushal has joined #ocaml
kushal has quit [Max SendQ exceeded]
picolino has joined #ocaml
kushal has joined #ocaml
willtor has joined #ocaml
clog has joined #ocaml
kushal has quit [Read error: Connection reset by peer]
Iwan_ has joined #ocaml
<willtor> Hey, all. Using Ubuntu 16.04. When I use "ocamlopt -c gen.ml" I get "Error: Unbound module Llvm". I installed the LLVM 3.8 dev package with opam...
<willtor> But I installed OCaml, a long time ago, using apt-get. Could it be confused where to look?
<adrien> try something like
<adrien> ocamlfind ocamlopt -packages llvm -c gen.ml
<adrien> (if I don't misremember)
fluter has quit [Ping timeout: 258 seconds]
kushal has joined #ocaml
<willtor> Doesn't know the option "-packages"
<adrien> willtor: sorry: -package
<adrien> and for the linking step you'll need to pass -linkpkg too
<willtor> Ooh. Okay. Thanks much!
<willtor> That's got it.
Simn has quit [Quit: Leaving]
soupault has joined #ocaml
rand__ has joined #ocaml
Iwan_ has quit [Ping timeout: 250 seconds]
govg has joined #ocaml
tvynr has quit [Ping timeout: 244 seconds]
govg has quit [Ping timeout: 265 seconds]
<adrien> :)
MercurialAlchemi has quit [Ping timeout: 265 seconds]
al-damiri has joined #ocaml
bruce_r has quit [Ping timeout: 264 seconds]
tane_ has joined #ocaml
tane has quit [Ping timeout: 260 seconds]
picolino has quit [Ping timeout: 240 seconds]
_y has quit [Ping timeout: 252 seconds]
<elfring> ggole: Would you like to point any source files out which were affected by the mentioned pattern matching evolution?
SilverKey has quit [Quit: Halted.]
picolino has joined #ocaml
_y has joined #ocaml
SpiceGuid has joined #ocaml
<ggole> Source files would usually be unaffected by a change of implementation
<elfring> ggole: Do source files usually belong to the implementation of an OCaml compiler?
<ggole> Are you asking which files in the compiler were changed?
<elfring> ggole: Yes. - Do I need to inspect affected source files myself?
<ggole> And see the associated history
tmtwd has joined #ocaml
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.40/20160120202951]]
tmtwd has quit [Ping timeout: 250 seconds]
shinnya has joined #ocaml
willtor has quit [Quit: BAM!]
seangrove has joined #ocaml
picolino has quit [Ping timeout: 240 seconds]
wtetzner has quit [Remote host closed the connection]
Algebr` has joined #ocaml
two_wheels has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
rand__ has quit [Quit: leaving]
MercurialAlchemi has joined #ocaml
slash^ has joined #ocaml
two_wheels has joined #ocaml
strykerkkd has joined #ocaml
SilverKey has joined #ocaml
dong-le has quit [Remote host closed the connection]
kushal has quit [Quit: Leaving]
copy` has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 244 seconds]
govg has joined #ocaml
dexterph has quit [Ping timeout: 250 seconds]
dexterph has joined #ocaml
<Algebr`> Okay....camlp4 seg faulting
<Algebr`> Code always seems to break when money is on the line
<Algebr`> Where should I even report this to? opam-repo?
fluter has joined #ocaml
Heasummn has joined #ocaml
ontologiae has quit [Ping timeout: 250 seconds]
<Heasummn> Is there some compilation of Ocaml errors and common solutions?
<Heasummn> I'm constantly getting errors that I've never encountered before, and don't know how to fix
<Algebr`> are they type errors?
<elfring> ggole: Thanks for the link to this Git repository.
<Heasummn> yeah
<Heasummn> This variant pattern is expected to have type exn. The constructor SyntaxError does not belong to type exn
<Algebr`> you're trying to pattern match on an exception?
<Heasummn> I moved the variant type SyntaxError from file a to file b, and just added an open to file B
<Heasummn> it worked before when it was in file a
<Algebr`> perhaps you have some name shadowing?
<Heasummn> can shadowing happen if I do something like this? A opens B and C. B opens C?
<Heasummn> It shouldn't right?
<elfring> Would you like to help further in distinguishing the side effects of these changes between compile and run time?
wtetzner has joined #ocaml
<Algebr`> doing an open can cause name shadowing
<ggole> Heasummn: open isn't transitive. It only makes names available unqualified, it does not include them in a module.
<ggole> (There's include for that.)
<Heasummn> Yeah alright, that's what I expected. So opening files in something wouldn't cause shadowing in another file
<Heasummn> Then there's no shadowing
<ggole> You can get shadowing, but not because of open.
<ggole> (I mean, not because of open inside the thing that you are opening.)
<ggole> Concretely: if you module M = struct let x = 0 end, open M, then you have shadowed any previous x. But module M = struct open X end, open M, you don't have to worry about X.
<ggole> Hope that's clear.
<Heasummn> Yeah there's no shadowing
<Heasummn> what else could cause that error?
wtetzner has quit [Ping timeout: 258 seconds]
fraggle-boate has quit [Remote host closed the connection]
fraggle-boate has joined #ocaml
<Heasummn> This variant pattern is expected to have type exn. The constructor does not belong to type exn
ggole has quit [Ping timeout: 252 seconds]
ggole has joined #ocaml
<Algebr`> not trying to be rude but the type error is pretty clear. Perhaps showing code would make it easier for others to help you
<Algebr`> the pattern match is expecting an exception and the thing you're matching on is not an exception
<Heasummn> alright
<Heasummn> let me post the stuff regarding the errors, that's just what causes it
<ggole> Looks like you've defined SyntaxError as a regular constructor
<ggole> You can only catch values of type exn
<Heasummn> module called Lexing*
<ggole> At a guess, open Error is making available unqualified a SyntaxError that is a regular constructor
<ggole> No, wait, those are different files.
<ggole> Try compiling with the identifier qualified (eg, Error.SyntaxError)
<Heasummn> Unbound Constructor Error.SyntaxError
<Heasummn> could it be the compilation step?
<Heasummn> I'm using oasis. I clean everything and then build
<Heasummn> relying on oasis to figure out dependencies and etc.
<ggole> Mmm.
<Drup> I doubt it
<ggole> I guess double check everything.
<Drup> but the code is too incomplete to answer
<ggole> It's hard to say from this much what's going on.
<Heasummn> one second
<Heasummn> https://github.com/heasummn/Crab This is the working version without Error.ml
pierpa has quit [Ping timeout: 276 seconds]
<Drup> and if you don't open and you qualify, like you did before ?
sh0t has quit [Remote host closed the connection]
<Heasummn> Unbound constructor
<Heasummn> there's something stranger
<Heasummn> Merlin isn't complaining about my use of Error in parse.ml
<Heasummn> but it is in crab.ml
<Drup> You do have the Error module in your list of modules in _oasis ?
<Heasummn> yeah
scarygelatin has quit [Read error: Connection reset by peer]
<Drup> and you redid oasis setup ?
<Heasummn> yep
<Heasummn> The run build script does all that
<Drup> please push in a branch
<Heasummn> alright
<Drup> ah, right core, give me at least 5 mins to install that
<Heasummn> I use core for one function. I will most likely replace it later
<Heasummn> you also need llvm
<Heasummn> to build
<Heasummn> for a side by side comparison
<Algebr`> using core for just one function might be overkill
<Heasummn> yeah
<Heasummn> side question, is there some Ocaml argument parser? Like argparse in python
<Algebr`> cmdliner
<Heasummn> cool
<Algebr`> and the stdlib comes with one too
<Drup> Heasummn: you should specify BuildDepends for the library too
<Heasummn> If Crab is a module, shouldn't the library automatically compile crab?
<Drup> (and your way of specifying ocamlbuild flags is not really right)
mcspud has quit [Ping timeout: 250 seconds]
<Heasummn> Drup, I wanted to use Incremental building with menhir, but ocamlbuild doesn't have that option, not easily
<Heasummn> so I have to manually use args
<Heasummn> hopefully that doesn't get removed, since that's an alpha feature
<Drup> I'm not sure what you mean by that
<Drup> but anyway, instead of NativeOpt and all that just, just add the things at the end of _tags, after the "OASIS END"
<Heasummn> oh those args
<Heasummn> yeah okay
<Drup> and it'll work just fine, and you can select specific files (so, only menhir generated code) to remove warnings on those
<Heasummn> I thought you were talking about XOCamlbuildExtraArgs
<Heasummn> ok
<Drup> Yes, it's also valid for your menhir flag, in fact
<Heasummn> I can just throw them in? or use them with true:
seangrove has quit [Ping timeout: 240 seconds]
<Drup> the later
<Heasummn> k
<Heasummn> any work with the error?
bruce_r has joined #ocaml
<Drup> just finished installing llvm
kakadu has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
<Drup> hum, it compiles fine for me ...
<Heasummn> really?
<Drup> yeah
<Heasummn> you ran ./run build?
<Drup> no, just "make"
<Heasummn> weird
<Heasummn> you did pull the failing branch right?
<Drup> it also compiles with ./run build
<Heasummn> cause using just make doesn't work
<Drup> sure it works, "oasis setup && make
<Heasummn> not for me
<Heasummn> same Unbound Constructor error
<Heasummn> you did clone the failing branch?
<Drup> do "git clean -dfx" and start again, you must have some leftover or something
<Algebr`> this one https://github.com/janestreet/ppx_type_conv/issues/4 is causing so much headache.
agarwal1975 has quit [Ping timeout: 240 seconds]
<Algebr`> rather, it means I can't use 4.03.0 :(
agarwal1975 has joined #ocaml
mcspud has joined #ocaml
<Heasummn> even after git clean -dfx
<Heasummn> not compiling
<Heasummn> git clean -dfx; oasis setup; make
seangrov` has joined #ocaml
<Heasummn> can you confirm that you have a file named src/error.ml?
<Drup> sure, the only changed I did was to nuke core out, to avoid having to compile ti
<Heasummn> what did you change?
<Drup> removed the open, fixed List.map, removed the other bits about file import just to test typechecking
<Drup> nothing significant
<Drup> List.iter*
<Heasummn> weird
<Heasummn> removing Core fixes it
<Heasummn> god damn
<Drup> really ? that's weird
<Drup> Oh
<Drup> there is an error module in core, isn't it ? and since you use open!, it doesn't warn
<Heasummn> I used open! to avoid conflicts with Menhir
<Heasummn> alright
<Heasummn> How can I specify to remove warnings only for Menhir?
<Heasummn> that way It'll warn me about stuff like this
<Drup> <path/to/the/merlin/file.*>: warn(...)
<Drup> in _tags
<Heasummn> alright
<Drup> menhir*
<Drup> bll~~
<Heasummn> path to the built version or path to the .mly file?
<Heasummn> build right?
kakadu has joined #ocaml
<Drup> neither, just use .* for extension
SilverKe_ has joined #ocaml
SilverKey has quit [Read error: Connection reset by peer]
<Heasummn> they're contained in two different folders
<Heasummn> nvm
<Drup> ah, no, never add the "_build" at the beginning
<Heasummn> oh ok
<Drup> ocamlbuild already know about that
Algebr` has quit [Remote host closed the connection]
<Heasummn> so <**/parser.*> ?
<Drup> you probably want to give the actual path
<Heasummn> <src/parser.*>?
dedgrant has joined #ocaml
AltGr has left #ocaml [#ocaml]
<Heasummn> yeah that works
<Heasummn> you said I could add the menhir flag within the _tags file?
<Drup> sure
<Heasummn> I get the error: Lexing error: Only ',' separated tags are alllowed.
<Heasummn> if I do: true: use_menhir, menhir, "menhir --table"
<Drup> isn't --table the default layout anyway ?
<Heasummn> not yet
<Heasummn> is it?
<Heasummn> let me see
<Heasummn> no
<Drup> oh, no, it isn't, because it's slower
<Heasummn> It allows nicer error handling
<Heasummn> I believe it's only heavier in memory, cause it needs to store a table
<Heasummn> anyway, is there no way to pass it in?
<Drup> I'm not sure
<Heasummn> alright, I'll just use the current method
<Drup> oh
<Drup> simply "table"
seangrov` has quit [Ping timeout: 258 seconds]
soupault has quit [Ping timeout: 258 seconds]
<Heasummn> true: table ?
<Drup> try it ^^'
<Heasummn> nope
<Heasummn> I read the ocamlbuild manual, there seems to be no other way
<Drup> :/
<Heasummn> Hopefully they don't remove ocamlbuild_more_args
<Drup> doubt it :)
tvynr has joined #ocaml
<Heasummn> thanks for all the help
<tvynr> Anyone have any idea how to check to see if two OCaml ASTs are equal?
<tvynr> We're writing a unit test for a code transformation library and it's failing on two ASTs that pretty-print to the same string.
agarwal1975 has quit [Quit: agarwal1975]
<Drup> you mean, Parsetree ?
<Heasummn> what does the AST consist of?
<Heasummn> like is it some Ocaml thing I don't know about, or is it a tree for your compiler/w/e
Anarchos has joined #ocaml
<tvynr> Yeah, the AST type defined in Parsetree of the OCaml compiler.
<Drup> tvynr: wild guess: locations ?
agarwal1975 has joined #ocaml
<tvynr> Sounds reasonable. But I'm assuming the compiler devs have to have some way of checking ASTs. (Maybe "hoping" is the better word to use.)
<Drup> as far as I know, no
<Drup> (because that's not useful at all at the parsetree level)
<Heasummn> Dumb question, but I want to split a library into two, what am I doing wrong. I made a new folder, added what I wanted to move into it, and access stuff inside of it as, "folder.Module". That's the correct way to do it right?
<ggole> tvynr: are you calling = on two trees?
<tvynr> Hm. I suppose there might be some PPX magic that'll allow me to create the appropriate equality routine...
<ggole> I was about to suggest that.
<tvynr> ggole: Yeah; we're pretty sure that's wrong.
<tvynr> ggole: I was just hoping that there'd be something for equality like there already is for pretty-printing (in Pprintast).
<ggole> You should be able to bind a couple of modules and convince ppx that comparing locations by equality should be (fun _ _ -> true)
<Drup> You can do it with ppx magic, yes
<Drup> I think I might have some code doing that hanging around
<tvynr> I'm assuming I'd need e.g. ppx_import to haul in the type declarations from the OCaml compiler's libraries. Not sure if ppx_import works with something for which you don't have the code, though. Really hoping to keep this as version independent as possible.
<tvynr> Thanks for all the help, by the way. :)
<Drup> ah, it was for the typedtree
<Drup> yes, ppx_import is the way
<tvynr> I'll take a crack at it with the available tools. Thanks for the guidance. :)
<Heasummn> How do I access a module within a Folder?
<Heasummn> Folder.Module right?
<tvynr> Depends on your build setup.
<mrvn> -I Folder
<tvynr> But probably just "Module"
<tvynr> No Java-like namespacing here. ;(
<Heasummn> ah cool
<tvynr> (You can emulate it, but it's sorta weird and messy.)
<Heasummn> then when I'm doing Core.Std, what am I opening?
<mrvn> but good that you remind me that I wanted to patch that into the compiler
<mrvn> Heasummn: the Std module of the Core module
<ggole> Hmm, the ast iterator might be a better way to do that
<Heasummn> ah ok
<Heasummn> I'm getting circular dependencies
<Drup> tvynr: you can use the same thing that I posted, but for the parsetree/deriving equals
<tvynr> Drup: Oh! Didn't realize that was for me. Thanks!
<Heasummn> Circular dependencies: "src/parsing/lexer.cmx" already seen in [ "src/parsing/parsing.cmxa"; "src/parsing/lexer.cmx" ]. What does that mean?
<tvynr> Your Parser module uses your Lexer module and vice versa.
<tvynr> Compilation in OCaml has to form a DAG.
<Heasummn> parsing is the name of my folder
ygrek has joined #ocaml
<tvynr> It's also the name of a module, yes?
<Heasummn> I don't have a .ml or .mli file named parsing
<tvynr> parsing.cmxa?
<tvynr> Oh.
<tvynr> Right.
<Heasummn> It's the name of the library
<tvynr> Um... did you try to compile your Lexer module and tell it to use your "parsing" library as a dependency?
<mrvn> best to keep names unique
picolino has joined #ocaml
<tvynr> Heasummn: That error looks like the sort of thing you might get if your Lexer module appears in a "parsing" library in an _oasis file and the "parsing" library lists itself in the BuildDepends section.
jmct has joined #ocaml
<Heasummn> I added a parsing folder, and moved stuff into it. I then made that a library, and had the main executable depend on it
<tvynr> Heasummn: Are you using Oasis?
<Heasummn> yeah
govg has quit [Ping timeout: 244 seconds]
<tvynr> Heasummn: Does the "parsing" library have a BuildDepends section?
<Heasummn> it needs menhir yeah
<Heasummn> but that is it
<tvynr> But the only thing listed there is "menhir". Hm...
<Heasummn> I changed some stuff and I'm getting a different error
<tvynr> Do tell. :)
shinnya has quit [Ping timeout: 240 seconds]
<Heasummn> I realized I wasn't adding the Lexer module as a module in the library, so I did that, and now I'm getting a Solver failure
luzie has quit [Quit: WeeChat 1.5-rc1]
<jmct> I'm struggling getting profiling to work with files I'm preprocessing with camlp5. Anyone have an insight on this?
<Heasummn> tvynr, are there any example oasis files like this?
<tvynr> Heasummn: Here's the one from our project: https://github.com/JHU-PL-Lab/odefa/blob/master/_oasis
<tvynr> It's kinda big, but it should have examples of what you need.
<tvynr> The "FindlibParent" bit makes the library be a child of an existing package; that is, "utils" becomes "odefa.utils". Hierarchies exist for packages, just not modules. :)
<Heasummn> that's great
kakadu has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
<Heasummn> Having done that
<Heasummn> It now compiles up to another point
<Heasummn> how would would I reference this new library within my other code?
<tvynr> Heasummn: If you're using Oasis, all of your code exists either in a Library or Executable.
<Heasummn> for example in src/ how would I reference code contained within a library src/parsing?
<tvynr> Heasummn: All you should have to do is add the name of that library (e.g. "parsing") to the BuildDepends of the appropriate section.
<Heasummn> src is the parent of src/parsing
<tvynr> That doesn't matter, though. If you tell Oasis that "src" is the path for the source code of your executable, it looks there.
<tvynr> Unlike languages like C#, Haskell, or Java, the filesystem doesn't implicitly define any namespacing.
<Heasummn> right. Now, let's say I've got a file, main.ml, how would I access parsing/parse.ml? Because right now I'm getting an error saying it doesn't exist
<tvynr> Just use the "Parse" module after you add "parsing" to the BuildDepends section of your executable.
jeffmo has joined #ocaml
<Heasummn> Here's what I did. I started the oasis file over. I made a library called parsing, located in src/parsing, no dependencies outside of menhirLib. Then I made an executable and had it depend on parsing the library
<Heasummn> But the solver fails when trying to compile
<Heasummn> some fiddling and I get this:
<Heasummn> [WARNING] Interface parsing.cmi occurs in several directories: /home/heasummn/.opam/4.03.0/lib/ocaml, src/parsing
<Heasummn> Is parsing a module within ocaml?
<tvynr> Yeah.
<tvynr> Because of the flat namespace stuff, I often name my modules quite redundantly.
<tvynr> There do exist projects that will automatically do hierarchical module layout things for you; I think I saw an ocamlbuild plugin for that.
<tvynr> But your program will probably need to have modules named e.g. FooParsing.
<Heasummn> god damn
<Heasummn> Renaming parsing to parse fixed everything
<Heasummn> these oasis/ocamlbuild errors get really cryptic
<Heasummn> I'll probably do the naming scheme
<Heasummn> FooParsing
LiamGoodacre has joined #ocaml
govg has joined #ocaml
fraggle_ has quit [Ping timeout: 260 seconds]
sepp2k has quit [Quit: Leaving.]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
<tvynr> Heasummn: Agreed; the error messages can get pretty cryptic. From what I can tell, this arises from the number of layers in the toolchain and the practical limits on how long people can spend generating good error messages. Thankfully, this IRC channel has a lot of people from whom I can beg assistance when I need it. :)
pyon has joined #ocaml
fraggle_ has joined #ocaml
wtetzner has joined #ocaml
kakadu has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
wtetzner has quit [Ping timeout: 265 seconds]
<Heasummn> I forgot to say thank you tvynr
<tvynr> Heasummn: No problem. I'm just glad I can be of help; I feel like I owe this IRC channel quite a bit by now. :)
<tvynr> Good luck!
fraggle_ has quit [Ping timeout: 264 seconds]
mpenet has quit [Remote host closed the connection]
dedgrant has quit [Ping timeout: 240 seconds]
fraggle_ has joined #ocaml
fraggle_ has quit [Ping timeout: 264 seconds]
AlexRussia has joined #ocaml
dedgrant has joined #ocaml
darkf has joined #ocaml
jyc has quit [Ping timeout: 250 seconds]
jyc has joined #ocaml
pyon has quit [Ping timeout: 276 seconds]
tvynr has quit [Ping timeout: 265 seconds]
_andre has quit [Quit: leaving]
unbalancedparen has joined #ocaml
shinnya has joined #ocaml
fraggle_ has joined #ocaml
rand__ has joined #ocaml
fraggle_ has quit [Remote host closed the connection]
fraggle_ has joined #ocaml
tvynr has joined #ocaml
ontologiae has joined #ocaml
pyon has joined #ocaml
elfring has quit [Quit: Konversation terminated!]
luzie has joined #ocaml
seangrove has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 250 seconds]
AlexRussia has quit [Ping timeout: 264 seconds]
ontologiae has quit [Ping timeout: 276 seconds]
jso has joined #ocaml
<jso> Hello.
<jso> We are running an experiment in our lab using OCaml, but we are getting a very strange behaviour.
<jso> The piece of code that is misbehaving looks like this:
<jso> for j = 0 to Array.length myArray - 1 do
<jso> if property.(id) then
<jso> (* do a bunch of stuff*)
<jso> done
<jso> Here, "property" is a huge array of boolean. In this experiment, we have 2 cases: in the first, "property.(id)" is always "true". In the second, "property.(id)" can be either "true" or "false". Therefore, we expect that the 2nd case should be faster, since you avoid a "bunch of stuff". But it turns out to be slower!
<jso> Even more surprising, if you remove the "if" inside "for" loop, both cases have similar running time. That is, it seems that the "if" inside the "for" loop, which is run by both cases, is making only the 2nd case slower.
<jso> We would really appreciate your help with this case, if you have any insight. Thank you.
<lyxia> Branch prediction strikes again?
<jso> I am sorry, what is that, pls?
<lyxia> look at the first answer
<jso> That's totally possible! Thank you for you quick reply
<lyxia> you're welcome
jeffmo has quit [Ping timeout: 244 seconds]
jeffmo_ has joined #ocaml
jeffmo_ has quit [Read error: Connection reset by peer]
jeffmo has joined #ocaml
<jso> Hello again, lyxia. Does anyone know the a solution for this issue with Branch prediction?
manizzle has quit [Ping timeout: 252 seconds]
<ggole> You could collect (or partition, if order doesn't matter) all the elements for which property.(id) is true, and then run code on them unconditionally.
<ggole> There's no guarantee that the cost of doing the partition will be lower than the gain, of course.
<jso> Thank you, ggole, we like this idea. We are going to try it.
Nahra has quit [Read error: Connection reset by peer]
Nahra has joined #ocaml
two_wheels has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
two_wheels has joined #ocaml
<jso> ggole, since Array has no "partition" function, do you have any suggestion on how we could split the array without using a "if"?
<seliopou> Yo, if there are any angstrom users around, I have a question: What would you think if the Unbuffered interface only taking a bigstring (or Cstruct.t)? To use a string as input, you could still go through the Buffered interface...
<ggole> jso: you could write your own. (Unstable) partition is a very simple algorithm.
dexterph has quit [Ping timeout: 265 seconds]
chris2 has quit [Ping timeout: 250 seconds]
<jso> Thank you, ggole. We are going to try it.
<ggole> (Not tested.)
<ggole> I have to go, good luck with your problem.
ggole has quit []
<jso> Thank you
tvynr has quit [Ping timeout: 244 seconds]
jso has left #ocaml [#ocaml]
chris2 has joined #ocaml
<Heasummn> Is there a unity like function in ocaml?
<Heasummn> fun x -> x?
jhonatanoliveira has joined #ocaml
<Drup> not predefined in the standard library
<Heasummn> alright
<Heasummn> I just have to use it so often
tane_ has quit [Quit: Leaving]
<Heasummn> Does there exist some sort of string split function?
<Heasummn> IE: 4, 5, 7 etc. And split on ,
<Heasummn> "4, 5, 7"
<Drup> in the standard library, only with regex, in Str
<Heasummn> that works
LiamGoodacre has quit [Ping timeout: 265 seconds]
<jmct> I'm struggling getting profiling to work with files I'm preprocessing with camlp5. Anyone have an insight on this? I've found one suggestion to have camlp5 use pr_o.cmo to dump to a file before compiling, but I seem to get naming issues when I do that.
agarwal1975 has quit [Quit: agarwal1975]
two_wheels has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<jhonatanoliveira> Hello again.
<jhonatanoliveira> Few minutes ago I had a question using this piece of code:
<jhonatanoliveira> for j = 0 to Array.length myArray - 1 do
<jhonatanoliveira> if property.(id) then
<jhonatanoliveira> (* do a bunch of stuff*)
<jhonatanoliveira> done
<jhonatanoliveira> Where "property" is a huge array of boolean. This is an experiment in which we have 2 cases: in the 1st, "property.(id)" is always "true". In the second, "property.(id)" can be either "true" or "false".
<jhonatanoliveira> We want that the 2nd case win, since it skips code execution but, as well explained by users ggole and lyxia, this doesn't happen because of branch condition.
<jhonatanoliveira> We have also tried to implement ggole 's idea of partitioning "property" instead of a "if" statement, but the 1st case still wins.
<jhonatanoliveira> Thus, the question now is more general: what is the better way of implementing this problem? The problem definition is: we can detect a property that skips part of the code execution, but using an array makes the checking for the property slower than the saved execution.
<jhonatanoliveira> We really appreciate any suggestion from the community. Thanks again.
tvynr has joined #ocaml
wtetzner has joined #ocaml
<Heasummn> Drup, How do I include Regex?
<Drup> Regex ?
<Drup> Str is the module distributed with the compiler, in the "str" ocamlfind library
<Drup> but honestly, just pick your stdlib extension of chocie
<Heasummn> No implementations provided for the following modules: Str
<Heasummn> I'm assuming I have to link/include it
<Drup> yes, "str" library
<Heasummn> k
<Drup> core is annoying because it's so big/non portable, but core_kernel is fine, if you want to stick with jst stuff (there is also batteries and containers)
<Drup> you are not doing a library, don't lose time with that kind of stuff
<Drup> jhonatanoliveira: I guess you can't avoid having to use an array of boolean to begin with ?
<jhonatanoliveira> Drup: we would be happy to avoid it, if that makes checking for the property faster
<Drup> it's hard to answer without more details about the whole thing :/
<jmct> any thoughts on my profiling issue?
<Drup> there are things like bloomfilters, but it's quite specialized, difficult to know if it's ok for your use case
<jhonatanoliveira> Drup: I could give more details for sure! It's just that the whole code is big and messy, so I tried to summarize the problem with that toy example
<jhonatanoliveira> Drup: I can take a look at them
LiamGoodacre has joined #ocaml
<Drup> there is an implementation in companion_cube's containers
<jhonatanoliveira> Drup: is that related to bloomfilters?
<Drup> yes
<Heasummn> expected: [45, ;, EOF] but got: [45, ;, EOF]. Thank you oUnit. Thank you
<Drup> not really convinced it'll be better, but you can try
<jhonatanoliveira> Very interesting, Drup, we'll definitely look into it. Thank you.
<Heasummn> What's the easiest way to iterate through a file?
<Heasummn> line by line
<Heasummn> a loop?
<Drup> Heasummn: Use an extension of the standard library, it'll have a function for that :3
<Heasummn> getting Batteries now
strykerkkd has quit [Read error: Connection reset by peer]
<tvynr> Heasummn: I had the exact same experience with oUnit today. ;)
<tvynr> ggole, Drup: I think I was wrong about not being able to use (=) on the OCaml AST. I did the ppx_import thing and I got the same results. I took that a step further and generated pp as well (so I could see the AST structure and not just the Pprintast form). Turns out the code was generating an identifier where a no-args constructor was expected.
<Drup> tbh, it means you have an issue with your print function, it's not really ounit's fault :p
<tvynr> Drup: Yeah; I shouldn't rely on Pprintast in my unit tests. ;)
<Drup> use printast instead of pprintast
<tvynr> Oh. Somehow missed that that was there.
<tvynr> Thanks. :)
two_wheels has joined #ocaml
SilverKe_ has quit [Quit: Halted.]
kakadu has quit [Remote host closed the connection]
two_wheels has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
jhonatanoliveira has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
al-damiri has quit [Quit: Connection closed for inactivity]
jhonatanoliveira has joined #ocaml
seangrove has quit [Ping timeout: 250 seconds]
LiamGoodacre has quit [Quit: Leaving]