gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
fraggle_ has joined #ocaml
myu2 has joined #ocaml
jm_ocaml has quit [Ping timeout: 240 seconds]
<hcarty> Does wildly different memory use with and without calls to Gc.full_major in a loop indicate something buggy/bad?
<hcarty> Wildly different = 500-600 megabytes vs 5+ gigabytes
<hcarty> Or does it mean I should tweak some GC parameters?
Edward_ has joined #ocaml
thatch has quit [Remote host closed the connection]
accel has joined #ocaml
<accel> anyone know of an interior point algorithm written in ocaml?
<thelema> hcarty: you could try upping the size of your minor heap... what're you doing to allocate so much memory?
Yoric has quit [Quit: Yoric]
sandmann has quit [Ping timeout: 240 seconds]
ccasin has quit [Quit: Leaving]
boscop_ has quit [Ping timeout: 240 seconds]
myu2 has quit [Remote host closed the connection]
thatch has joined #ocaml
thatch has quit [Remote host closed the connection]
ftrvxmtrx has quit [Ping timeout: 276 seconds]
rofh has joined #ocaml
ftrvxmtrx has joined #ocaml
charlesno has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 246 seconds]
thatch has joined #ocaml
ftrvxmtrx has joined #ocaml
rofh has left #ocaml []
Edward_ has quit []
kaustuv_ has left #ocaml []
pencilk has joined #ocaml
charlesno has left #ocaml []
smrz has joined #ocaml
accel has quit [Quit: leaving]
<smrz> Hello, I'm new to OCaml. I need to write a function that takes two functions contained in a tuple as an argument, and returns a new function that composes the two arguments in sequence. Does anyone mind explaining how to do this? I'm not sure how to specify that the value returned from one function should be used as input to the second...
drunK has quit [Remote host closed the connection]
<thelema> let assignment (f,g) = ...
<thelema> smrz: ever programmed in any other language?
<smrz> maybe I'm not begin clear
<smrz> let compose (p:(('b -> 'c) * ('a -> 'b))) : 'a -> 'c =
<smrz> so, i would like something like:
<smrz> begin match p with
<smrz> | (x, y) -> x y
<smrz> end
<smrz> where the value returned by y is the argument for x
<thelema> almost - x y passes the function y as the first parameter to x
<smrz> right
<smrz> i understand that
<smrz> but how to I combine them into one function?
<thelema> try | (x,y) -> (fun a -> ...)
<thelema> s/try//
<smrz> right, but what about the '...' part?
<smrz> sorry if this is an obvious question, but I've been looking around and for some reason it's not clear to me
<thelema> I assume you're a student working on an assignment, so I'm going to be a bit pedagogical here...
<smrz> thelema that's fine, i'm not offended
<smrz> and yes, you're correct
<smrz> i'm not trying to get you to do my work for me, just trying to figure out the basics of ocaml syntax
<thelema> if you had defined functions x and y (i.e. let x a = ... b in let y b = ... c in)
<thelema> how would you take a value a and apply both x and y to it?
<thelema> let's say you had value a as well (let a = ... in)
<smrz> well you could do y ( x a)
<smrz> right?
<thelema> let x a = string_of_int (a + 5) in let y b = [b^"foo"] in let a = 3 in y (x a)
why has joined #ocaml
<thelema> try that out in your toplevel
<thelema> (I assume you're at a computer w/ ocaml installed on it)
<smrz> right
<smrz> no that makes sense to me
<smrz> i guess what I'm not clear about, is given my definition:
<smrz> let compose (p:(('b -> 'c) * ('a -> 'b))) : 'a ->
<smrz> let compose (p:(('b -> 'c) * ('a -> 'b))) : 'a -> c' =
<smrz> you're not given the variable you want to compute
<smrz> so, that would make more sense to me if the definition was:
<smrz> let compose (p:(('b -> 'c) * ('a -> 'b))) (q:'a) : 'c
<thelema> you have to return a function, right?
<smrz> yes
<thelema> so return the function (fun a -> ...)
<smrz> so, something like:
<smrz> | (x,y) -> fun a -> x ...
<smrz> but I can't put y there, because the compiler gives me a type error
<thelema> because y is a function of type ('a -> 'b) and x doesn't take that kind of vale as its parameter
<thelema> *value
<smrz> right
<smrz> sorry if it feels like i'm moving horribly slow
<thelema> okay, | (x,y) -> (fun a -> let temp = ... in ... )
Amorphous has quit [Ping timeout: 272 seconds]
<why> what am i doing wrong :::::: let greetings name = if name = "Sam" then "Hi " ^ name else "Hello, " ^ name ^ ". How are you?";;
<why> if you dont mind me asking
<thelema> why: it looks good to me - what's the error?
<why> This expression has type (unit -> unit) * (unit -> string) but an expression was expected of type (unit -> unit) * (unit -> unit)
<why> i have program that tests my functions
<thelema> why: I see nothing in what you typed that's a pair, are you sure the error is there?
<thelema> unless you're using smart quotes
<smrz> Ah! okay, how's this:
<smrz> | (x, y) -> (fun a -> let temp = y a in x temp)
thatch has quit [Ping timeout: 240 seconds]
thatch has joined #ocaml
<thelema> smrz: does it have the right type?
<why> Aww, i am supposed to actually print the string
<smrz> thelema: do you mean I should have (a:'a) instead?
<thelema> smrz: no, you already have too many type annotations
<thelema> smrz: I'm just encouraging you to put that into the toplevel (without type annotations) and see what type it infers
<smrz> ah, okay
<smrz> yeah that doesn't seem completely correct
<smrz> actually, no
<smrz> it does
<smrz> val compose_pair : ('a -> 'b) * ('c -> 'a) -> 'c -> 'b = <fun>
<smrz> is that what you mean?
<thelema> smrz: yes
<smrz> right
ftrvxmtrx has quit [Ping timeout: 250 seconds]
<smrz> okay, and you don't like all the type annotations?
<smrz> is that a style thing?
<thelema> smrz: mostly
<smrz> thelema: are there other issues with it ?
thatch__ has joined #ocaml
thatch has quit [Ping timeout: 276 seconds]
<thelema> smrz: they can prevent your program from being able to adapt to type changes, if you decide that you want a record instead of a tuple, you'll have to change the type annotations *everywhere* values of that type are passed, as opposed to just where the values are inspected.
<smrz> thelema: ah, makes sense
<smrz> thelema: I really appreciate all your help; thank you.
Amorphous has joined #ocaml
ymasory has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
<thelema> smrz: you're welcome
myu2 has joined #ocaml
thatch has joined #ocaml
thatch__ has quit [Read error: Connection reset by peer]
ftrvxmtrx has quit [Ping timeout: 272 seconds]
myu2 has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
<mrvn> smrz: you could also just write let compose (x, y) = fun a -> x (y a) or even simpler plain let compose x y a = x (y a)
<mrvn> smrz: no need to tuple the functions.
<mrvn> smrz: You can also cosider using # let compose (x, y) a = y (x a);;
<mrvn> val compose : ('a -> 'b) * ('b -> 'c) -> 'a -> 'c = <fun>
<smrz> mrvn: thanks, that is clearer. The tuple stipulation, though, isn't mine, so I have to work with it.
<mrvn> Applying x first makes for a nicer type. Sure that isn't what was asked?
<smrz> I'm not sure I understand the point your making, but the tuple has this type stipulated:
<smrz> (p:(('b -> 'c) * ('a -> 'b)))
<smrz> so I need to apply y first, then x
<mrvn> ok. odd.
* smrz shrugs
<mrvn> The tuple requirement is also odd. You do that in languages where you can't have multiple parameters, where you have to write let compose = function x -> function y -> function a -> x (y a)
<mrvn> but who nows what teachers come up with. :)
<mrvn> could even be something so you can't just google the answere. :)
<smrz> hah, i hope my prof doesn't feel the need to do things like that
<mrvn> he might just have started with a different language where you generally use tuples for multiple arguments
<smrz> yeah maybe
<smrz> though he's very all-about-ocaml
<mrvn> good. ocaml deserves more promotion
<mrvn> let integer i s = Printf.sprintf "%s %d" s i let real r s = Printf.sprintf "%s %f" s r let f = integer 1 $ integer 2 $ real 3.0;;
<mrvn> # f "The three values are";;
<mrvn> - : string = "The three values are 3.000000 2 1"
<mrvn> The fun of ocaml. :)
<mrvn> # let ( $ ) x y = fun a -> x (y a);;
<mrvn> val ( $ ) : ('a -> 'b) -> ('c -> 'a) -> 'c -> 'b = <fun>
<mrvn> for your compose.
<smrz> okay, explain what the ( $ ) is doing
<mrvn> $ is an infix operator like +, -, *, /. The () is a syntax requirement when defining an operator.
<smrz> ah, so you can do x $ y?
<mrvn> or: # let ( + ) x y = Printf.printf "adding %d + %d = %d\n" x y (x+y); x+y;;
<mrvn> val ( + ) : int -> int -> int = <fun>
<mrvn> # 1+2;;
<mrvn> adding 1 + 2 = 3
<mrvn> - : int = 3
<smrz> hah, awesome
<mrvn> What do you thing let f = ( + ) 1 does?
<smrz> would that be a partially applied function?
<mrvn> yes.
<smrz> so x + would be the same as x + 1?
<mrvn> f x you mean
<mrvn> The ( <operator> ) syntax comes in handy when you want to pass it as argument to another function too. Did you have to write a function to compute the sum of a list of ints yet?
<smrz> sorry, yes
<smrz> no, but i'm doing similar problems
<smrz> working right now on writing a recursive function to handle list insertion
<smrz> (in a sorted list)
<smrz> so, something that would be called like:
<smrz> f [1;4;7] 5
ftrvxmtrx has quit [Ping timeout: 240 seconds]
<mrvn> smrz: got it yet?
<smrz> mrvn: yeah, mind taking a look at it though?
<smrz> I'd love any pointers on how to write things better
<mrvn> go ahead
<smrz> (you'll have to excuse the type annotations, heh)
<smrz> let rec insert (x:'a) (l:'a list) : 'a list =
<smrz> begin match l with
<smrz> | [] -> [x]
<smrz> | h::tl -> if (h < x) then h::(insert x tl) else if (h = x) then l else x::h::tl
<smrz> end
<smrz> (it's stipulated that if the element already exists in the list, you shouldn't add a second instance)
<mrvn> oh, no duplicates?
<smrz> yeha
<smrz> yeah*
<mrvn> I allowed duplicates
<mrvn> hey, you reversed the arguments too.
<mrvn> 06:19 < smrz> f [1;4;7] 5
<smrz> ah yeah, sorry
<smrz> so for this assignment, the prof basically gives us the top line of each function
<mrvn> In your case: Just because x > h doesn't mean the next element in the list is > x.
<mrvn> You have to check tl recursively.
<smrz> it's stipulated the list given is sorted
<smrz> hold on
<smrz> aren't I checking that though?
<smrz> I have if (h < x) then h::(insert x tl)
<mrvn> oh, sorry. I thought the x::h::tl was h::x::tl. too early for me.
<smrz> heh fair
<smrz> you in EST?
<mrvn> 6:35 here
<mrvn> You can write your code as: http://paste.debian.net/105226/
<mrvn> But using "if" is fine too. Only change I would do is to replace h::tl with l.
<smrz> ah yeah that makes sense
<mrvn> and loose the begin/end.
<smrz> heh, my prof wouldn't like you
<smrz> so looking at your code
<smrz> (your soln, not your rewriting of mine)
<smrz> just the first fn:
<smrz> let rec insert list x =
<smrz> match list with y::ys when y < x -> y::(insert ys x) | _ -> x::list;;
ftrvxmtrx has joined #ocaml
<smrz> this doesn't stipulate what to do when y == x or y > x
<smrz> or does it and I'm just not seeing it?
<mrvn> smrz: the _ catches all
<smrz> oh!
<smrz> got it
<mrvn> as said, it allows duplicates.
<smrz> yeha
<mrvn> Using the "when" syntax you can combine the case of [] and h::tl with h > x.
ulfdoz has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 246 seconds]
<mrvn> smrz: whats next? sorting a list using the insert?
<smrz> tail recursion, but i *think* i have it working
<smrz> although now eclipse is being difficult
thatch has quit [Remote host closed the connection]
<mrvn> smrz: that would be the (* For LONG lists *) part then. :)
<smrz> yeah so talk to me about this LONG list part
<smrz> tail recursion is generally faster?
<mrvn> tail recursion means the compiler doesn't need to use up stack space for the recursion. That way you don't run into the stack limit
<smrz> oh, right
<smrz> but is there a speed boost as well?
<mrvn> Other than that it is usualy slower.
<mrvn> or maybe same speed.
<mrvn> A non tail recursive call needs to add a new stack frame. So it has to waste some minimal time there. So it could be faster with tail recursion. In this case though you need to create a accumulator as you recurse and then unravel that on the way back. That costs time too.
<flux> wouldn't tail recursion would generally be faster, but sometimes if you have code that isn't naturally tail recursive, and the converted version might not be..
<mrvn> flux: do you know if a tail call skips the GCs unregister root / register root?
<mrvn> A tail call to the same function that is
<mrvn> flux: How would you write a non tail recusive function if the problem is naturally tail recursive? Add an extra try ... with? :)
<flux> mrvn, I'm thinking problems that naturally lend themselves to tail recursive solutions. the solution doesn't always accidentally become tail-recursive. although I don't have examples of this :)
<mrvn> flux: maybe factorial.
ftrvxmtrx has joined #ocaml
<mrvn> I can't think of a function that can be written both ways and is complex enough to eat up considerable time before stack overflow.
<mrvn> Or it is so complex the recursive call won't matter either way.
<mrvn> fac 200000;; is around the stack limit and takes no time.
<mrvn> recursive: ./foo 0.01s user 0.01s system 91% cpu 0.015 total
<mrvn> tail: ./foo 0.00s user 0.00s system 89% cpu 0.008 total
<mrvn> One learns something new every day. Tail recusive is actually significantly faster.
cyanure has joined #ocaml
<ulfdoz> mrvn: That is not really surprising, as it is basically transformed into a while loop. In theory it should be possible to transform it in to code, that does not even grow the stack.
myu2 has joined #ocaml
<mrvn> ulfdoz: tail recursion does not grow the stack
<mrvn> http://paste.debian.net/105232/ One thing one could do better is to untag the values inside the loop.
Snark_ has joined #ocaml
<smrz> alright, mrvn, i have a new question
<smrz> if you're game
<mrvn> shoot
<smrz> I'm given the following toy language
<smrz> and an expression such as
<smrz> let e1 : exp = Mult(Const 2l, Const 3l) (* "2 * 3" *)
<smrz> How do I do pattern matching over an expression like e1?
<mrvn> match e1 with Mult(sub1, sub2) -> ..
<smrz> sorry, how would I go about doing pattern matching on an arbitrary expression in the toy langauge?
<smrz> (also, i'm loving meta langauge vs. object/toy language --- I was a philosophy undergrad, and this concept maps almost perfectly onto a concept in philosophy of (natural) language)
<mrvn> you have to match each case seperately
<mrvn> smrz: there are more complex languages that have up to 5 levels of meta.
<smrz> heh, let's just stick to this for now :)
pencilk has quit [Remote host closed the connection]
accel has joined #ocaml
ulfdoz has quit [Ping timeout: 276 seconds]
<accel> if you agree that ocaml is the best programming language ever, paypal me $1.00 usd :-)
<mrvn> smrz: http://paste.debian.net/105236/, enjoy.
<smrz> oh man
<mrvn> smrz: fun would be to write code that outputs asm code for the expression. i.e. compiles the thing.
<smrz> yeah, that's next week
<smrz> we're using x86lite
<mrvn> ouch. x86 asm really sucks. lite can't make it better. We did that with powerpc in the "building a compiler" course.
<accel> is x86lite an ocmal library
<accel> for outputting assembly?
almaisan-away is now known as al-maisan
<mrvn> We went from scratch to a working compiler for a subset of ocaml in one semester.
<smrz> x86lite is a subset of x86 assembly
<accel> waht does scratch mean? you could use ocaml? you could use gcc? you could use x86? you were handed a bunch of transistors? you had to trigger the big bang?
<mrvn> accel: 0 lines of ocaml code.
<accel> so you could an ocmal compiler in ocaml?
<accel> you had ocaml/emacs/linux as tools
<mrvn> yes.
<accel> that is kinda cool
<accel> can you post a link to the course material?
<mrvn> that was ~10 years ago
<smrz> never date yourself on the Internet!
<mrvn> We also did invent the wheel for everything. So not using the ocaml stream parser, regexps, lex or yacc. We had to "invent" them first.
<mrvn> You would never do that in real life but that way you learn about each step.
<accel> back in my college years
<accel> we would have to creat efire, trigger the stone age, the bronze age, the iron age, the industrial revolution, invent the transistor, then start building compilers
<mrvn> .oO(When we played doom on the VT52 terminals)
cyanure has quit [Remote host closed the connection]
smrz has quit [Quit: Computer has gone to sleep.]
smrz has joined #ocaml
ttamttam has joined #ocaml
cyy has joined #ocaml
<cyy> how feasible would it be to implement Python's grammar using camlp4 (or camlp5) -- since its whitespace sensitive?
<smrz> okay, time for bed, thanks for all the help mrvn
jamii has joined #ocaml
edwin has joined #ocaml
why has quit [Quit: Page closed]
ikaros has joined #ocaml
ygrek has joined #ocaml
<accel> wtf
<accel> why is there no chatter in this channel
<accel> do ocaml programmers spend their time working?
<flux> cyy, apparently it's quite tricky
<flux> the white space thingy-developer opted to use non-camlp4/5-solution
<accel> is ocaml not white space sensistive?
<flux> it is only sensitive in the sense either there is white space or there isn't
<cyy> yeah I saw that... hm
<cyy> python's grammar is not context-sensitive or anything, it just needs the lexer to read whitespace as a token
<accel> hello
<accel> does anyone hear me?
<cyy> yes accel
<accel> have i been isolated in #ocaml?
<accel> ah, so is ocaml white space sensistive?
<flux> accel, did I not react to your message?-)
<cyy> flux answered it
<accel> oh
<flux> the same as C, etc
<accel> got it; thanks
<accel> I guess ocaml ppl do not like to type a<TAB>
<accel> as in
<accel> accel: it's not white space sensistive
<accel> :-)
<accel> (wasn't sure if flux was replying to cyy)
<cyy> i'll have to see if I can get camlp4's lexer to see whitespace as significant, there must be a way
<mrvn> cyy: I wouldn't be surprised if here isn't.
<cyy> mrvn: do you know what the appropriate mailing list might be to ask about this?
<accel> camlp4's lexer is _that_ limited?
<accel> where you can't even define your own lexer?
<cyy> it looks like you can maybe write your own lexer
<cyy> by reimplementing the Lexer interface
LeNsTR has quit [Quit: LeNsTR]
<cyy> I wonder if anyone has tried that
ftrvxmtrx has quit [Quit: Leaving]
<cyy> well if not, this is a nice blog entry. doesn't look super hard: http://ambassadortothecomputers.blogspot.com/2010/08/reading-camlp4-part-10-custom-lexers.html
al-maisan is now known as almaisan-away
ikaros has quit [Quit: Leave the magic to Houdini]
ygrek has quit [Ping timeout: 240 seconds]
Yoric has joined #ocaml
accel has quit [Quit: leaving]
accel has joined #ocaml
avsm has joined #ocaml
ygrek has joined #ocaml
myu2 has quit [Ping timeout: 276 seconds]
myu2 has joined #ocaml
Edward_ has joined #ocaml
emias has joined #ocaml
jm_ocaml has joined #ocaml
smerz has joined #ocaml
mnabil has joined #ocaml
ftrvxmtrx has joined #ocaml
ttamttam has left #ocaml []
<accel> how does ocaml search for files?
<accel> i.e. if I'm in ~/blah
<accel> and I want to refer to ~/blah/foo/bar/Set.ml
<accel> how do I do so?
<eaburns> ocamlc -I ~/blah/foo/bar
<accel> i'm in ~/blah/test.ml
<accel> and inside of test.m I want to refer to ~/blah/foo/bar/Set.ml
<accel> if I wanted to refer to ~/blah/Queue.ml
<accel> I could just use (in test.ml) Queue.-----
<eaburns> ocamlc -c foo/bar/Set.ml ; ocamlc -I foo/bar test.ml
<eaburns> that seems to work for me
<accel> so I have to specify a pass?
<accel> a _path_ ?
<gildor> accel: just as in C
<accel> in C, with #include , I can refer to files not directly in the same directory
<eaburns> yeah, you have to tell it to include foo/bar in the path
<accel> i.e. I can do #include <blahblah/foo/cat/dog.h>
<accel> rather than attaching a -I/blahblah/foo/cat onto the gcc line
<accel> so there's no way to tell ocaml to look into directories ?
<gildor> accel: indeed, you can do both
<accel> gildor: how do I do the latter
<accel> suppose ony ~/blah is in ocaml's path
<gildor> (in C)
<accel> how do I in test.ml tell it to load ~/blah/foo/bar/Set.ml ?
<gildor> accel: there is a way to do this through the module system
<gildor> accel: but it is not very convenient
<accel> so ... keep all *.ml files in the same directory?
<accel> what is the right way to hanle mult directory ocaml projects
<eaburns> use ocamlbuild and use the include directive in the _tags file
<gildor> accel: and upstream of OCaml has talked about doing exactly what you want -- but it is just a project
<flux> accel, I've used ocamlfind to manage largish projects with clearly separate submodules
<eaburns> I am less familiar with ocamlfind than I should be, but if you are using ocamlbuild to build your project then you can put '"foo/bar": include' in the file blah/_tags. Then you can use 'ocamlbuild test.native' to build
ygrek has quit [Remote host closed the connection]
<eaburns> If your project is big enough for multiple directories, you may also want to look into oasis. I used it a while ago for a project and I thought that it was pretty nice
<gildor> eaburns, accel: indeed with oasis you can say that Path: blah and Modules/InternalModules: Queue, foo/bar/Set
<gildor> it will automatically include foo/bar
<gildor> (i.e. set it in ocamlbuild's _tags file)
<gildor> but if there is a Set.ml in blah/ it won't work
<accel> i'm slightly surprised
<accel> after all these years, ocaml hasn't solved this problem :-)
<accel> but then again, when in rome, do as the romans do
<accel> time to learn theocaml style
<gildor> accel: because there are workarounds
<gildor> accel: all PL around have problems, anyway
<accel> yeah; but most problems are _deep_ / as a result hard to fix
<accel> whereas this seems a very superficial problem
<accel> like something fixable with plastic surgery
<gildor> and consider as cosmetic
<gildor> so the priority is less important than a bug in the compiler
<gildor> you can see this as a Feature Request, rather than a bug
<gildor> (moreover upstream maybe don't like the java.system.io.blah.foo.bar style ;-)
<accel> and after all these years
<accel> no one has bothered to implement the feature?
<gildor> no, because people can lvie with it
<flux> I wonder how it should work then
<flux> directories should automatically become module hierarchies?
<gildor> flux: yes, I think it was the proposal
<gildor> flux: but Xavier told us that he waits for a path
<gildor> path -> patch
* gildor time for lunch
<adrien> that's what I remember too, and I think I've done too much shell scripting lately because I was thinking that it could be done with some scripting in the build system =/
<adrien> bon appétit =)
<accel> hmm
<accel> so deos this eman my program
<accel> can not use two modules of the same name?
<eaburns> correct
<accel> i.e. I can't have Dog/Toys.ml and Cat/Toys.ml ?
Yoric has quit [Quit: Yoric]
<eaburns> at least, I am not aware of a way to directly do that
<eaburns> You can use mlpacks to get the behavior that you want
<eaburns> so, you would build all of the modules in Dog and then 'pack them' as submodules in a Dog module. Do the same for Cat. Then you can use Dog.Toys and Cat.Toys
<adrien> you'd have to "hide" the one(s) you don't want to use to the build system
<eaburns> but, I think that they problem is they both need to be used
<adrien> now, that might seem like an annoying limitation but I think it's not a terrible thing because it's probably clearer
<adrien> ah, both, not possible afaik
<adrien> or, possible, but that might get ugly and painful ;-)
<accel> hmm; multiple files of the same name is probably a bad idea too I guess
drunK has joined #ocaml
<adrien> I currently use different modules with the same name in a project but I've separated them quite well (I think they even create different executables)
cyy has quit [Quit: cyy]
<accel> type vec3 = { x : float; y : float; z : float; };;
<accel> let add v1 v2 =
<accel> how do I define add to do component wise addtin ?
<eaburns> let add v1 v2 = { x = v1.x +. v2.x; y = v1.y +. v2.y; z = v1.z +. v2.; }
<accel> let v+ v1 v2 = { x = v1.x +. v2.x; y = v1.y +. v2.y; z = v1.z +. v2.z; }
<accel> is there a way I can call it v+ instead of add?
<accel> perferably, I want to do :
<accel> v1 v+ v2
<flux> with camlp4. but otherwise, perhaps +| would do for you.
<flux> that would be lexed the same as v1 v + v2 anyway,w hich is the same as (v1 v) + v2
<eaburns> you can make an infix operator for it, but it cannot begin with a 'v'
<accel> why not?
<accel> what can it begin with?
* eaburns looks it up
<flux> an operator consists of operator characters, and its first character indicates its precedence
<accel> do you have a link?
<flux> the ocaml manual has a section on the language definition
<eaburns> here's the precedence table
<eaburns> here's the symbols for infix operators
<eaburns> so, it must begin with an 'infix-symbol' and it may be followed by any 'operator-char'
<eaburns> for example: let ( +! ) v1 v2 = ... in v1 +! v2
<accel> I don't understand this:
<accel> infix-symbol::= (= ∣ < ∣ > ∣ @ ∣ ^ ∣ | ∣ & ∣ + ∣ - ∣ * ∣ / ∣ $ ∣ %) { operator-char }
<accel> operator-char::=! ∣ $ ∣ % ∣ & ∣ * ∣ + ∣ - ∣ . ∣ / ∣ : ∣ < ∣ = ∣ > ∣ ? ∣ @ ∣ ^ ∣ | ∣ ~
<accel> so +abcd is an invalid infix symbol?
<flux> yes
<eaburns> correct
<flux> a+b is lexed the same as a + b
<accel> i understand BNF; I just thought I was misreading something
<flux> you cannot modify the lexing behavior in ocaml (without camlp4/5)
<accel> time to learn camlp4
<eaburns> I see
<flux> well, there are other approaches to that
<flux> based on camlp4 of course
<flux> I mean, using camlp4 for something like that might be considered overkill :)
<flux> http://pa-do.forge.ocamlcore.org/ can perhaps do what you want
<flux> it would then work like V.(v1 + v2)
<accel> Overkill? I was born to kill ants with nukes.
<accel> Vec3.ml:
<accel> type vec3 = { x : float; y : float; z : float; };;
<accel> cat Quat.ml
<accel> type quat = { v : Vec3.vec3 ; w : float; }
<accel> why can't I compile Quat.ml ?
<accel> ocaml Quat.ml
<accel> File "Quat.ml", line 1, characters 18-27:
<accel> Error: Unbound type constructor Vec3.vec3
<adrien> well, what's the issue? maybe it needs to know the type
<accel> is Vec3.vec3 not a type?
<accel> vec3 is a record define in Vec3.ml
<adrien> it is, but how do you compile? what's the ocaml* invocation?
<accel> ocaml Vec3.ml; ocaml Quat.ml
<accel> File "Quat.ml", line 1, characters 18-27:
<accel> Error: Unbound type constructor Vec3.vec3
<eaburns> ocamlc?
<accel> ah
<accel> I'm an idiot
<accel> it works now
myu2 has quit [Remote host closed the connection]
<accel> is there a way to do : type blah = { ... } such that objects of type "blah" can only be created via "make_blah", rather than { ... }
<eaburns> look at 'private'
<flux> you would use module interfaces to publish the type as abstract or private
<accel> not documented there
<accel> ah; private
<accel> i see
accel has quit [Quit: leaving]
<eaburns> its in the language extensions
boscop_ has joined #ocaml
fraggle_laptop has joined #ocaml
myu2 has joined #ocaml
jm_ocaml has quit [Remote host closed the connection]
eye-scuzzy has quit [Quit: leaving]
ygrek has joined #ocaml
LeNsTR has joined #ocaml
myu2 has quit [Remote host closed the connection]
myu2 has joined #ocaml
ccasin has joined #ocaml
seafood has joined #ocaml
ygrek has quit [Ping timeout: 240 seconds]
cyanure has joined #ocaml
Yoric has joined #ocaml
seafood has quit [Ping timeout: 250 seconds]
BiDOrD has quit [Ping timeout: 264 seconds]
BiDOrD has joined #ocaml
Associat0r has joined #ocaml
<edwin> + ocamlfind ocamldep -package unix -package num -modules src/cryptokit.mli > src/cryptokit.mli.depends
<edwin> ocamldep: unknown option `-modules'.
<edwin> ^looks like wrong version of ocamlfind?
<edwin> ocamldep accepts -modules...
<edwin> ocaml-findlib-1.1.2pl1-16.el5.src.rpm
<thelema> edwin: if you can, try upgrading to findlib 1.2.5
<edwin> is it available for RHEL5?
<thelema> it's available as source. rwmjones would know more about any rpms - he's the redhat guy around here
<edwin> hmm it doesn't even try to run ocamldep
<edwin> it just says -modules is unknown, I straced it
<thelema> edwin: RHEL6 has 1.2.5
almaisan-away is now known as al-maisan
<edwin> rwmjones: are there any working ocaml-findlib packages for RHEL5? the one I got (1.1.2) doesn't know about ocamldep -modules ...
cyanure has quit [Remote host closed the connection]
myu2 has quit [Remote host closed the connection]
<edwin> alternatively is there a way to disable usage of -modules in _oasis?
<gildor> ouch, ocamlfind 1.1.2 is quite old
<edwin> thats what comes with RHEL5
<edwin> I'll see if using GODI is any easier
<gildor> edwin: 1 solution for you, create an ocamlfind shell script and remove the -modules before calling the real ocamlfind
<edwin> than finding working packages for RHEL5
<edwin> ah good idea
<gildor> gildor: and submit a feature request to oasis to use ocamlfind as defined in setup.data (i.e. at configure step)
<edwin> and another for oasis to check for working findlib ;)
<gildor> edwin: for now, we use "ocamlfind" but we should load this value in myocamlbuild.ml from setup.data
<gildor> edwin: you mean to to have at least findlib >= 1.2.X
<gildor> ?
<gildor> but that should be a combination between using ocamlbuild and findlib
<gildor> -> E or W when compiling _oasis in setup.ml
<edwin> no, I mean just running ocamlfind ocamldep -modules and checking that it works
dark has joined #ocaml
<dark> http://codepad.org/lobvxlbk This kind of expression is not allowed as right-hand side of `let rec'
<dark> can someone help me understand that?
<gildor> edwin: oasis relies more on version than on live test
<gildor> (i.e. not like autoconf, but this is on purpose)
<flux> dark, the right-hand side of let rec is a function, and those aren't allowed
<dark> ? õ.o
<dark> i would never think of such restriction on my own
<dark> do you know why?
Snark_ is now known as Snark
<flux> well, you can put arguments and it works
<dark> yeah, i discovered the hard way :)
<flux> I think it's one aspect of the '_a typing
<dark> but, couldn't the compiler put arguments on himself?
<dark> hm õ.o
<dark> i mean: the compiler knows the arity of everything. and it knows that if f has arity n, f is the same as (fun a1 a2 .. an -> f a1 a2 .. an)
<dark> so it could lift this in all cases, if he wished to
<flux> but, think when it is evaluated
<flux> let rec a = b evaluates b immediately
<flux> as would be rec a = b; c
<flux> and perhaps it thinks that b can have a side effect.. just rambling here :-)
<dark> hmm o.o
<dark> yes, but, functions can't have side effects..
<dark> but, yes
<dark> let rec a = b; c isn't the same as let rec a x = b; c x
<dark> but, why it has this restriction just for let rec? õ.o
<thelema> It's possible that the thing on the right hand side has side effects, and how those would be encapsulated within a recursive call isn't clear
<dark> (i mean: if f is a function, evaluating f can't have side effects)
<dark> i saw this a; b thing, but this would apply for non-letrec too
<thelema> if f is a function, with an argument right there, then it definitely can't
<flux> if you remove the recursion, it works
smrz has quit [Quit: Computer has gone to sleep.]
<thelema> flux: except for possibly some '_a problems
<mrvn> dark, flux: The flatten_sum example works just fine here. Ocaml 3.11.2
Modius has quit [Quit: "Object-oriented design" is an oxymoron]
<mrvn> aeh, never mind. I mispasted.
<mrvn> I wish I knew why sometimes when you highlight something in iceweasel X still has the last thing in the paste box.
<adrien> mozilla application sucks^W don't respect anythin
<adrien> they implement their own window and clipboard management
<mrvn> They also like to steal the focus seconds after you moved the mouse over the window onto something else.
<mrvn> or pop to the front.
<adrien> http://notk.org/~adrien/screenshots/firefox_still_does_not_listen_to_window_managers.png <- should have no decorations (and not even mentionning that it start fullscreen...)
<dark> talking about that, I am looking for making emacs work with ctrl+c ctrl+v clipboard (That's ok for C-w M-w C-y to work with select/middle mouse button clipboard)
<dark> it's frustating
<dark> C-v scrolls down .-.
<dark> (ok that is a question for ##emacs, but i don't expect to solve it anyway..)
<dark> I'm trying to build some algebra system, with letters and numbers. something smart, that would reduce 2x+x to 3x and so on. currently I'm trying to reduce just the numbers. I begun with a binary tree (Sum of expr * expr, etc) but I quickly discovered that to do the way I was trying to solve it was more productive to use folds and so on
<dark> so i have two tasks, a function to flatten a expression (to turn Sum [a; Sum l] into Sum ([a] @ l), and decompose a*(b+c) into a*b+a*c, and a function to reduce it, substituting numerical expressions by numbers
<dark> i think those functions need to be mutually recursive
<mrvn> don't see that
<dark> i didn't knew that this problem was so hairy o.o
<dark> i was thinking, it is going to be straightforward..
<mrvn> dark: why do you think Mathematica costs so much?
<dark> ahaha, but a _simple_ algebra is easier than the scilab-like part of Mathematica
<mrvn> How do you reduce a*b+a*c+b*c?
<dark> it is reduced already
<dark> i mean
<mrvn> how do you anti-decompose it?
<dark> this is my normal form
<dark> i will not anti-decompose; my normal form is sums of monomials
<dark> i mean, err, my normal form is the usual polynomial normal form
<mrvn> ok, that makes it a lot simpler. (and less readable results)
<dark> :)
<dark> I have only two operations, Sum and Mul
<dark> I will add a Pow to group x*x to x^2
<dark> it will be analogous to group x+x to 2*x
dgfitch has quit [Quit: Lost terminal]
<dark> my algorithm: if I have Sum [..], I separate [..] into numbers and non-numbers; the result is Sum (sum of numbers @ [reduce nonnumbers])
<dark> so Sum [Num 1.; Var 'x'; Num 2.] is Sum [3.; Var 'x']
<mrvn> So step one is to decompose everything, then sort the list and then merge identical terms
<dark> but I need to also include as numbers expressions that reduce to numbers
<mrvn> when decmposing you do partial evaluation on any operation involving 2 numbers
<dark> I was trying to write this decompose function.. I gave up while decomposing multiplications that might have sums on it
<dark> I'm now trying to reduce, and doing just one step of decomposition on my arguments, but this will not be enough...
dgfitch has joined #ocaml
oriba has joined #ocaml
<dark> I thought about decomposing and sorting, but it was when I was working with a binary tree. When I had only sum of two exprs. With sum of a list of exprs, I can just filter my list for constants (it's slower)
<dark> i mean, i don't plan to sort
<mrvn> does your parser output Sum of expr * expr or Sum of expr list?
<dark> Sum of expr list
<dark> I had Sum of expr * expr but my algorithms was becoming too awkward. (I am working with folds & friends now)
<mrvn> type expr = Num of float | Var of string | Sum of expr list | Mul of expr list
<mrvn> So you have something like that?
<dark> yes, exactly that. oh, not exactly, Var of char :)
<dark> of char because i want a convenient parser, like 2xy+xy => 3xy
* mrvn wants xy as var :)
<mrvn> 2 x y
<dark> uhm. @.@
<dark> I was thinking about Xy as being X with index y
<mrvn> but char or string doesn't matter after the parser is done.
<dark> yes
<dark> (I didn't liked my forced capitalization; your whitespace thing seems nicer :)
<dark> ok I think I will have decompose and reduce as separate steps
caligula_ has quit [Ping timeout: 255 seconds]
<dark> I think that while decomposing Mul [Num 1.; Sum [Num 2.; Num 3]; Num 4.], it would be nicer to do the 1*4 multiplication before
Associat0r has quit [Quit: Associat0r]
<dark> but then I return to my nemesis, decomposing and reducing being mutually recursive
<dark> maybe it is better to just decompose in the dumbest way, and try to combine smarter
<mrvn> dark: Mul of expr list makes it really complicated.
<dark> mrvn, but any algorithm for Mul of expr * expr can be used for Mul of expr list: Mul [] is Num 1., and Mul a::b is the same as (would be) Mul (a, <expand Mul b>)
<dark> the problem is, my algorithms for Mul of expr * expr became increasingly messed up (like, bare recursion for things i would rather use a high order function)
ftrvxmtrx has quit [Quit: Leaving]
ulfdoz has joined #ocaml
ikaros has joined #ocaml
<mrvn> Lets keep the variables in a term sorted: http://paste.debian.net/105288/
<dark> interesting, I use the let rec loop .. exactly as that
ulfdoz has quit [Ping timeout: 276 seconds]
<dark> and, hmm, I think that maybe I would want a term -> expr function
<mrvn> And lets keep the resulting list of terms sorted too: http://paste.debian.net/105290/
mbernstein has joined #ocaml
<dark> hmm o.o
numeromancer has joined #ocaml
<dark> thelema (or whoever knows), can I disable the "revised syntax" while pretty-printing on a batteries-enabled top-level?
<dark> # type a = int list;;
<dark> type a = list int
<thelema> dark: install the newest git of batteries and tell me if it solves the problem for you too
<dark> this is severely confusing me
<thelema> the patch that may fix this went in yesterday.
<dark> uhm will try later, thank you (I can easily lose focus. I'm now struggling to create a buffer named X, and set there an specific major mode, on emacs)
<dark> (and to think I thought earlier that I would move quickly to this stage for my little language: let x = 1 in x+2+y displaying 3+y. hah. I will take ages understanding this problem of normalizing the polynomial)
<dark> mrvn, anyway you decompose is nice @.@ do I really have to have a type for decomposed expressions?
<dark> i wanted decompose (and also the normalizing function itself) to return the same type, because i will be doing a lot of other things (like substituting variables)
<dark> but what I can do is to normalize just at the last step
<mrvn> dark: no.
<dark> ok
<mrvn> dark: char list * float does just fine
<dark> oh i meant, to make decompose : expr -> expr
<mrvn> I just find it helps type inference while developing
<dark> expr -> term would mean that my parser is string -> expr, and my pretty-printer is term -> string
avsm has quit [Quit: Leaving.]
<dark> this is a bit too uhm how can i say.. asymmetric?
<dark> but my output can't be non-normalized, so those might be accurate types
<thelema> dark: it should be pretty trivial to convert terms back into exprs
<mrvn> val e : expr = Mul [Var 'a'; Var 'a'; Sum [Var 'b'; Var 'c'; Var 'b']]
<mrvn> 2. a^2 b + a^2 c
<mrvn> That is what you wanted, right?
<mrvn> Mul [Num 3.; Var 'a'; Num 2.; Var 'a'; Sum [Var 'b'; Var 'c'; Var 'b']] ==> 12. a^2 b + 6. a^2 c
<mrvn> I would prefer 6 a^2 (2 b + c)
<thelema> mrvn: don't solve the whole problem for him right in his face unless he wants you to. :)
<dark> hah yes, i feel if i take it i also lose all the fun of it
<mrvn> dark: nah, implement you own. :)
<dark> but my problem with your code was that i felt that i wouldn't fully understand it (i need to change it a lot..)
<dark> in fact i begun trying to do everything at once, but the type errors convinced me to do a partial implementation :P
<thelema> dark: have fun implementing your own, when you're done or stuck, have a look at mrvn's code
<mrvn> And then make the thing tail recursive for extra fun. :)
<mrvn> dark: I tried doing it in one too. Gave that up quickly. Then I added the intermediate types and helper functions.
<hcarty> thelema: Thanks for the GC suggestion. The program is manipulating a large number of large multi-dimensional float arrays, so keeping things functional results in lots of garbage to collect :-)
<hcarty> thelema: I'm most concerned with making sure that this isn't indicative of a bug somewhere, since there is some C involved.
<thelema> dark: try to think about data types, as they can make a world of difference. mrvn's (float * char list) type basically sets how his whole program works
al-maisan is now known as almaisan-away
BiDOrD has quit [Remote host closed the connection]
<mrvn> thelema: char list * float actually so 2 a and 4 a sort before 3 b
<dark> oh now i see
<thelema> mrvn: sure.
<dark> I tried to work with expr -> expr instead of expr -> term because I wanted it to be free form; like, to be able to write a^b. so there would be cases where the thing would fail to normalize. when i reduced the operation set to + and *, i think mrvn's char list * float makes sense
<mrvn> dark: As a bit of explanation: pow builts the power list from a list list. (a+b) * (c+d) -> ac + ad + bc + bd.
<thelema> hcarty: hmmm, I imagine the functional-ness requires creating lots of new arrays... you're using BA, of course. I wonder how much benefit you'd get from mutating an accumulator
<mrvn> The decompose basically does an in order traversal of the expression accumulating the floats and vars along the way as it goes down.
<mrvn> When it reaches a leaves it outputs the term.
<mrvn> -s
<dark> hmm, I was using List.cartesian_product from batteries. My Mul was decomposed with a fold, accumulating the terms, and then doing a cartesian product (like your pow), and then it kept failing to type check and it got nowhere
<mrvn> The rest is then just finding duplicate terms in the resuling list of terms and dupliate vars inside each term.
<thelema> hcarty: there's a point where functional code without deforestation runs into physical bottlenecks, and I think your code is seeing that.
<mrvn> dark: The pow is a lot simpler if you have "Mul of expr * expr"
<hcarty> thelema: Thanks, I'll look in to all of this. For better or worse, the BAs are converted to normal OCaml arrays to ease manipulation by other functions.
<thelema> hcarty: that's quite worse, I expect. I understand why you're paining the GC
<hcarty> thelema: I just (re)found elehack's posting on GC tuning. I've been waiting for a chance to try some of what's talked about there.
<thelema> hcarty: I've found the heap size to be most important, and when allocating large values, turning down the space_overhead parameter temporarily as well.
<mrvn> dark: same code without the intermediate types: http://paste.debian.net/105294/
<dark> but your version with Term is actually more readable
<dark> my trouble was that the output of the simplification isn't expr. but it can be converted to expr as thelema pointed out
<mrvn> dark: Only is you add Pow of char * int
<dark> (I mean expr -> term and expr -> (char list * float) is the same thing)
<dark> hm. what i would have is Pow of expr * expr or something
<dark> and the normalization wouldn't be complete
<mrvn> dark: urgs, that gets really difficult to decompose
<dark> also i would use rationals instead of float, to have arbitrary precision. and then i *could* treat integers as a special case of pow (the one that would play nicely with polynomials, like your Pow of char * int)
<dark> but actually
<dark> i have trouble understanding the problem without such complications already :)
<mrvn> dark: Why not use type expr = [`Num of float | `Var of char | `Sum of expr list | `Mul of expr list] type res = [ `Mul of expr list | `Num of float | `Sum of expr list | `Var of char | `Pow of char * int ]
<mrvn> Then you can use the same pretty printer for expr and res
<dark> hm interesting o.o
<mrvn> dark: another idea is to already do the x^n in decompose/pow. The insert function would increment the power of a variable if it already exists.
<mrvn> type term = Term of (char, int) list * float
<mrvn> Term ([(x, 2); (y, 1)], 3.) --> 3 x^2 y
<dark> ultimately i want to type this: let x = 5 in 1^x, and the interpreter would say, 1. (what i mean is, in the end it seems that the result will potentially have the same operations of the input; so if ^ is allowed at input, those types are actually the same; if this is the case, i wouldn't need a variant)
<mrvn> dark: And one thing you also need to consider: Sum [Mul [Num 1.; Var 'x']; Mul [Num (-.1.); Var 'x']] --> T (0., [(x, 1)])
<dark> but with current constraints i think your types are interesting :)
<dark> oh
<dark> this one I already do
LeNsTR_ has joined #ocaml
LeNsTR_ has quit [Changing host]
LeNsTR_ has joined #ocaml
<mrvn> dark: a^(x+y) -> a^x * a^y?
<dark> hm yes, but this one i don't do :) i meant, 0 times anything is 0
<dark> http://codepad.org/FhJpcYfW lots of useless things (leftovers from older attempts) but
ulfdoz has joined #ocaml
LeNsTR has quit [Ping timeout: 240 seconds]
LeNsTR_ is now known as LeNsTR
<mrvn> dark: a / b ==> a * b^(-1)
<dark> Mul [] is 1, Mul [x] is x, Mul [one; x] is x, Mul [zero; x] is zero
<dark> and also
<dark> Sum [Num 1.; Var 'x'; Num 2.] is Sum [Num 3.; Var 'x']
<dark> because it collects all constants and sum them separatedly
<mrvn> That I already do
<dark> oh
myu2 has joined #ocaml
<dark> that M there is that I planned to make a map, from 'x' to, hmm, now i'm not sure..
<dark> the idea was to enable me to make x+x = 2x, but you certainly solved this better :)
<mrvn> Sum [Num 1.; Var 'x'; Num 2.] ==> + x
<mrvn> or maybe not.
<mrvn> val s : term list = [Term ([], 3.); Term (['x'], 1.)]
<mrvn> simplify_term is buggy
<mrvn> 3. + x
myu2 has quit [Remote host closed the connection]
<mrvn> Combining the plain Nums is just a special case of combining any 2 terms with the same variable list.
<mrvn> dark: I've added eliminating 0 terms: http://paste.debian.net/105302/
* dark is trying to understand how pow works
ftrvxmtrx has joined #ocaml
<dark> i'm starting to think that heavy functional programming might be write-only
<mrvn> dark: That is just your cartesian product and flatten
<mrvn> and sorting
ftrvxmtrx has quit [Client Quit]
<dark> my cartesian product did a map after it, because the output wasn't of form (a * b) list
ftrvxmtrx has joined #ocaml
<mrvn> for [a; b; c]::list is does (a * list) @ (b * list) @ (c * list)
<mrvn> and I acumulate the term as i recurse through the list of terms: loop one [a; b; c] -> loop (a) [b; c] -> loop (a b) [c] -> loop (a b c) [] -> (a b c)
mnabil has quit [Ping timeout: 240 seconds]
<hcarty> thelema: Do you know if there is a way to align the usage/help output from BatArg.handle? It doesn't look like there is, but I'm not certain.
<dark> mrvn, i think I will try to make Mul of expr * expr | Sum of expr * expr | ..
<mrvn> dark: that is much simpler to understand.
<hcarty> thelema: If not, I'll submit a bug report and (hopefully) a patch
<mrvn> Then you have just Lift.fold_left (fun acc e1 -> List.fold_left (fun acc e2 -> (mul e1 e2) @ acc) acc second) [] first
<mrvn> Multiply each element of the first list with each of the second and put them all into one list.
<edwin> gildor: I went with GODI in the end, and added FindlibVersion: >= 1.2.0 to my _oasis
<edwin> gildor: I'll open those 2 feature requests for you now (ocamlfind path, and findlib version default)
LeNsTR has quit [Quit: LeNsTR]
jamii has quit [Ping timeout: 246 seconds]
smerz has quit [Remote host closed the connection]
Yoric has quit [Quit: Yoric]
infoe has quit [Ping timeout: 240 seconds]
<thelema> hcarty: haven't used batarg - I've still got my own argument handling library that I use
<adrien> "batarg", I thought "batard" at first =/
<adrien> (casing would help of course)
cyanure has joined #ocaml
<thelema> only 2 characters off
<adrien> depends on the language
<adrien> now, if the module is actually a mix of several other ones, it'd probably be appropriate
* adrien wonders when he'll be done with his current schoolwork ='(
<thelema> :)
<NaCl> adrien: work? WORK?
<adrien> I spent the day working and expect to spendsomething like 3 more days working and typing non-stop ='(
<adrien> that's still for work, but at least I won't be typing a report: anyone aware of support libraries to draw openstreetmap maps?
ygrek has joined #ocaml
<adrien> can maybe do it with cairo, I only need the streets
<hcarty> adrien: If you're working from OCaml, Cairo or PLplot are probably your best bets. Cairo may be the simplest, depending on how the data are formatted.
<adrien> would plplot work for a _map_ ?
<adrien> I mean, I want to reproduce the arrangement of streets
<edwin> gildor: opened the feature requests for you
<hcarty> adrien: It has some basic map support. But at the end of the day, it's lines in a coordinate system - Cairo and PLplot support that.
<hcarty> adrien: PLplot could be overkill if all you want to do is show lines
<adrien> right, both should work, but as you say, plplot might be too much
<hcarty> adrien: But it does remove the need for you to manage coordinates yourself.
<adrien> I think I'll have a fixed scale so coordinates will be easy
<adrien> oh
Snark has quit [Quit: Ex-Chat]
<adrien> I could do svg maybe
<hcarty> (Cairo and PLplot both support SVG output :-D)
<adrien> yeah, I know, but writing it directly might be simpler: one line of text per line on the output
<hcarty> That's true
<hcarty> The best approach depends on what the goal is - quick + dirty view of data or piece of a larger project
<adrien> quick and dirty will be enough for tonight, it's currently not very early
<orbitz> Hello
<orbitz> I have a module layout question. I want to namespace all my code so you can od import Orbitz and have ccess to Orbitz.Foo
<orbitz> but Foo is large so I don't want to define it in orbitz.ml
<orbitz> is the standard routien to maek orbitz_foo.ml, and then make orbitz.ml import that or osmething?
<hcarty> orbitz: You can put "module Foo = Foo" in orbitz.ml, and the content of Foo in foo.ml
<orbitz> what about orbitz.mli?
<hcarty> orbitz: Or "module Foo = Orbitz_foo" + orbitz_foo.ml
<orbitz> right now I'm copying the orbitz_foo.mli to orbitz.mli, but that is a pita
<hcarty> orbitz: That would require duplication, or "include Orbitz_foo"
<hcarty> I think more recent OCaml versions support include in signatures...
<orbitz> is the mli like module Foo = sig include Orbitz_foo end?
<orbitz> or just include
<hcarty> module Foo = sig include module type of Orbitz_foo end
<hcarty> IIRC
<orbitz> thanks hcarty
<hcarty> orbitz: You're welcome. A few warnings: 1) This is OCaml 3.12.0 or later only; 2) camlp4 doesn't play well with "module type of"
<hcarty> (2) is hopefully not an issue for a .mli
<orbitz> Hrm
<orbitz> ok
<orbitz> I should be good for 3.12.0
<eaburns> orbitz: you should checkout mlpacks too. I don't know much about it, but it will build the Orbitz module for you by packing together a bunch of modules as submodules
<orbitz> I could generate teh .mli on the fly via ocamlc I think
<orbitz> but that seems nasty
caligula_ has joined #ocaml
<adrien> openstreetmap: from less than 1GB of compressed data in 2007 to almost 15GB nowadays, I think my ram won't be useless tonight =)
<thelema> adrien: how much ram do you have?
<adrien> 8GB
<thelema> I hope you don't swap too much
<adrien> first step will be to remove most of the data, but I'll probably still have quite a lot, it should fit in ram hopefully
<adrien> I'm going with a dump from early 2008 anyway right now: "only" 3.6GB compressed (I won't get the full most recent dumps before several hours)
<adrien> ah... "If you have sufficient space to unpack the full planet file (~180 GiB in September 2010)", gonna be fun :P
<adrien> hmmm, I'll have to make some room on the disks too I think
<thelema> :)
<adrien> ah, no, *MUCH* better: they have daily "extracts" by countries, and sometimes by region, and I found one file that is "only" 180MB compressed
<thelema> yes, much better
* thelema is decompressing a 1.9GB tar.bz2 file now
<adrien> the file was actually 122MB compressed: and after bunzip2: "-rw-r----- 1 adrien users 1.8G Jan 21 03:44 ile-de-france.osm"
<thelema> that should be an easy size for your ram
<mrvn> Would it make sense to add bubble_fold to batteries? http://paste.debian.net/105324/
<orbitz> hcarty: does this look obviously wrong in any way? http://ideone.com/XQ61t
itewsh has joined #ocaml
<itewsh> hello !
<orbitz> Hi
<hcarty> orbitz: You probably need to include the files providing Ort_* in the ort.ml compilation line
<hcarty> orbitz: Or use something like ocamlbuild to do the magic bits for you
* orbitz grumbles
<orbitz> hcarty: by include the files do you mean module Seq = struct include Ort_seq end?
<hcarty> orbitz: No, in the ocamlc call
<orbitz> oh
<hcarty> ocamlc ... ort_*.ml ort.ml
<hcarty> mrvn: What is a bubble fold?
<thelema> mrvn: my question too - why would I want to use this function?
<thelema> I can tell that it can hold one element of the list inside a bubble and switch it into place down the line.
jm has joined #ocaml
<thelema> and fold it in there instead of its original position... but when would this be useful?
<mrvn> yes. It is like fold but you get to act on 2 elements of the list processing one and keeping one in the bubble.
strlen has joined #ocaml
<mrvn> You would use this in bubble_sort for example. Or if you want to create a space seperated string of all elements of the list
<mrvn> (only works with the former)
<thelema> how is this useful for string.concat?
<thelema> I can see bubble_sort coming out of this, but I wouldn't want to implmemnt bubble sort this way.
<mrvn> # bubble_fold (fun acc x y -> (acc^x^", ", y)) (fun acc x -> acc^x) "" ["one"; "two"; "three"];;
<mrvn> - : string = "one, two, three"
<thelema> String.concat ", " ["one"; "two"; "three"]
<mrvn> its the more general form of concat.
<thelema> except it can't allocate the final string, but has to work incrementally, O(n^2)
<mrvn> general as in it can work with things other than string
<hcarty> mrvn: It looks interesting - but I can't see how it would be applied elsewhere. Do you have a non-String.concat example?
<mrvn> Sort of the same: pretty printing.
<hcarty> mrvn: I could see a double-bubble case perhaps, if you want to treat the first and last elements in a special way.
<mrvn> I often want to output a list of things with a seperator inbetween them. But no seperator after the last element.
<thelema> what would keep an exception handler from catching an exception defined in another file?
<mrvn> it is already caught in that other file?
<hcarty> mrvn: The *.print functions, or *.t_printer functions in Batteries provide something like that.
<thelema> no, it's hitting the topleve
<thelema> it's stopping the program
<mrvn> thelema: maybe it is raised somewhere else outside your try?
<thelema> I was raising Invalid_argument "some string", and I just changed it to raise new_exception
<thelema> and changed the catch to match, Foo.new_exception
<thelema> no, only raised in one place, definitely within the try
<mrvn> odd
<thelema> quite.
<hcarty> thelema: Does Foo.new_exception have a string or other argument which could be mismatched?
<thelema> nope, no arguments.
<thelema> "exception No_new_state"
<thelema> "with Ns_parse.No_new_state -> "...
<hcarty> thelema: That is very peculiar
<thelema> wow, renaming the exception to "Parse_failure" fixed the problem.
<hcarty> thelema: Is it possible some compilation got out of sync?
<thelema> I thought so at first, but my make clean didn't fix it
<thelema> and this last compile, I didn't make clean
<thelema> so it went from failing to working without a make clean
eaburns has left #ocaml []
<thelema> anyway, could be that, somehow.
<hcarty> If you change it back, does it break again?
<thelema> yes
<hcarty> That's really weird :-)
<thelema> quite.
<thelema> as if there's a hashcode collision between 'no_new_state' and some already defined exception that's not caught at linking
<thelema> not that I define many exceptions
<thelema> grrr... ocaml needs to give an error for multiply defined exceptions.
<hcarty> thelema: Was it defined twice?
<thelema> yes, I had already defined the same exception later in the file, so it was trying to catch the second exception, not the identically named first one.
<hcarty> I'm surprised it doesn't warn/error on that, but doesn't allow modules to be replaced/shadowed.
<hcarty> s/doesn't/does/ for the second doesn't
<mrvn> thelema: did they have different arguments or why were they different?
<thelema> not different at all, but I recall now that exceptions get assigned sequential ids for use under the hood, like variant types, not like polymorphic variants
eye-scuzzy has joined #ocaml
<mrvn> makes sense. Otherwise this would segfault: exception Foo of int let bar () = raise (Foo 1) exception Foo of int list let () = List.iter (fun _ -> ()) (try bar () with Foo l -> l);;
<thelema> well, I'd rather ocaml give an error (or at least a warning) on the second [exception Foo] in a file
<mrvn> I wish exception were part of a functions signature
<thelema> me, not so much
<mrvn> thelema: that way it would have told you that you are matching against an exception that is never thrown.
<thelema> but imagine the pain in the new signatures
<mrvn> you mean in mli files?
<thelema> everywhere we'd have to read them
<mrvn> Most functions don't throw one
<thelema> and imagine the problems that'd cause with higher-order functions - one wouldn't be able to Array.map (Hashtbl.find ht) keys
<thelema> you'd need an Array.map_exn for each exn?
<mrvn> thelema: you would, it would just throw the exceptions Hashtbl.find throws.
<thelema> anyway, my problem would be quite well solved by the much simple 'no duplicate exceptions' rule
<mrvn> Array.map : ('a -> 'b [exn]) -> 'a array -> 'b array [exn] = <fun>
<thelema> and if you had a map function that caught Failure exceptions (and only those)...
<mrvn> Array.map : you need subset types there [exn | !Failure ] or something.
<mrvn> # let foo = function `A -> `A | `B -> raise (Failure "foo") | x -> x;;
<mrvn> val foo : ([> `A | `B ] as 'a) -> 'a = <fun>
<thelema> bleh
<mrvn> That type isn't quite right there. the function never returns a `B.
<mrvn> Should be ['a | !`B] there too.
<thelema> especially if you get really specific, and only catch Failure str where str contains the letter 'g'
<mrvn> thelema: yeah, it could get quite complex.
<mrvn> I guess then it would just say it still throws Failure.
<mrvn> hehe. I just found an old mergesort in my homedir: http://paste.debian.net/105333/
<mrvn> Uses a fixed amount of stack and O(n) heap.
<mrvn> Ocamls merge sort uses O(log n) stack *pffft*
<flux> ..which one performs better?
<flux> ;)
<thelema> I imagine there's a tradeoff point... somewhere... when the fixed stack is faster than O(log n) stack
<mrvn> mine is tail recursive and as we saw yesterday that is faster
<thelema> that said, O(log n) ~ O(1)
Edward__ has joined #ocaml
<mrvn> thelema: in 32bit a list has less than 1 billion elements. so log n <= 30 => O(1). true. :)
Edward_ has quit [Ping timeout: 240 seconds]
<thelema> and in 64-bit, there's just a factor of 2
<mrvn> <= 61 for 64bit.
<mrvn> a little bit more than factor 2
<thelema> yes, yes.
lamawithonel_ has joined #ocaml
lamawithonel has quit [Ping timeout: 255 seconds]
edwin has quit [Remote host closed the connection]
fraggle_laptop has quit [Ping timeout: 260 seconds]
<dark> it seems.. wrong o.o
<dark> it lacks rec, and more, it does not work
<dark> the sum
<dark> it gives Exception: Stream.Error "" for "1 + 1"
<dark> i think i figured it out though
<dark> also the ocaml manual has an example nearly identical to what i'm trying to do, bah u.u
<thelema> what you're trying to do is apparently the example problem of choice
jm has quit [Ping timeout: 240 seconds]
<dark> but i have only + at my parser
<dark> I haven't introduced *
<dark> but i'm seeing this parser, http://caml.inria.fr/pub/docs/manual-ocaml-307/manual003.html which works
<dark> oooh
<dark> that grammar is left recursive
<dark> o.o
<dark> it is parsing parse_expr and the first token it parses in a production, n, is also a parse_expr
ygrek has quit [Ping timeout: 240 seconds]
jm has joined #ocaml
cyanure has quit [Remote host closed the connection]
numeromancer has left #ocaml []
itewsh has quit [Quit: Quitte]
EliasAmaral has joined #ocaml
dark has quit [Ping timeout: 240 seconds]
<EliasAmaral> ocamlfind requires a preprocessor at some META file in order to use camlp4. can I do it without actually creating this file? (I could using OMakefile..),
<thelema> "-syntax camlp4o"?
<thelema> if you have ocamlfind installed, it should already have meta files for camlp4
<EliasAmaral> $ ocamlfind ocamlc -syntax camlp4o -package batteries calc.ml -o calc
<EliasAmaral> ocamlfind: When using -syntax, the META variable 'preprocessor' must be set
<EliasAmaral> it always worked....
<EliasAmaral> anyway if someone here can run it, http://codepad.org/ThXZZgMr
ccasin has quit [Quit: Leaving]
<EliasAmaral> the parser is from ocaml manual, haven't managed to make one working .-.
Yoric has joined #ocaml
<EliasAmaral> but i think i will use ocamllex / ocamlyacc anyway
<EliasAmaral> actually http://codepad.org/JFDfrEBS
<thelema> hmm, I'm surprised batteries isn't setting that for you, the normal META file for batteries has a bunch of camlp4 extensions
<thelema> they're not enabled unless you -syntax camlp4o/r
accel has joined #ocaml
<EliasAmaral> omake could compile it..
boscop_ has quit [Ping timeout: 240 seconds]
<EliasAmaral> oh, what i needed was batteries.syntax
<EliasAmaral> or any other .syntax actually
LeNsTR has joined #ocaml
<EliasAmaral> my program won't work with -thread, and batteries won't compile without -thread o.o
<EliasAmaral> with -thread it justs do nothing