gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
thomasga has quit [Quit: Leaving.]
cyphase has quit [Ping timeout: 245 seconds]
ftrvxmtrx has joined #ocaml
kolera has quit [Quit: Leaving]
ftrvxmtrx has quit [Ping timeout: 260 seconds]
cyphase has joined #ocaml
Boney has quit [Quit: leaving]
struktured has quit [Ping timeout: 265 seconds]
fantasticsid has joined #ocaml
tufisi has quit [Ping timeout: 245 seconds]
tufisi has joined #ocaml
Hodapp has quit [Remote host closed the connection]
fantasticsid has quit [Ping timeout: 244 seconds]
Guest14256 is now known as dnm
emmanuelux has quit [Remote host closed the connection]
ivan\ has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
ivan\ has joined #ocaml
ftrvxmtrx has joined #ocaml
Hussaind has joined #ocaml
Hussaind has left #ocaml []
ftrvxmtrx has quit [Ping timeout: 250 seconds]
kmicinski has joined #ocaml
ulfdoz has quit [Ping timeout: 260 seconds]
Davidbrcz has joined #ocaml
lusory has joined #ocaml
kmicinski has quit [Ping timeout: 250 seconds]
Davidbrcz has quit [Ping timeout: 256 seconds]
kmicinski has joined #ocaml
ocp has joined #ocaml
pango is now known as pangoafk
Kakadu has joined #ocaml
fpz has quit [Read error: Operation timed out]
samposm has quit [Read error: Operation timed out]
samposm has joined #ocaml
fpz has joined #ocaml
djcoin has joined #ocaml
cdidd has quit [Remote host closed the connection]
mika1 has joined #ocaml
Sablier has joined #ocaml
dca has quit [Read error: Connection reset by peer]
<Drakken> ocamlc -pack should have a -include foo.cmo option that includes the submodule directly in the main module.
ftrvxmtrx has joined #ocaml
<adrien> so that if you had Foo.bar, you could have Pack.bar?
<Drakken> right, for ocamlc -pack -o pack.cmo -include foo.cmo
<adrien> you could probably do something along
<adrien> module Pack = struct
<adrien> include Foo1
<adrien> include Foo2
<adrien> erf, no, sorry
<adrien> not include, but something along that; the idea is to rewrite it somehow
<adrien> because what you're asking for goes against the clear packing that -pack provides
* adrien has to go, already 1 hour late =)
<yezariaely> is there some predefined possibility to check list equivalence (but order)
<yezariaely> maybe a set/bag would be the better choice ...
<Drakken> There's a Set module in the standard library.
<yezariaely> Drakken yes, I know. just got the idea, that maybe the data structure is the wrong one ;-)
<Drakken> I think your idea is right :)
<yezariaely> but the idea came into my mind just after I posted the first question :D
<Drakken> ha ha too bad! :D
<Drakken> yezariaely cheers. Just having fun with you :)
<yezariaely> your most welcome ^^
Anarchos has joined #ocaml
thomasga has joined #ocaml
Submarine has joined #ocaml
eni has joined #ocaml
BiDOrD has joined #ocaml
<yezariaely> why is there no map for Set?
<_habnabit> what?
BiDOrD_ has quit [Ping timeout: 245 seconds]
<yezariaely> of course you would have to define what happens if two elements are equivalent afterwards. And it would be hard to have a map function mapping to a different type (as the comparison function is required for the new set) but for A -> A this would be cool.
<yezariaely> Set.map (fun) set
<_habnabit> oh
<flux> fortunately you can easily implement it with fold
<flux> and going that way allows easily using different types as well
<yezariaely> hmm
<yezariaely> sure you are right.
<_habnabit> well you could have one that was (key -> key) -> t -> t I guess
<yezariaely> but why is it not in the lib...
<_habnabit> it seems pretty pointless to me
<flux> I think I agree with _habnabit
<_habnabit> when I need to change types, I use enums in batteries, fwiw
<flux> Batteries comes with Set.map, though
<yezariaely> in my scenario, type changing is not necessary
<_habnabit> yeah but I mean going from one set to another
<_habnabit> 27
<_habnabit> whoops
<yezariaely> oh, I did not look at batteries until now. Maybe I should ...
<flux> obviosuly that BatSet.map doesn't support changing type
cago has joined #ocaml
<yezariaely> sure, reason is clear
<_habnabit> does the polymorphic set support it?
<_habnabit> well, let's see
<flux> S1.enum foo |> Enum.map ( (+) 1) |> S2.of_enum would work though, as _habnabit pointed out.
<_habnabit> I do that a lot in my code
<_habnabit> oh, yeah, there is a BatSet.map with ('a -> 'b)
<_habnabit> probably just makes the set compare on compare, though
<yezariaely> how does it work with the comparison?
<yezariaely> ah ok
bacam has quit [Ping timeout: 240 seconds]
bacam has joined #ocaml
err404 has joined #ocaml
eni has quit [Quit: .]
mcstar has joined #ocaml
kmicinski has quit [Read error: Connection reset by peer]
Asmadeus has quit [Ping timeout: 256 seconds]
Asmadeus has joined #ocaml
Yoric has joined #ocaml
<yezariaely> using BaSet.Make can I some generate the set from a list?
<yezariaely> MySet.from_list [1,2,3]
<yezariaely> or s.th.
<yezariaely> ehm [1;2;3]
<_habnabit> in batteries, there's a thing
<_habnabit> otherwise you'd need a fold
<yezariaely> _habnabit: that exactly was my question? How does it work in batteries? because, http://ocaml-batteries-team.github.com/batteries-included/hdoc/BatSet.Make.html, does not mention a from_list
<_habnabit> List.enum l |> MySet.of_enum
yezariaely has left #ocaml []
yezariaely has joined #ocaml
Anarchos has quit [Quit: Page closed]
<yezariaely> unfortunately just killed my window here, I hope no one did answer me in between...
<_habnabit> 09:01:04 < _habnabit> List.enum l |> MySet.of_enum
ocp has quit [Ping timeout: 244 seconds]
<yezariaely> thx
<yezariaely> where is |> defined?
<_habnabit> Batteries.Pervasives.(|>)
<_habnabit> you are doing `open Batteries`, right?
<yezariaely> ah no … /
<yezariaely> :/
cago has quit [Ping timeout: 245 seconds]
snearch has joined #ocaml
snearch has quit [Quit: Verlassend]
err404 has quit [Remote host closed the connection]
cago has joined #ocaml
thomasga has quit [Quit: Leaving.]
eikke has joined #ocaml
thomasga has joined #ocaml
tufisi has quit [Ping timeout: 245 seconds]
snearch has joined #ocaml
tufisi has joined #ocaml
Davidbrcz has joined #ocaml
struktured has joined #ocaml
Hodapp has joined #ocaml
thomasga has quit [Read error: Connection reset by peer]
thomasga1 has joined #ocaml
ocp has joined #ocaml
<yezariaely> I get a Reference to undefined global `Batteries' when linking.
<yezariaely> ocamlfind query batteries yields /usr/lib/ocaml/batteries
<yezariaely> ocamlfind ocamlc -package unix,oUnit,batteries -linkpkg ..
<yezariaely> anyone has an idea?
<flux> try -thread
<yezariaely> thx, worked. but now, compilation process is much slower :/
<flux> because it works?-)
<flux> how slow?
<flux> I'm not sure if I've ever seen a slow ocaml compilation..
<wieczyk> Maybe a bit silly and old question: Does ocaml-team have any plans to add parallel-gc and add supports os-level threading?
<wieczyk> support for*
<adrien> parallel gc: oc4mc, and "maybe"
<flux> maybe it depends on if oc4mc will turn out to be useful
<adrien> as for os-level threading, it's already there
<adrien> oc4mc needs more testing
<wieczyk> Thanks for oc4mc, I did not hear about this ;]
<adrien> people won't use oc4mc until it has had more testing
<adrien> chicken-egg =/
<adrien> wieczyk: "ocaml 4/for multicore"
<yezariaely> flux: about 2 seconds. before, it was rather 700ms ;-)
<yezariaely> ok, not really slow...
<flux> quite a bump, though.. I wonder if the problem is Batteries having so many symbols that it slows down?
<flux> try profiling the compiler ;)
<yezariaely> let me check this
<yezariaely> I'll checkout the old version
<flux> I suppose batteries should work without -thread as well
<yezariaely> it is even worse: before batteries full project build took 300ms, now, full project build takes 15seconds!
<adrien> which build system are you using?
<yezariaely> ocamlmakefile
<adrien> also, it'd be good to have a comparison between batteries+threads and threads only
<yezariaely> ok, second
<yezariaely> 8seconds with threads only.
<yezariaely> the major part of the time is consumed when building a new toplevel
<yezariaely> it is 600ms with threads, and without ocamlmktop
<yezariaely> although another binary is created here, then
<yezariaely> I'll cancel the ocamlmktop, I don't need it anymore.
<yezariaely> how can I get batteries working without the -thread?
<jaxtr> ahh it's a wonderful day!
snearch has quit [Quit: Verlassend]
gnuvince has quit [Ping timeout: 250 seconds]
Davidbrcz has quit [Remote host closed the connection]
Davidbrcz has joined #ocaml
bjorkintosh has quit [Ping timeout: 240 seconds]
bjorkintosh has joined #ocaml
_andre has quit [Quit: Lost terminal]
_andre has joined #ocaml
<Drakken> How do you debug "interface mismatch" bugs in camlp4?
snearch has joined #ocaml
<Drakken> My functor params and the argument module for them are all explicitly typed from the same .mli file.
<Drakken> So where's the mismatch?
<yezariaely> can I somehow hide an import when I use open Modulename ?
<yezariaely> e.g. Module1 has a submodule Test, I have a module Test in my project. When I now open Module1, and later open module Test, the Test module of Module1 is opened, and not mine. How can I open mine?
osa1 has joined #ocaml
<Drakken> You can bind the contents of M1 individually
<Drakken> i.e. let (foo,bar) = M1.(foo,bar)
<Drakken> or rename the old Test, open M1, and rebind Test.
<Drakken> module T2 = Test;; open M1;; module Test = T2;;
<yezariaely> ah the renaming is nice
<yezariaely> thx
gnuvince has joined #ocaml
Davidbrcz has quit [Remote host closed the connection]
Davidbrcz has joined #ocaml
err404 has joined #ocaml
maufred_ has joined #ocaml
Snark has joined #ocaml
emmanuelux has joined #ocaml
<thelema_> yezariaely: open Batteries_uni
silver has quit [Remote host closed the connection]
<yezariaely> thelema_ wonderful, compilation is much faster now :)
<mfp> yezariaely: linking can also get slow; if your platform is supported, -cclib -B/usr/lib/gold-ld can help
<yezariaely> mfp cool. Of course, I did not express myself correctly. Linking is the slow part. Not the compilation
<yezariaely> gold linker is faster?
<mfp> yezariaely: yes, quite a lot (3X IIRC on some code of mine)
<yezariaely> wow
<yezariaely> worth a try, then
Davidbrcz has quit [Remote host closed the connection]
<Drakken> Is the current/project directory still in the ocamlbuild search path if the target is in a subdirectory?
Davidbrcz has joined #ocaml
beckerb has joined #ocaml
Yoric has quit [Ping timeout: 265 seconds]
thomasga1 has quit [Ping timeout: 244 seconds]
avsm has joined #ocaml
<kaustuv> I haven't looked into this in a couple of years, but is it nowadays possible to build and deploy OCaml programs on Windows without a Cygwin installation?
<kaustuv> (not counting cross-compilation from Linux)
<adrien> yes
<adrien> but state your detailled constraints
djcoin has quit [Ping timeout: 265 seconds]
<kaustuv> My constraint is that I want my program to be compilable from source using as few dependencies as possible. Preferably with a 64 bit wordsize, though this isn't critical. Cygwin is a rather large dependency and introduces all kinds of weirdness the last I looked at it (such as a fake filesystem representation that requires translating paths using some cygwin utility)
Submarine has quit [Quit: Leaving]
<kaustuv> FWIW, I use ocamlbuild as my build system and my code is pure OCaml
<kaustuv> (except the batteries dependency, but I think batteries is pure as well...)
djcoin has joined #ocaml
<Drakken> $ camlp4rf _build/Metl.cmo _build/MetlString.cmo rules.ml
<Drakken> Camlp4: Uncaught exception: DynLoader.Error ("./_build/MetlString.cmo", "interface mismatch on Metl")
<Drakken> Anybody know what that means, or what I'm doing wrong?
<thelema_> kaustuv: yes, batteries is pure
<adrien> kaustuv: ocamlbuild still has a dep on bash iirc but msys can provide, and... it can almost certainly be removed without too much pain
<adrien> currently I'm working on yypkg stuff again but removing the bash dependency is something I want to do
<kaustuv> Can you confirm that it works with a 64 bit wordsize? Googling returns mixed results, but some of the pages we last modified years ago
<adrien> haven't tried it myself but it definitely should
<adrien> especially ocaml 4 and mingw-w64
<adrien> thelema_: yypkg :]
<adrien> thanks for the link
<kaustuv> "The next version of the Windows installer will encourage the user to install Cygwin." !!
<kaustuv> anyhow, thanks to the both of you
Sablier has quit [Read error: Connection reset by peer]
<adrien> I'll be announcing a new batch of yypkg work in a few days
ftrvxmtrx has quit [Quit: Leaving]
<adrien> bootstrapping toolchains is awful :-)
<kaustuv> thanks for doing the work that I never would, even if they paid me
<adrien> :-)
eikke has quit [Ping timeout: 252 seconds]
cago has quit [Quit: Page closed]
mika1 has quit [Quit: Leaving.]
<mrvn> adrien: bootstrapping is awful :->
<adrien> binutils: done
<adrien> mingw-w64 headers: done I think
<adrien> gcc: should be almost good
<adrien> mingw-w64 crt: shouldn't be an issue
<adrien> so it shouldn't take too long
<adrien> the main issue is that my liver might get damaged in the long run :P
Phlogistique has left #ocaml []
thomasga has joined #ocaml
Davidbrcz has quit [Ping timeout: 245 seconds]
thomasga1 has joined #ocaml
thomasga has quit [Read error: Connection reset by peer]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
thomasga has joined #ocaml
thomasga1 has quit [Read error: Connection reset by peer]
djcoin has quit [Quit: WeeChat 0.3.2]
osa1 has quit [Quit: Konversation terminated!]
<adrien> kaustuv: also, windows is not that awful
<adrien> it's mostly like an embedded posix system
<adrien> with possibily removed features that are useful
<adrien> and some braindead things
<adrien> but you can cross-compile and import a whole gnu userland ;-)
<mrvn> it has (had) the absolute minimum of posix so it got the certificate without it being of any use.
<adrien> actually not even that
<adrien> it had an additional posix layer
ocp has quit [Ping timeout: 245 seconds]
<adrien> but "supported"
<mrvn> nothing wrong with it being a layer
eikke has joined #ocaml
<adrien> well, cygwin is a layer
<adrien> perf is awful
<mrvn> nah, cygwin is an application and library
<adrien> but the issue is that it wraps everything and for some things, it emulates in userland what would be better in kernel
<adrien> usermode linux could make windows posix too :P
Anarchos has joined #ocaml
smerz has joined #ocaml
<bjorkintosh> adrien, why bother with all that?
<adrien> because not doing so is denial of today's realtiy
<adrien> reality*
<adrien> with a proper way to develop with gcc and free tools and libs, it'll be easier to bring a number of software on windows
<adrien> it'll save time which will be usable for other issues
<adrien> and with better free software on windows, it will be easier to migrate away from it
<Anarchos> adrien or better to get stuck with it ...
<adrien> at least, people stuck with it will have better software
Sablier has joined #ocaml
eikke has quit [Ping timeout: 245 seconds]
beckerb has quit [Quit: Konversation terminated!]
cdidd has joined #ocaml
fschwidom has joined #ocaml
thomasga has quit [Quit: Leaving.]
<Anarchos> adrien do you know the "unix-hater handbook" ?
<bjorkintosh> it's great.
<bjorkintosh> i learnt about "apropos" from it.
Kakadu has quit [Quit: Konversation terminated!]
smerz has quit [Remote host closed the connection]
<bjorkintosh> i think it's online isn't it?
<Anarchos> bjorkintosh yes, i read it online this week
<Anarchos> bjorkintosh i felt like enlighment after reading it. So much things became lightnening true after that
<bjorkintosh> it ought to be on the 'must read' list for unix users.
smondet has quit [Read error: Connection reset by peer]
<bjorkintosh> adrien, ostensibly, with a raspberry pi, the cost of switching is $45.00
<bjorkintosh> or the cost of burning a knoppix CD.
smondet has joined #ocaml
<adrien> Anarchos: yes, why?
<adrien> bjorkintosh: or the issue is with migrating software
mgodshall has joined #ocaml
<Anarchos> adrien cause it list some myths about unix :)
<bjorkintosh> it's a pretty funny book.
<Anarchos> bjorkintosh yes
smondet` has joined #ocaml
smondet has quit [Ping timeout: 245 seconds]
<adrien> Anarchos: ah, the simplicity? =)
Yoric has joined #ocaml
<Anarchos> adrien yes, and stable and portable
cdidd has quit [Remote host closed the connection]
<jonafan> i should look through the UHH again
<jonafan> on one hand, i'm a lot more familiar with unix now
<jonafan> on the other hand, unix has probably progressed a lot since i read it, let alone since the book was written
<Anarchos> adrien i appreciate a lot the excuses of K. Thompson some yearsz ago
<Anarchos> jonafan the book is still lrelevant
cdidd has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
cdidd has quit [Remote host closed the connection]
emmanuelux has joined #ocaml
<jonafan> eeeehhhh
eikke has joined #ocaml
<wmeyer`> hi
<adrien> jonafan: well, "unix" has not changed; but almost noone is running unices nowadays ;-)
<adrien> morning wmeyer`
<wmeyer`> adrien: I can always count on you! and i am always younger half of day :-)
<wmeyer`> (or actually older half of a day)
<jonafan> yeah but much of this applies to linux which most people do use
Guest82433 has quit [Changing host]
Guest82433 has joined #ocaml
Guest82433 is now known as ssbr_
<adrien> jonafan: there are lots of differences in linux
<adrien> wmeyer`: younger I think
<adrien> or mostly later
<adrien> you're so 6 hours ago
<wmeyer`> oh you are talking about windoze
silver has joined #ocaml
<jonafan> but yeah, i'm skimming this and not finding very good criticism
<wmeyer`> it's so great that i don't need to use at any rate!
silver is now known as Guest91411
<wmeyer`> last bits gone at work, as i was herebly granted an IMAP access to the exchange server \o/
Guest91411 has quit [Client Quit]
silver_ has joined #ocaml
silver_ has quit [Client Quit]
silver__ has joined #ocaml
silver__ has quit [Client Quit]
<jonafan> like documentation: i find documentation on linux is pretty good, at least compared to most things which are terrible
Snark has quit [Quit: Quitte]
silver_ has joined #ocaml
<jonafan> many pages complaining about newsgroups
eikke has quit [Ping timeout: 252 seconds]
<wmeyer`> jonafan: I quite like newsgroups, gmane, etc. especially reading with Gnus
<wmeyer`> jonafan: people say - forums are better - i can't say bad word about newsgroups apart they are being spammed and less popular than in past
<jonafan> well, it seems like they've probably shed all the dimwits that are attracted to shiny things
<jonafan> i've never really tried reading any newsgroups though
osa1 has joined #ocaml
<wmeyer`> jonafan: try, there are famous people hanging around
<wmeyer`> and some famous trolls too :-)
<adrien> aren't them the same people?
<Hodapp> troller skates?
<Anarchos> wmeyer` yes really skilled computer scientist and really skilled trollers. Intersection is not empty (already saw tanenbaum et torvalds trolling ?)
snearch has quit [Quit: Verlassend]
<wmeyer`> adrien: these days yes - mostly
eikke has joined #ocaml
<wmeyer`> ended up with embedded prolog
<Anarchos> wmeyer` what ?
<wmeyer`> Anarchos: Needed unification -- for the type system eventually
<wmeyer`> Anarchos: It's a combination of type propagation plus this small twist of dependent types makes it pleasant to just throw some unification code
<Anarchos> wmeyer` ok
Sablier_ has joined #ocaml
Sablier has quit [Read error: Connection reset by peer]
osa1 has quit [Quit: Konversation terminated!]
eikke has quit [Read error: Connection reset by peer]
smondet`` has joined #ocaml
smondet` has quit [Ping timeout: 244 seconds]
ocp has joined #ocaml
silver_ has quit [Read error: Connection reset by peer]
eikke has joined #ocaml
silver has joined #ocaml
ocp has left #ocaml []
Submarine has quit [Ping timeout: 260 seconds]
smerz has joined #ocaml
cdidd has joined #ocaml
fschwidom has quit [Remote host closed the connection]
pangoafk is now known as pango
smondet`` has quit [Ping timeout: 260 seconds]
osa1 has joined #ocaml
eikke has quit [Ping timeout: 244 seconds]
eikke has joined #ocaml
eni has joined #ocaml
<_habnabit> how are you supposed to do any cleanup around raising exceptions in C?
<_habnabit> it looks like the various caml_raise functions immediately longjmp
gnuvince has quit [Ping timeout: 244 seconds]
<_habnabit> well, I guess I have to clean up first
<_habnabit> I'm more used to setting exception state and then doing an error return, so I can have a common cleanup-and-return-NULL section
<wmeyer`> _habnabit: nothing stops you from doing that
Sablier has joined #ocaml
<wmeyer`> _habnabit: I suppose you can wrap it into the C function easily
<_habnabit> wmeyer`, I'm not sure how, if caml_raise never returns
<wmeyer`> _habnabit: the approach I've taken in one library was to always return option for partial functions, and then lift all the functions to contain exceptions in a submodule Exceptions
<_habnabit> wmeyer`, I was thinking I'd be able to do, like, `caml_failwith("message"); goto cleanup; ... cleanup: cleanup(whatever); return NULL`
<_habnabit> that makes sense, but in this specific case there's multiple kinds of failure
<wmeyer`> you can always do #define BEGIN_EXC char * error_state = NULL;
Sablier_ has quit [Ping timeout: 265 seconds]
<wmeyer`> #define END_EXC if (error_state != NULL) caml_failwith(error_state);
<wmeyer`> void foo () {
<wmeyer`> well you know what I mean
<wmeyer`> you surround the block with these macros
<_habnabit> yeah
<_habnabit> that's what I'll end up doing probably
_andre has quit [Quit: leaving]
Sablier_ has joined #ocaml
Sablier__ has joined #ocaml
Sablier has quit [Ping timeout: 245 seconds]
Sablier_ has quit [Ping timeout: 244 seconds]
Sablier has joined #ocaml
Sablier__ has quit [Ping timeout: 256 seconds]
Sablier_ has joined #ocaml
Sablier has quit [Ping timeout: 244 seconds]
mcstar has quit [Quit: mcstar]
Yoric has quit [Ping timeout: 248 seconds]
eni has quit [Ping timeout: 245 seconds]
Sablier_ has quit [Read error: Connection reset by peer]
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
err404 has quit [Remote host closed the connection]
<_habnabit> arrrgh
<_habnabit> so I'm making a library and I get mcl.a, libmcl.a, and dllmcl.so out of it
<_habnabit> except if I try to _use_ it at all after it's installed, I get errors like:
<_habnabit> 'Undefined symbols: "_caml_mcl"' and 'Error: The external function `caml_mcl' is not available'
<_habnabit> (respectively when linking and when #requiring)
<_habnabit> I'm comparing what I get out of nm for each of those files to what I get for another library, but it seems like the symbols are defined/undefined the same way
eikke has quit [Ping timeout: 252 seconds]
<_habnabit> i.e. they're undefined in mcl.a but defined in libmcl.a and dllmcl.so
<_habnabit> how does ocaml decide how to load stublibs, anyway?
<ssbr_> "Parse error: Deprecated syntax, use a sub rule. LIST0 STRING becomes LIST0 [ x = STRING -> x ]"
<ssbr_> whose idea was that? now I have to write LIST0 [x = LIDENT -> x] SEP "_"
<ssbr_> that is just silly.
<_habnabit> revised syntax?
<ssbr_> _habnabit: ?
<_habnabit> are you using revised syntax? I don't recognize that
<_habnabit> oh, maybe it's ocamlp4
<ssbr_> Sorry, yeah, ocamlp4
<ssbr_> this is in a p4 file
<wmeyer`> ssbr_: yep, that is needed, but it's useful
<_habnabit> well, that was dumb. I switched to using oasis's myocamlbuild and it loads now
<_habnabit> what could it possibly be doing
<wmeyer`> ssbr_: sometimes you want to perform some temporal conversion (hint: one letter polymorphic variants are extremely useul in these cases)
<wmeyer`> ssbr_: the inline rules for Camlp4 parsers are maybe the best thing there ;-)
<ssbr_> wmeyer`: temporal conversion?
<ssbr_> polymorphic variants? :<
<wmeyer`> at no rate this is a good code:
osa1 has quit [Quit: Konversation terminated!]
<wmeyer`> but you get the idea - later you unpack the variants to your target AST
<wmeyer`> ssbr_: btw, you were doing something with datalog - I also ended up with some very dumb unification routine
<wmeyer`> so the polymorphic variants are even more useful in local scope of the inline rules - they allow to have different types on the branches
<ssbr_> datalog doesn't really have unification, because it has no compound terms
<wmeyer`> ssbr_: oh sorry, but it performs some kind of substitution
<ssbr_> it joins variables together if they're made to be equal to each other
<ssbr_> With our implementation, if you have p(X, Y, ...) :- X=Y, ... . then all instances of Y are replaced with X, so that it becomes p(X, X, ...) :- ... .
<ssbr_> or was that a preprocessing step that gets followed up on later? Bah. The code confuses me.
<wmeyer`> oh yes, now i remember, it's just substitution then
<ssbr_> Yeah
<wmeyer`> ssbr_: yes, sort of, so the problem, is that you want to return from the same parser either element or list
<ssbr_> wmeyer`: no, no
<ssbr_> the problem is that I want to use LIDENT directly rather than [x = LIDENT -> x]
<wmeyer`> ok, yes
<wmeyer`> that was just side effect - understand you want to just have list of strings
<ssbr_> wmeyer`: but that's not a problem... it typechecks after I make that substitution
<wmeyer`> it would be nice if that was permitted
<wmeyer`> maybe i bumped also on this, but it does not bother me that much
<wmeyer`> the thing that bothers me - is that i don't understand how the camlp4 parsers work
<wmeyer`> at all
<wmeyer`> and the error recovery could be very imprecise with LIST thing
<wmeyer`> ssbr_: sorry my brain stopped working today already
<wmeyer`> being to pro-active with the caffeine
<Hodapp> caffeine and I don't always get along.
<ssbr_> I know that they aren't very good :<
<Hodapp> if I have too much at once - where 'too much' is about the difference between 1 cup and 1.5 cups of coffee - I huddle on the ceiling shaking.
<ssbr_> do you know how infuriating it is to change this: LIST1 x -> x -- into this? -- x; LIST0 y -> x::y
<ssbr_> the latter works and the former doesn't.
<ssbr_> It is maddening.
<wmeyer`> ssbr_: i made biggest mistake in my parser - however I can change it - toplevel expressions are in the LIST ;-)
eikke has joined #ocaml
<ssbr_> uhhhhhh
<ssbr_> sorry, I am dumb today
<ssbr_> x = LIST1 var -> x vs x = var; y = LIST0 var -> x::y
<wmeyer`> Hodapp: yes, sometimes i got similar effects, but i am not too sensitive, and i got used to that
<ssbr_> I am too sensitive. That is __RIDICULOUS__
<wmeyer`> Hodapp: not sensitive - means my body can take it without shaky feeling
<ssbr_> I am also blind and can't tell when you're talking to someone else. :|
<wmeyer`> ssbr_: no problem :-)
* wmeyer` being emotional with camlp4 parsers
<wmeyer`> ssbr_: so what's happening with LIST1
<wmeyer`> when you use LIST1
<wmeyer`> both look correct
<ssbr_> wmeyer`: it makes an irrevocable decision earlier to not go that direction. :)
<ssbr_> wmeyer`: the body of the LIST1 is not considered to be "inline" and isn't factorized for LL parsing
<ssbr_> even though it can be trivially rewritten (as above) so that it can be factorized
<ssbr_> I do not know the technical term for factoring grammars
<wmeyer`> ssbr_: me either :-)
<wmeyer`> ssbr_: don't worry will bump into this issues quite often with camlp4
<wmeyer`> these*
<ssbr_> that's the opposite of encouraging
<wmeyer`> for instance
<wmeyer`> i have
<wmeyer`> let (foo) = 1
<wmeyer`> because the grammar was to ambigous ;-)
<wmeyer`> i hope to fix it someday
<wmeyer`> too*
<wmeyer`> ssbr_: should i encourage you to become a daily camlp4 hacker?
<wmeyer`> really???? :-)
<ssbr_> :)
<wmeyer`> ssbr_: In fact the parser is usually not the biggest part
<wmeyer`> i tend to just use camlp4 in the begining, trying very hard
<ssbr_> wmeyer`: I have written code for other parsing systems that are not as annoying
<wmeyer`> and later just use menhir ...
<wmeyer`> the beautiful thing about camlp4 is that allows you to implement quotations or/and extend the existing grammar, and also because it has already a decent lexer
<wmeyer`> that are selling points
<wmeyer`> one the code generation side of camlp4 - i can say it's damn useful
<wmeyer`> not perfect but i can live with it
eikke has quit [Ping timeout: 265 seconds]
<_habnabit> is there a way in oasis to perform an action _in addition to_ the default -configure and -build actions? I don't want to replace them; I just want to also do something else. (cc gildor_ ?)
<ssbr_> hmmm, there is apparently a difference between ".";"b";"d";...;"r" and ".bddvarorder" in camlp4
<ssbr_> something about keywords? the docs don't say what keywords are though. All I know is that the second only fails half my tests, as opposed to all of them.
gnuvince has joined #ocaml
<wmeyer`> ssbr_: yes, of course Camlp4 is not lexerless
<ssbr_> "of course" -- the only parser generators I've used are lexerless :(
<wmeyer`> ssbr_: and it assumes it will be seperated by tokens
<ssbr_> does it dynamically generate a lexer based on what I put in quotes?
<ssbr_> eh, s/dynamically //
<wmeyer`> ssbr_: oh, so you use PEG or packrat - usually the LALR parsers are after lexing pass... sorry
<wmeyer`> ssbr_: no there is one lexer, just a_LIDENT is single token that contain anything
<ssbr_> wmeyer`: well how do I find out how things are lexed?
<ssbr_> I am interested in lines of the form ".bddvarorder FOO_BAR_BAZ"
<wmeyer`> ssbr_: what would like to parse, so i can tell you maybe how to to this
<ssbr_> e.g..bddvarorder ABSBOOL0_ABSBOOL1_AP0_AP1_AP2
<wmeyer`> ok, so either you will post-process that or implement your own lexer ....
<wmeyer`> with the second thing is easier
<wmeyer`> split the string on _
<wmeyer`> with the first token is more complex
<ssbr_> currently I do ".bddvarorder"; vars = LIST0 [x = LIDENT -> x] SEP "_" -> VarOrderDecl vars
<ssbr_> is that not right?
ftrvxmtrx has joined #ocaml
<wmeyer`> as dot is used as field accessor in ML
<ssbr_> before I did `".";"b";"d";"d";"v";"a";"r";"o";"r";"d";"e";"r"; vars = LIST0 [x = LIDENT -> x] SEP "_" -> VarOrderDecl vars`
<wmeyer`> no, this will not work
<ssbr_> Because the thing LIST0 is handling is one single token?
<wmeyer`> vars = LIDENT -> split_by "_" vars
<wmeyer`> i would suggest using custom lexer
<wmeyer`> ocamllex is nice :-)
<ssbr_> split_by ?
<ssbr_> wmeyer`: will ".bddvarorder" be two tokens then?
<wmeyer`> ssbr_: yes, something that splits the string between
<wmeyer`> yep
<wmeyer`> but you will permit ". bddvarorder" too
<wmeyer`> if that is ok for you
<ssbr_> I don't really care, for now.
<ssbr_> "." needs to be its own token for other stuff anyway
<ssbr_> and _ probably can't be its own token because names like "_foo" and "foo_bar" are permitted, etc.
<wmeyer`> ssbr_: it all sound like you want a custom lexer - do you plan to embed your Datalog in ML?
bjorkintosh has quit [Ping timeout: 260 seconds]
<wmeyer`> ssbr_: because lexers are not extensible in Camlp4
<ssbr_> wmeyer`: that sounds like a neat idea.
<ssbr_> that isn't planned though, no
<wmeyer`> ssbr_: it would be nice :-) you can plug lexer in quotation AFAIK
<ssbr_> (Str.split (Str.regexp (Str.quote "_")) vars)
<wmeyer`> so you can say
<ssbr_> eeep.
<wmeyer`> yes
<ssbr_> I miss Python when it comes to stuff like this. OCaml doesn't have to be this difficult :S
<wmeyer`> let terms = <:datalog< ala(A,B):-ma(A),kota(B). kota(C):- cool(C).>>
<ssbr_> Anyway, it appears to compile without breaking previously-executing code. Woo! Thanks.
<wmeyer`> glad to hear that i am helpful sometimes - and not only annoying all the time :-)
<wmeyer`> Consider this embedding Datalog it would very nice to have as a syntax extension