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
<wmeyer`> it's very cool series about camlp4
<wmeyer`> it shows how to embed json inside ML
<wmeyer`> so perfect starting point for Datalod quotations
<ssbr_> "It is not necessary to use Camlp4’s parsing facilities in order to implement quotations—ultimately we will need to provide just a function from strings to ASTs, so we could use ocamlyacc or what-have-you instead—but it is convenient."
<ssbr_> that answers a question I had. <_<
<wmeyer`> I didn't know it
<wmeyer`> and you can have custom lexer
<wmeyer`> so I personally would go for it
<wmeyer`> >:)
<wmeyer`> come on - everybody dreams about Datalog or Prolog embeded in ML
<ssbr_> Then why don't they do it? :(
<ssbr_> there are practically no good datalog implementations, also
<ssbr_> the one I'm working on is A) terrible, B) closed source
<wmeyer`> ssbr_: Maybe they are enjoying feeling of dreaming - and don't want to destroy it by the camlp4 hell
<ssbr_> camlp4 isn't that bad... just annoying.
<ssbr_> I haven't even tried a lex/yacc style parser generator yet.
<wmeyer`> ssbr_: I agree that was a joke
<wmeyer`> ssbr_: camlp4 is damn useful
<wmeyer`> ssbr_: but has steep learning curve, either is tooling, parsing or code generations
<wmeyer`> ssbr_: Datalog or even subset of Prolog is also very useful to have
<wmeyer`> you could look at HOL, similar idea but full blown proover embeded in ML
<wmeyer`> classical example
<wmeyer`> let term = `A = B /\ B = A`
<wmeyer`> so like in shell everything between backticks is a HOL term
<wmeyer`> (not sure if I recall correctly the term)
<wmeyer`> it's just a Camlp5 extension and OCaml toplevel
<ssbr_> wmeyer`: the first step is to get a good BDD library for ocaml
<wmeyer`> and just use OCaml code to prove it
<ssbr_> like, bindings for BuDDy for example
<ssbr_> (which is what this codebase uses)
<wmeyer`> hmm, never tried it
<ssbr_> It's alright. Do you know much about BDDs?
<ssbr_> (BuDDy is dead anyway.)
<wmeyer`> Maybe second time I hear it
<ssbr_> wmeyer`: OK, so we have a truth table for a boolean relation. Turn it into a decision tree, where you look at each variable and head towards a leaf, where the leaves are either true or false
<ssbr_> then collapse all the leaves into 2 elements: true, false
<ssbr_> then get rid of duplicate vertices in the graph, and pointless vertices (that have both outgoing edges going to the same place)
<ssbr_> bam, done
<ssbr_> they are really tiny encodings of boolean relations, which can be used to represent finite-domain relations
<ssbr_> the upshot being that datalog on finite domains is _waaaaaaay_ faster than prolog.
<ssbr_> also, faster than handwritten C.
<ssbr_> (unless your handwritten C uses BDDs ;)
silver has quit [Read error: Connection reset by peer]
<pippijn> ssbr_: do you know maude?
<wmeyer`> ssbr_: So where is that used?
<ssbr_> pippijn: negative
<ssbr_> wmeyer`: BDDs? Datalog?
<wmeyer`> ssbr_: Expert systems?
<ssbr_> Oh. Program analysis.
<pippijn> it uses buddy
<ssbr_> pippijn: http://maude.cs.uiuc.edu/ ?
<pippijn> yes
<wmeyer`> ssbr_: yep you mentioned before, I quite like of limiting languages - so you can have them highly optmisied for contrainted problems
<wmeyer`> so that's why we should have <:datalog<>> :-)
<wmeyer`> it's very comon approach in Lisp community to have lot's of good stuff in form of DSLs, somewhat less common in ML
<wmeyer`> ssbr_: No pushing - just thinking it would be useful
<ssbr_> :)
<ssbr_> My problem is that I don't have a lot of use for datalog, so I don't really have a good reason to start a new implementation on my own
<ssbr_> I'm more interested in fixing regexps, anyway
<ssbr_> pippijn: maude has a hard time explaining what maude is
<wmeyer`> ssbr_: yes, i can see it, you can always leave it to somebody else
<pippijn> it's a programming language
<pippijn> a pretty cool one
<ssbr_> Sure, but it doesn't actually explain term rewriting / rewriting logics
<pippijn> you write rewrite rules and it matches and applies them until none of them matches, anymore
<pippijn> in general, they are pure, but there is some support for state and I/O
<pippijn> it can be used to find solutions in an incompletely specified problem
cyphase has quit [Read error: Connection reset by peer]
cyphase has joined #ocaml
zzz_` has joined #ocaml
zzz_ has quit [Ping timeout: 260 seconds]
<pippijn> wyrd--
<pippijn> File "interface_draw.ml", line 324, characters 6-12: Assertion failed
noamsml[kersh] has quit [Ping timeout: 252 seconds]
wmeyer`` has joined #ocaml
wmeyer` has quit [Ping timeout: 246 seconds]
smerz has quit [Remote host closed the connection]
wmeyer``` has joined #ocaml
wmeyer`` has quit [Ping timeout: 245 seconds]
fraggle_ has quit [Read error: Connection reset by peer]
bjorkintosh has joined #ocaml
Hussaind has joined #ocaml
Hussaind has left #ocaml []
emmanuelux has quit [Remote host closed the connection]
sgnb` has joined #ocaml
sgnb has quit [Ping timeout: 264 seconds]
fraggle_ has joined #ocaml
sgnb` has quit [Remote host closed the connection]
sgnb` has joined #ocaml
sgnb` has quit [Ping timeout: 245 seconds]
phao has joined #ocaml
wtetzner has quit [Ping timeout: 246 seconds]
eni has joined #ocaml
eni has quit [Ping timeout: 248 seconds]
Psyclonic has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
BiDOrD_ has joined #ocaml
BiDOrD has quit [Ping timeout: 248 seconds]
<yezariaely> can I somehow evaluate test case coverage with ounit?
<yezariaely> e.g. line coverage, and such
<yezariaely> ah, with qtest, this seems to be possible
hcarty has quit [Ping timeout: 260 seconds]
hcarty has joined #ocaml
hcarty has quit [Ping timeout: 244 seconds]
hcarty has joined #ocaml
hcarty has quit [Ping timeout: 245 seconds]
hcarty has joined #ocaml
<taruti> What buildsystem is preferred for new ocaml code?
<_habnabit> oasis + ocamlbuild
<taruti> thanks
eni has joined #ocaml
mcstar has joined #ocaml
silver has joined #ocaml
flux has quit [Ping timeout: 265 seconds]
osa1 has joined #ocaml
lusory has quit [Ping timeout: 252 seconds]
eni has quit [Ping timeout: 240 seconds]
ulfdoz has joined #ocaml
Sablier has joined #ocaml
eni has joined #ocaml
Sablier_ has joined #ocaml
Sablier has quit [Read error: Connection reset by peer]
Yoric has joined #ocaml
eni has quit [Quit: Leaving]
<wmeyer```> morning
<adrien> morning :-)
<wmeyer```> :-)
ftrvxmtrx has quit [Ping timeout: 252 seconds]
milosn has quit [Read error: No route to host]
milosn has joined #ocaml
eikke has joined #ocaml
ftrvxmtrx has joined #ocaml
milosn has quit [Ping timeout: 265 seconds]
eikke has quit [Ping timeout: 244 seconds]
milosn has joined #ocaml
eikke has joined #ocaml
greggies has joined #ocaml
osa1 has quit [Quit: Konversation terminated!]
Smerdyakov has joined #ocaml
cdidd has quit [Remote host closed the connection]
Smerdyakov has quit [Quit: Leaving]
Submarine has quit [Quit: Leaving]
osa1 has joined #ocaml
<osa1> can anyone help me? why I'm getting type error in this code: http://hpaste.org/69426
<pippijn> "derive a token" nice :)
<osa1> yeah, I may be using these terms wrong ..
<pippijn> debugging type errors starts with adding explicit type annotations
<osa1> hmm, I didn't know that we can explicitly declare types. I just started learning OCaml
<pippijn> let add (a : int) (b : int) : int = a + b
<pippijn> or
<pippijn> let add : int -> int -> int = fun a b -> a + b
<osa1> most of this code is pattern matching, where should I add type declarations?
<pippijn> you can add identity functions with explicit types to see where things break
<mrvn> osa1: you can add types pretty much anywhere in your code
<mrvn> experiecne will teach you where it makes most sense
<mrvn> osa1: In you case the error is that you need "let rec derive"
<mrvn> Warning 11: this match case is unused.
<mrvn> val derive : 'a parser -> 'b -> 'a parser = <fun>
<mrvn> Literal token and Literal _ match the same thing
<osa1> great, thanks.
phao has quit [Quit: Not Here]
<osa1> is there a generic function to compare records or should I create one for each record I create?
<mrvn> Pervasives.compare
avsm has quit [Quit: Leaving.]
<mrvn> or just <, >, =, <>, ==, !=
<osa1> mrvn: I'm getting Exception: Invalid_argument "equal: functional value". error
<osa1> oh, thats because I have a fun in my record
<mrvn> you can't compare functions other than ==
<mrvn> so yes, you need your own compare for the record
<yezariaely> you cannot somehow overwrite the pervasives.compare for specific types?
<mrvn> no. Not enough runtime type information for that
ski has quit [Ping timeout: 252 seconds]
ski has joined #ocaml
wtetzner has joined #ocaml
<osa1> does built-in types have string representations? functions like bool -> string or int -> string ?
<Qrntz> string_of_bool, string_of_int are the conversion functions
bokuk has joined #ocaml
hto_ has joined #ocaml
osa1 has quit [Quit: Konversation terminated!]
Yoric has quit [Ping timeout: 264 seconds]
flux has joined #ocaml
silver has quit [Read error: Connection reset by peer]
silver has joined #ocaml
eni has joined #ocaml
struktured has quit [Ping timeout: 265 seconds]
snearch has joined #ocaml
Yoric has joined #ocaml
sgnb has joined #ocaml
Yoric has quit [Ping timeout: 265 seconds]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
sivoais has quit [Read error: Connection reset by peer]
sivoais has joined #ocaml
osa1 has joined #ocaml
avsm has joined #ocaml
osa1 has quit [Quit: Konversation terminated!]
mehdid has quit [Remote host closed the connection]
osa1 has joined #ocaml
<osa1> why `let s = SomeData(lazy s)` doesn't work?
<yezariaely> works for me, osa1:
<yezariaely> # let s = 1;;
<yezariaely> val s : int = 1
<yezariaely> # let s = lazy s;;^CInterrupted.
<yezariaely> # type test = Ctor of int lazy_t;;
<yezariaely> type test = Ctor of int lazy_t
<yezariaely> # let s = Ctor(lazy s);;
<yezariaely> val s : test = Ctor (lazy 1)
mjonsson has joined #ocaml
<yezariaely> ah the interrupted line should have been deleted
<yezariaely> The constructor SomeDate must take an a' lazy_t!
<osa1> # type test = Ctor of int lazy_t;;
<osa1> type test = Ctor of int lazy_t
<osa1> # let s = Ctor(lazy s);;
<osa1> Error: Unbound value s
<osa1> yezariaely: strange, doesn't work for me
<yezariaely> ah sorry... I defined the s before
<osa1> yezariaely: yeah that's the point. the structure is recursive
emmanuelux has joined #ocaml
<yezariaely> the error message is kind of strange...
<yezariaely> Error: This expression has type test lazy_t
<yezariaely> but an expression was expected of type int lazy_t
<yezariaely> as there is the word "test" inside ...
<yezariaely> damn...
<yezariaely> my error
<yezariaely> gimme second
<yezariaely> I am to tired right now ^^
<yezariaely> ok:
<yezariaely> type 'a test = Ctor of 'a lazy_t;;
<yezariaely> let rec s = Ctor(lazy s);;
<yezariaely> with -rectypes command line switch
<yezariaely> then it workds
<yezariaely> osa1: ok
beginner has joined #ocaml
eni has quit [Ping timeout: 252 seconds]
<beginner> how can i determine the compile error if i only get File "test.ml", line 1, characters 0-1: Error: Error-enabled warnings (2 occurrences)
<osa1> yezariaely: great, thanks.
<osa1> yezariaely: do you know any other useful flags?
<yezariaely> beginner: nothing else?
<beginner> nothing else
<yezariaely> osa1: no, this is the only one i normally use. but it can lead to problems...
<beginner> it says little later that test.cmi was deleted
yezariaely has left #ocaml []
yezariaely has joined #ocaml
<yezariaely> beginner: can you paste the code?
<beginner> i dont think i can its work related
<yezariaely> can you paste a minimal example?
<yezariaely> try the following: it seems that you have the -wran-error applied. can you check this?
<yezariaely> warn, not wran
<beginner> is activated in the makefile
<yezariaely> can you remove it and try again?
<yezariaely> then look at the warnings it prints?
<yezariaely> or the errors and fix the warnings?
<beginner> how?
<yezariaely> how what?
<beginner> thats all i get make[1]: Zirkuläre Datei promela.cmi <- promela.cmi Abhängigkeit wird nicht verwendet. ocamlfind ocamlopt -package extlib -c -warn-error +a-4-6-7-9-27..29 -for-pack Promela cbmc.ml File "cbmc.ml", line 174, characters 21-163: Warning 8: this pattern-matching is not exhaustive. Here is an example of a value that is not matched: [] File "cbmc.ml", line 181, characters 21-161: Warning 8: this pattern-matching is not exhaustive. He
<beginner> so what to look for?
emmanuelux has quit [Ping timeout: 264 seconds]
<yezariaely> this is different to your first error message.
<beginner> i changed the file name to test in the first version
<yezariaely> maybe. but the error message is different
<yezariaely> you know what -warn-error does?
<beginner> no
<yezariaely> it treats the warnings as errors.
<yezariaely> so compilation fails if you get a warning
<yezariaely> here, the error messages 4-6-7-9-27..29 are excluded.
<yezariaely> so you got several warnings here
<beginner> ok, and where can i see the warnings, or is the not exhaustive pattern matching the reason?
<yezariaely> read your message please!
<yezariaely> "where can i see the warnings" < check the output!
<yezariaely> osa1: what do you want to do with it?
<yezariaely> beginner: please, tell me if the problem is solved
<beginner> i am still thinking about how i can fix my pattern matching in the code
<yezariaely> it tells you that you did not include the case of the empty list
<yezariaely> add it and the warning will disappear
<beginner> as soon as i fixed it i will inform you. Thanks for the help
<yezariaely> that's nice. I hate it, if you help people and they suddenly disappear...
<beginner> wouldnt do that
bokuk has quit [Ping timeout: 245 seconds]
<beginner> thanks a lot, i now works just fine :)
<yezariaely> you're welcome
bokuk has joined #ocaml
snearch has quit [Quit: Verlassend]
beginner has quit [Quit: irc2go]
hcarty has quit [Ping timeout: 244 seconds]
hcarty has joined #ocaml
bjorkintosh has quit [Quit: Leaving]
lorill has joined #ocaml
cdidd has joined #ocaml
gnuvince has quit [Ping timeout: 245 seconds]
gnuvince has joined #ocaml
beginner has joined #ocaml
<beginner> how can i pass arguments through a chain of function calls with opitonal arguments?
ski has quit [Read error: Operation timed out]
hto_ has quit [Quit: leaving]
<Drakken> beginner optional arguments are passed the same way as mandatory labeled arguments.
<Drakken> If caller foo and callee bar both use the name x for an argument, you can call bar ~x:x from inside foo.
<Qrntz> (or just bar ~x)
<beginner> my code looks like that Module1.string_of_lst ~pid:"hallo" but if i execute that then module1 prints only the default value. I have to mention that that called function is recursive (maybe that changes anything)
<mrvn> beginner: nope
<beginner> mrvn: nope to what?
<mrvn> being recursive doesn't change anything
osa1 has quit [Quit: Konversation terminated!]
<Drakken> maybe one of the function calls is missing the pid arg
osa1 has joined #ocaml
phao has joined #ocaml
<phao> does ocaml comes with some GUI library?
<mrvn> not ocaml
<phao> of course it is
<phao> there is a library that comes with it
<phao> I just am asking if there is some GUI functionality in there.
<mrvn> There is a graphics module, hardly a GUI. For a gui there is stuff like gtk. But that doesn't come with ocaml itself.
<phao> ok... thx
<beginner> mrvn: so it should be fine to do something like Module1.string_of_lst ~pid:some_string and then this function calls another function with string_of ~pid:some_string?
phao has left #ocaml []
<beginner> yezariaely: maybe you could help with my problem, like with the last one before?
<Drakken> beginner string_of ~pid:pid
lorill has quit [Remote host closed the connection]
<_habnabit> Drakken, fwiw if the name of the variable is the same as the name of the parameter, you can do ~pid
<Drakken> yea, Qrntz just posted that.
<Drakken> but it might be confuzing to a beginner
<Drakken> confusing
<beginner> i lost you
<beginner> what might be confusing?
<Drakken> that ~x is the same as ~x:x
<beginner> so if i call them differently it should work?
<Drakken> if you call what differently?
Sablier_ has quit [Read error: Connection reset by peer]
<Drakken> string_of_lst takes an argument called pid, so inside string_of_lst the value of the argument is called pid.
<beginner> instead of ~x:x ~x:something_different
<Drakken> that's not a chain
<beginner> is there an easy way how i can post my funtion calls?
<Drakken> copy & paste if they're only a line or two. pastebin if they're longer.
<beginner> let body = Module1.string_of_lst ~pid:"test" (Process.get_body x) in
<beginner> thats my initial call
<beginner> string_of_lst ?pid:(id="null") xs, thats the function i call
<beginner> and thats what this one calls
<beginner> (List.fold_left (fun a b -> a ^ "\t" ^ (string_of ~pid:test b) ^ "\n") "" xs) ^ "\n\t"
<Drakken> ?pid(id="null") should be ?(pid="null")
<Drakken> unless you want to call the pid "id" inside the function
<Drakken> what's test?
<Drakken> as it stands, it should be ~pid:id
<Drakken> that will pass "test" to string_of
<beginner> but it doesnt, or i missunderstand you
<Drakken> if the fold is in the body of string_of_lst, then id should be equal to "test"
<Drakken> when you call string_of_lst ~pid:"test"
<beginner> something inbetween, why do i need to write ?pid(p=10) if i could simply write ?(p=10) and use the variable p the same way in the code?
<Drakken> you don't need to
<Drakken> but pid is a more descriptive name than p
<beginner> but why did they design it this way, to allow bot approaches?
<Drakken> sometimes it helps to use a different name
<Drakken> like if a new pid is introduced in the body of the function, you might define the paramater as ~pid:old_pid, and then call the new pid new_pid
<Drakken> oops, I mean ?pid:old_pid
<beginner> i still understood ;)
<Drakken> you mean you _finally_ understand, or you still _mis_understand?
<beginner> i mean i could follow it if you mistype something, but the reason why i still get the defaul arguments is totally unclear to me
<Drakken> the only way you can get the default is if you don't specify a different value
<Drakken> or if the value you specify is the same as the default
<beginner> same name or value?
<Drakken> you should get a compiler error if you use the wrong label name.
<beginner> no compiler error
<Drakken> if you get a default value, then you didn't specify the optional argument.
<Drakken> you might test it by changing the ? to a ~
<beginner> the problem is i have lots of calls to that function, thats why i chose optional arguments
<Drakken> whatever. you can't get the default value unless you forget to specify the arg in a call somewhere, or the arg value is equal to the default.
<mrvn> raise an exception and check the backtrace
<beginner> i will try
emmanuelux has joined #ocaml
beginner has quit [Ping timeout: 245 seconds]
eni has joined #ocaml
eikke has quit [Ping timeout: 244 seconds]
greggies has quit [Ping timeout: 245 seconds]
Tobu has quit [Ping timeout: 248 seconds]
Tobu has joined #ocaml
mcstar has quit [Quit: mcstar]
ski has joined #ocaml
hcarty has quit [Ping timeout: 244 seconds]
hcarty has joined #ocaml
ski has quit [Ping timeout: 240 seconds]
ski has joined #ocaml