adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 4.00.1 http://bit.ly/UHeZyT | http://www.ocaml-lang.org | Public logs at http://tunes.org/~nef/logs/ocaml/
mjonsson has quit [Read error: Connection reset by peer]
lolcathost has joined #ocaml
mjonsson has joined #ocaml
tac has joined #ocaml
lolcathost has quit [Remote host closed the connection]
astertronistic has joined #ocaml
ulfdoz has quit [Ping timeout: 246 seconds]
ulfdoz has joined #ocaml
walter|r has quit [Quit: This computer has gone to sleep]
walter|r has joined #ocaml
wormphle1m has quit [Read error: Connection reset by peer]
wormphlegm has joined #ocaml
pkrnj has joined #ocaml
pkrnj has quit [Ping timeout: 240 seconds]
pkrnj has joined #ocaml
trotro has quit [Quit: Leaving]
pkrnj has quit [Quit: Computer has gone to sleep.]
pkrnj has joined #ocaml
madroach has quit [Ping timeout: 244 seconds]
madroach has joined #ocaml
Neros has quit [Remote host closed the connection]
andreypopp has quit [Quit: sleep]
walter|r has quit [Quit: This computer has gone to sleep]
andreypopp has joined #ocaml
andreypopp has quit [Client Quit]
walter|r has joined #ocaml
Playground has joined #ocaml
mye has quit [Quit: mye]
tac has quit [Quit: Page closed]
<gustav__> I can't code C without thinking of variables as immutable now. They aren't, but... it's helpful.
<gustav__> OCaml is like a better LISP... good thing this isn't a LISP channel maybe.
<gustav__> Too many parantheses in that.
Yoric has quit [Ping timeout: 246 seconds]
Playground has quit [Ping timeout: 245 seconds]
BiDOrD_ has joined #ocaml
BiDOrD has quit [Ping timeout: 260 seconds]
Skolem has quit [Quit: Skolem]
justdit has quit [Ping timeout: 264 seconds]
justdit has joined #ocaml
mye has joined #ocaml
larhat has joined #ocaml
pkrnj has quit [Quit: Textual IRC Client: www.textualapp.com]
tautologico has quit [Quit: tautologico]
justdit has quit [Ping timeout: 240 seconds]
mjonsson has quit [Read error: Operation timed out]
justdit has joined #ocaml
lolcathost has joined #ocaml
deu5 has quit [Quit: Leaving]
larhat has quit [Quit: Leaving.]
testcocoon has quit [Quit: Coyote finally caught me]
testcocoon has joined #ocaml
answer_42 has joined #ocaml
Yoric has joined #ocaml
Snark has joined #ocaml
lolcathost has quit [Ping timeout: 256 seconds]
pango is now known as pangoafk
oiz has joined #ocaml
<flux> gustav__, just declare all variables as 'const' :)
lolcathost has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
lolcathost has quit [Ping timeout: 260 seconds]
gustav__ has quit [Read error: Connection reset by peer]
gustav__ has joined #ocaml
Cyanure has joined #ocaml
djcoin has joined #ocaml
gustav__ has quit [Read error: Connection reset by peer]
hkBst has joined #ocaml
hkBst has quit [Changing host]
hkBst has joined #ocaml
Cyanure has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
ontologiae has joined #ocaml
<oiz> hello, i have a type T = I of int | S of string, a map m of type (string,int) Hashtbl, and i want to write a function that takes as argument x of type T, matches x, and treats the case here x = I n and x = S s where n = Hashtbl.find m s when Hashtbl.mem m s in the same way; how can i do that without duplicating the code?
ontologiae has quit [Ping timeout: 255 seconds]
jbrown__ has joined #ocaml
|jbrown| has quit [Ping timeout: 260 seconds]
Cyanure has joined #ocaml
cago has joined #ocaml
<flux> hmm, I'm not sure I understand, as you cannot search both strings and integers from the same map. perhaps you can show actual code doing it, with code duplication, and we can suggest how to simplify it?
larhat has joined #ocaml
mfp has quit [Ping timeout: 246 seconds]
<_habnabit> oiz, what flux said
<oiz> flux: _habnabit: http://ocaml.nopaste.dk/p15245
<_habnabit> oiz, write a function; call it with n
<flux> oiz, you mean duplication in guard patterns and the expression it chooses?
<oiz> _habnabit: ye that's what i'm doing now, but isn't there some syntax trick with the match? for instance with the keyword "as" or something like that?
<flux> although your example isn't the best perhaps, because .mem returns a boolean which you know is true..
<oiz> flux: why is it true?
<flux> oiz, if you really, really want to get rid of the duplication, you can use lazy evaluation
<flux> oiz, well, you can only enter the clause when Hashtbl.mem h s is true
<flux> therefore your code is equivalent to let n = true in ..
<flux> it's as if you had written: if Hashtbl.mem h s then let n = Hashtbl.mem h s in .. (* n must be true here *)
<oiz> flux: i'm sorry that's a typo
<oiz> n is an integer (Hashtbl.find h s)
astertronistic has quit [Ping timeout: 245 seconds]
<flux> ah, and it's not the 'duplication' of Hashtbl.mem/Hashtbl.find you want to get rid of, but the part you didn't write :-)
<flux> oiz, just define a local function
<flux> as _habnabit suggested
<_habnabit> oiz, there is, but you can't use it here because you need to call a function with the value
<oiz> _habnabit: "there is" what?
<flux> let do_it_with_n n = (* do something with n *) in match .. -> do_it_with_n n ... | -> do_it_with_n n -> ..
<_habnabit> oiz, there's a way to have alternate matches like you were thinking
<_habnabit> oiz, but the types need to be the same _before_ calling functions
<oiz> they're both integers
<_habnabit> oiz, it's not an integer before you call Hashtbl.find
<oiz> so i cannot put Hashtbl.find somehow in the match clause?
<_habnabit> oiz, if you had, say, type t of A of (int, string) | B of (string, int) and you did `function A (i, _) | B (_, i) -> succ i`
<flux> oiz, in other words: http://ocaml.nopaste.dk/p15246
<_habnabit> oiz, you see the difference?
<flux> (but it's missing code for do_something_with_n)
<flux> oiz, I can't think of how to write that otherwise in that particular case
<oiz> ok i get it
<oiz> oh what about
mfp has joined #ocaml
<oiz> match (x, k) with (I n,_) | (S s, n) when Hashtbl.mem h s && n = Hashtbl.find h s -> (* do something *)
<oiz> but k isn't defined, it should be havoced i guess :)
<flux> oiz, you could use something like this in with batteries, but it's a bit convoluted: let get_s = function S s -> s | _ -> assert false let f h x = let v = lazy (Hashtbl.find_option h (get_s t x) in match x, v with | I n -> do_something_with_n n | S s, lazy (Some n) -> do_something_with_n n | ..
<_habnabit> oiz, i suppose so, but that's rather complicated
<_habnabit> oiz, what's the point, if you have to write code like that?
<oiz> ye i agree i prefer the local function method
<oiz> but thanks for explaining
Yoric has quit [Quit: Instantbird 1.3a1pre -- http://www.instantbird.com]
Yoric has joined #ocaml
<flux> nice, this compiles: match assert false, assert false with | `Int n, _ | `Str _, lazy (Some n) -> n
<flux> but still pretty convoluted..
<oiz> match assert false, that's weird :o
<flux> well, it's just for checking the syntax
<flux> assert false returns a polymorphic value that is compatible with everything
<flux> of course, it never really does that, because of the exception
<oiz> right
Kakadu has joined #ocaml
chambart has joined #ocaml
oiz has quit [Ping timeout: 245 seconds]
Neros has joined #ocaml
ontologiae has joined #ocaml
thomasga has joined #ocaml
sepp2k has quit [Remote host closed the connection]
eikke has joined #ocaml
_andre has joined #ocaml
Yoric has quit [Ping timeout: 246 seconds]
larhat has quit [Read error: Connection reset by peer]
larhat has joined #ocaml
<pippijn> "A channel is a high-level object for performing IOs. It allow to read/write things from/to the outside worlds in an efficient way, by minimising the number of system calls."
<flux> what channel?
<pippijn> Lwt_io.channel
lolcathost has joined #ocaml
<pippijn> this seems to be pretty slow
<pippijn> only reading the lines takes 0.6 seconds
<pippijn> reading + making a list takes 1.9 seconds
<pippijn> reading+making+reversing is 2.1s
<pippijn> perl does the same thing in 1.4 seconds
<pippijn> except it's not the same thing
<pippijn> but the same result
<pippijn> open my $fh, '<', 'random.dat' or die $!; my @lines = <$fh>;
<flux> I'm not sure for using Lwt_io would be any faster than plain input_channel
<flux> I mean, there must be some overhead in the cps stuff..
<pippijn> reading the entire file in perl into one big variable takes 0.38 seconds
<pippijn> that's almost twice as fast as reading the entire file in ocaml without putting it into variables
<flux> reading it how?
<pippijn> input_line
<flux> have you straced it, do they do the same system calls?
<pippijn> ignore (input_line channel)
<The_third_man> pippijn: that's normal, with input_line, you do on syscall per line, while reading the whole file reduces the amount of syscalls
<pippijn> The_third_man: so how can I read the whole file at once in ocaml?
<pippijn> also, that should *not* be normal
<flux> the_third_man, really?
<pippijn> also, that is definitely not true
<flux> I seriously doubt that
<pippijn> because input_line cannot know where the line ends before it read at least more than the line
<flux> but I would imagine perl might use bigger buffers for systeam reads
<pippijn> perl uses 8KB buffers
<flux> pippijn, well, it could also read one character at a time, but that'd be really slow :)
<flux> it might involve more copying in ocaml than in perl
<pippijn> ocaml starts with a 4KB buffer
<pippijn> and then it "randomly" varies the size
<pippijn> 4035, 3726, 3756, ...
<pippijn> but never >4KB
<pippijn> 1 memory page
<flux> interesting
<flux> you could patch it to use 8k buffers and see how it performs then
<flux> although the difference is quite big
<pippijn> you think that accounts for the double time it takes in ocaml vs. perl?
<flux> not really, but it might account for some
<flux> the rest could come from (possibly) additional copying
avsm has joined #ocaml
<pippijn> I'm looking at the C code, too
<pippijn> and my conclusion is
<pippijn> if I need fast file I/O, I need to do it myself
<pippijn> I don't see where they set the buffer size, but i/o channels are monsters
<avsm> the buffer size was bumped in 4.00.0, so make sure you're on the latest
<pippijn> oh, what is it now?
<flux> pippijn, they might choose it in the functions that returns in_channel..
<pippijn> lwt implements their own
<pippijn> #define IO_BUFFER_SIZE 4096
<pippijn> there it is
<pippijn> lwt's channels are pure ocaml
<pippijn> I'll time their execution
Kakadu has quit [Read error: Connection reset by peer]
Kakadu has joined #ocaml
<pippijn> I need to rewrite the loop into recursion
<pippijn> so I'll time that with the ocaml channel, first
<pippijn> I'm confused
<pippijn> it segfaults
makrz has joined #ocaml
<pippijn> ok, stack overflow
<makrz> hi
<pippijn> catching exceptions make it non-tail-recursive
<makrz> how would you write something like List.for_all for Hashtbl, without going through the whole Hashtbl when not necessary?
<flux> makrz, sadly, with exceptions
<makrz> :)
<pippijn> 2.1 seconds, still
<makrz> that's what i did, feeled a bit dirty
<flux> makrz, hide it behind a dozen abstraction layers and never lay your eye on it again
<flux> then go to shower
<flux> problem solved.
<makrz> lol
<flux> something like fold_until would solve that for Hashtbl
<flux> ..or an actual iterator interface
Neros has quit [Ping timeout: 260 seconds]
chambart has quit [Ping timeout: 265 seconds]
mye_ has joined #ocaml
<pippijn> flux: using lwt, it's extremely slow
<flux> figures
<pippijn> I don't know if I am maybe doing something wrong
<pippijn> 42.349 total
<flux> have you tried how long it takes to Unix.read & discard the file in as big chunks as possible?
mye has quit [Ping timeout: 246 seconds]
mye_ is now known as mye
<pippijn> 0.123 seconds for 4kb buffer
<pippijn> the same with 8
<pippijn> slower with 16k
<pippijn> much slower with 2k
<pippijn> 4k seems to be best
<pippijn> one memory page
lolcathost has quit [Quit: leaving]
lolcathost has joined #ocaml
mye has quit [Quit: mye]
<pippijn> does/did anybody here use omake?
<adrien> I did a bit and I'm interested in giving it another try
<pippijn> after going all power-user on oasis and ocamlbuild..
<pippijn> I found that it can't do what I need
<pippijn> and it doesn't scale
<pippijn> a no-op build on my project takes 4 seconds
<pippijn> for me, that is unacceptable
<pippijn> it takes 0.12 seconds for omake
<pippijn> but now I have a problem
<adrien> did you try with a few "traverse: false"?
<pippijn> adrien: it's not about traverse
<adrien> using git too?
<pippijn> it's about computing hashes
<pippijn> the actual up-to-date checks take too long
<adrien> how many files?
<pippijn> 800
<pippijn> oh wait
<pippijn> maybe 400 :)
<adrien> well, you know it's a no-op but how does ocamlbuild would know it is?
<pippijn> adrien: it doesn't
<pippijn> but neither does omake
<pippijn> and it's fast
<adrien> so, omake does things differently and the difference is no surprise
lolcathost has quit [Remote host closed the connection]
<adrien> if you don't want the build system to check the contents of file, yes, avoid ocamlbuild at all cost :P
<pippijn> ok, around 300 files
<pippijn> adrien: omake checks the contents
<pippijn> but only if the timestamp changed
<pippijn> omake keeps a db for that, ocamlbuild doesn't
Playground has joined #ocaml
<adrien> afaiu, ocamlbuild _always_ checks the contents
<pippijn> that is bad, because I have many and several large files
Yoric has joined #ocaml
<flux> i/d-notify + ocamlbuild, that could automatically build whenever the files are changed, without checking if they have in fact!
<pippijn> omake can do that
<pippijn> using FAM ;)
<pippijn> omake is 5 years old, FAM is 9 years old
<pippijn> but if I can get omake to do what I want (and I think I can), I might fork it and continue its development
<adrien> flux: but it won't be portable
<pippijn> it can be optional
<flux> adrien, so, basically, if a feature cannot be supported on ALL platforms, it should be supported on none?-)
<flux> I suppose there are some wrapper libraries for those features - like FAM
<pippijn> except FAM sucks
<pippijn> it doesn't follow links
<flux> what I would like to see would be support for btrfs so that when you get the even, you also get a snapshot you can operate in
<pippijn> so it doesn't work at all for out of tree builds
<flux> "get the event"
ontologiae has quit [Ping timeout: 252 seconds]
Neros has joined #ocaml
Cyanure has quit [Remote host closed the connection]
andreypopp has joined #ocaml
Playground has quit [Quit: leaving]
lolcathost has joined #ocaml
csag8264 has joined #ocaml
rossberg has joined #ocaml
cdidd has quit [Remote host closed the connection]
Neros has quit [Read error: Operation timed out]
Neros has joined #ocaml
<Kakadu> Anybody knows what is bad with my camlp4 code? http://paste.in.ua/7712/#15
<pippijn> I think building a build system on top of omake is better than making a whole new one like ocamlbuild
andreypopp has quit [Quit: sleep]
* Kakadu will brb after dinner and rad everything
<pippijn> Kakadu: you're missing |
<Kakadu> pippijn: aaaaaaaaah, :)
andreypopp has joined #ocaml
chambart has joined #ocaml
<pippijn> but does omake work on native windows?
ppseafield has joined #ocaml
<adrien> flux: as long as you have a good fallback, I don't object ocamlbuild using inotify on linux
<adrien> but inotify doesn't work anywhere else
<adrien> and you'll need something specific to each OS to get the same functionality everywhere or use a library that does that
<flux> sure, you need to have fallback already for debugging purpose..
ontologiae has joined #ocaml
mjonsson has joined #ocaml
justdit has quit [Ping timeout: 255 seconds]
ollehar has joined #ocaml
ollehar has quit [Quit: ollehar]
lolcathost has quit [Ping timeout: 260 seconds]
ollehar has joined #ocaml
lolcathost has joined #ocaml
andreypopp has quit [Quit: sleep]
lolcathost has quit [Ping timeout: 260 seconds]
andreypopp has joined #ocaml
gustav__ has joined #ocaml
<pippijn> adrien: it's no functionality
<pippijn> adrien: it's purely an optimisation
<pippijn> adrien: the observable behaviour is exactly the same
mjonsson has quit [Ping timeout: 248 seconds]
<adrien> then write the new code while breaking the old one and we'll talk again once you've managed to do so :P
<pippijn> I am not the least bit interested in ocamlbuild, anymore
<makrz> when getting a "Fatal error", where can i know where it's coming from?
lolcathost has joined #ocaml
<pippijn> makrz: Printexc.record_backtrace true
<makrz> nice thanks
ollehar has quit [Remote host closed the connection]
cago has quit [Quit: Leaving.]
<Kakadu> It seems that camlp4 parser use fast-back backtracking strategy. Am I right?
<pippijn> I feel so bad.. I'm writing java
<pippijn> I'm writing a map
<pippijn> in java, every map is an explicitly coded loop
<pippijn> it's so.. basic
<djcoin> pippijn: :) I'm far from being a java expert but you should look for external lib, including guava (from Google) I guess: http://code.google.com/p/guava-libraries/wiki/FunctionalExplained
<pippijn> djcoin: I do things like that
<pippijn> djcoin: my colleagues hate it
<djcoin> Robust code =)
csag8264 has quit [Remote host closed the connection]
Kakadu has quit [Quit: Konversation terminated!]
andreypopp has quit [Quit: sleep]
justdit has joined #ocaml
justdit has quit [Read error: Connection reset by peer]
travisbrady has joined #ocaml
justdit has joined #ocaml
justdit has quit [Read error: Connection reset by peer]
justdit has joined #ocaml
justdit has quit [Ping timeout: 240 seconds]
mye has joined #ocaml
travisbrady has quit [Quit: travisbrady]
Kakadu has joined #ocaml
travisbrady has joined #ocaml
deu5 has joined #ocaml
jamii has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
tac has joined #ocaml
hkBst has quit [Quit: Konversation terminated!]
<makrz> if i have a list of Variables, and two maps "min" and "max" from Variables to int, how can i generate all the possible valuations of these variables?
thomasga has quit [Quit: Leaving.]
<makrz> or said differently, how can i rewrite that in a nicer way? http://ocaml.nopaste.dk/p15252
<makrz> there is a "!result" missing at the end
<makrz> pippijn: scala is cool, and you can use it with java
<makrz> i'll be back later
makrz has quit [Quit: Page closed]
<djcoin> pippijn: did you give birth to iter() and new DataIteration.Processor() {}, or does it come from another lib ?
<pippijn> I made that
<djcoin> :)
<pippijn> it works for any number of arguments
<pippijn> it iterates over maps
<pippijn> "Products" is just a description for exceptions thrown and caught in iter
<pippijn> so it can say "While processing Products"
<djcoin> I would have liked to find back this awesome link of a coworker paste the first thing a guy coming from FP background switched to C# : 3000 lines long of FP iodioms (like currying etc.)
<pippijn> I'm not like that
<pippijn> but when I can make things simpler, I do
<pippijn> the implementation of iter is not simple at all ;)
<djcoin> Sorry for my poorly phrased sentence !
<djcoin> :)
<pippijn> it's not compile-time type-safe
<pippijn> it iterates over lists of maps
<pippijn> over a list of maps
<pippijn> and each map is expected to contain the keys "Blattname" and "gid"
<pippijn> if java had dependent types, it could be compile-time type-safe
sepp2k has joined #ocaml
beginner42 has joined #ocaml
<beginner42> how can i install an oasis package
<thelema> beginner42: is there a setup.ml file?
<beginner42> yes
<thelema> ocaml setup.ml -configure && ocaml setup.ml -build && ocaml setup.ml -install
<thelema> iirc
<beginner42> worked thanks
xavierm02 has joined #ocaml
<thelema> n/p
lolcathost has quit [Ping timeout: 246 seconds]
<xavierm02> why can't we set the tail of a list?
<xavierm02> I mean I understand that two lists may share a common end.
<xavierm02> but the programmer is probably aware of that when he tries to modify the list
<_habnabit> xavierm02, what do you mean by 'set' it?
<xavierm02> well
<_habnabit> xavierm02, you can do let l' = match l with h :: t -> h :: t' | _ -> invalid_arg "..."
<xavierm02> yes
<xavierm02> but that copies most of the list
<_habnabit> xavierm02, no it doesn't
<xavierm02> are you sure?
<_habnabit> xavierm02, why would you think it copies?
<xavierm02> let a = [ 2, 3, 4 ] in let b = 1 :: a and c = 0 :: 1;;
<xavierm02> if it doesn't copy
<xavierm02> it might break other lists
<xavierm02> that use the same tail
<xavierm02> c = 0 :: a
<_habnabit> xavierm02, how is that possible? afaik using :: will always create a new list _node_ but it copies neither the head nor the tail
lolcathost has joined #ocaml
<xavierm02> ok
<xavierm02> I'll give you a real example in a few minutes
<_habnabit> # let l = [1; 2; 3] in let a = 4 :: l and b = 5 :: l in List.tl a == List.tl b;;
<_habnabit> - : bool = true
<_habnabit> looks like it doesn't copy to me
<_habnabit> also,
<_habnabit> # let l = [1; 2; 3] in let a = 4 :: l and b = 5 :: l in List.tl (List.tl a) == List.tl (List.tl b);;
<_habnabit> - : bool = true
<flux> xavierm02, you can never modify a list, that's why it's safe to not copy, but just reference.. but, you may be able to mutate stuff pointer by lists, so that's when you need to manually do a deep copy
thomasga has joined #ocaml
Yoric has quit [Ping timeout: 252 seconds]
lolcathost has quit [Remote host closed the connection]
larhat has quit [Quit: Leaving.]
cdidd has joined #ocaml
lolcathost has joined #ocaml
makrz has joined #ocaml
deu5 has quit [Remote host closed the connection]
<beginner42> adrien: do i need to clone the webkit repo or is there a debian package, so i can use your binding?
<makrz> i'm back; anyone has a better idea to write this? http://ocaml.nopaste.dk/p15254
<makrz> also, i wanted to know, would Set's of List "word"? what about Sets of Sets?
<makrz> work*
<makrz> (unrelated questions)
csag8264 has joined #ocaml
srcerer_ is now known as srcerer
thomasga has quit [Quit: Leaving.]
csag8264 has quit [Remote host closed the connection]
<xavierm02> _habnabit: http://pastebin.com/DghnJFGm
<xavierm02> _habnabit: I know if I don't keep it in a variable, the list will be dropped by the garbage collector. But I want to reuse it for my "sublist"
<flux> makrz, maybe you could use Map instead of Hashtbl for valuation, to avoid copying
<xavierm02> _habnabit: And I can't. I have to copy all those items when I could just "skip" the one I don't one by setting the tail of the previous element to the next
<makrz> flux: yes ok
<_habnabit> xavierm02, so... why can't you do the code I suggested on line 26?
<flux> xavierm02, I don't think you can really write that more efficiently than: List.filter (fun x -> x >= 0) l
<_habnabit> xavierm02, let prev' = match prev with h :: t when head < 0 -> h :: t' | _ -> prev in loop prev' tail
<xavierm02> _habnabit: It will copy the list from what I understand
djcoin has quit [Quit: WeeChat 0.3.9]
<_habnabit> xavierm02, as I _just_ said, it won't
Xizor has joined #ocaml
<flux> xavierm02, you cannot express that prev.tail <- tail part in your code.. or is that your question, how to do it?
<flux> xavierm02, if you really really want to do it, it's actually possible. iirc ExtLib does it with List.map, possibly batteries as well
<flux> but, it should be well verified that it does the right thing..
<_habnabit> flux, it's possible, but in this case not necessary
sepp2k1 has joined #ocaml
sepp2k has quit [Ping timeout: 240 seconds]
<xavierm02> type 'a mut_list = {
<xavierm02> hd: 'a;
<xavierm02> mutable tl: 'a list
avsm has quit [Ping timeout: 260 seconds]
<xavierm02> }
<xavierm02> that's how they implement the list
<xavierm02> so I get why it works
<xavierm02> but don't you loose more perf by switching to a non-native list than you win by not copying the list?
<xavierm02> anyway
<xavierm02> ty :)
<_habnabit> xavierm02, for the Nth time, there is no copying
<xavierm02> there must be some copying
<xavierm02> otherwise
<xavierm02> if I keep the list in a variable
<xavierm02> it's get modified
<xavierm02> it'll*
<xavierm02> and
<xavierm02> I tried to understand your code
<_habnabit> xavierm02, as I said, it creates a new list node, because the previous one is immutable. the tail is not copied.
<xavierm02> ok
<xavierm02> the tail is not copied
<xavierm02> but if you have
<xavierm02> [ a, b, c, d, e ]
<xavierm02> and you want to remove c
pkrnj has joined #ocaml
<xavierm02> you copy [ a, b ] and then append [ d, e ] to it
<xavierm02> so if you want to remove the very last item
<_habnabit> incorrect
<xavierm02> you're screwed
<_habnabit> oh, wait, yes
<_habnabit> but it's not copying because it's not the same thing
<xavierm02> yeah
<xavierm02> it doesnt really copy
notdan has quit [Remote host closed the connection]
<xavierm02> it just creates a new "beginning of list" that is similar
<adrien> beginner42: there is no debian package for lablwebkit
<xavierm02> but if the "beginning of the list" is the whole list minux 1 item
<xavierm02> it sucks :/
<adrien> you should use the tarball
<beginner42> adrien: i downloaded your tarball
tane has joined #ocaml
<beginner42> and cloned the git repo of the webkit project
csag8264 has joined #ocaml
gustav__ has quit [Remote host closed the connection]
pangoafk is now known as pango
gustav__ has joined #ocaml
csag8264 has quit [Remote host closed the connection]
notdan has joined #ocaml
<adrien> beginner42: you mean the 3GB webkit repo?
<beginner42> adrien: yes that one :)
<adrien> that was not necessary :p
<adrien> you probably should use tarballs
<adrien> but the git repo can be handy for debugging
<beginner42> now that i have them i wont delete it, but what tarballs do you refer to?
<pippijn> I have a question about omake
csag8264 has joined #ocaml
<pippijn> this is my omakefile: http://paste.xinu.at/onFM/
<pippijn> and I would like to not write explicit relative paths (../structure)
<pippijn> but rather,register an internal library and refer to it by name here
csag8264 has quit [Remote host closed the connection]
beginner42 has quit [Remote host closed the connection]
mye has quit [Quit: mye]
ontologiae has quit [Ping timeout: 264 seconds]
travisbrady has quit [Quit: travisbrady]
travisbrady has joined #ocaml
mye has joined #ocaml
callen has left #ocaml []
Cyanure has joined #ocaml
travisbrady has quit [Quit: travisbrady]
Yoric has joined #ocaml
mye has quit [Quit: mye]
lolcathost has quit [Quit: leaving]
lolcathost has joined #ocaml
bru` has joined #ocaml
<bru`> Hi! I have trouble wrtiting a lexer:
<bru`> Fatal error: exception Failure("lexing: empty token")
<pippijn> bru`: you need a default rule and an eof rule
<bru`> Even though, in my 2 rules, I'm handling both eof and _
<pippijn> oh
<pippijn> bru`: can you show me the lexer?
<bru`> (the last one simple doing | _ as that { raise blahblah })
<bru`> sure
<bru`> ah!
mye has joined #ocaml
<bru`> nevermind, I forgot I had a third rule…
<bru`> and did not add the "| _ as that blahblah" on it…
<bru`> next time my problem will be a real one!
<pippijn> :)
pkrnj has quit [Quit: Computer has gone to sleep.]
pkrnj has joined #ocaml
makrz has quit [Ping timeout: 245 seconds]
emmanuelux has joined #ocaml
chambart has quit [Ping timeout: 252 seconds]
<bru`> and… how can I easily print all the remaining lexbuf? I'm doing this, but I doubt it's correct:
<bru`> | _
<bru`> { raise (Not_Excepted
<bru`> (String.sub lexbuf.Lexing.lex_buffer (Lexing.lexeme_start lexbuf)
<bru`> lexbuf.Lexing.lex_buffer_len)) }
_andre has quit [Quit: leaving]
<bru`> Well, I fixed the problem in my parsing so I don't need it anymore!
bru` has quit [Ping timeout: 245 seconds]
mye has quit [Quit: mye]
oriba has joined #ocaml
ftrvxmtrx has joined #ocaml
travisbrady has joined #ocaml
ontologiae has joined #ocaml
answer_42 has quit [Quit: WeeChat 0.3.9]
tac_ has joined #ocaml
tac has quit [Ping timeout: 245 seconds]
avsm has joined #ocaml
pkrnj has quit [Quit: Computer has gone to sleep.]
deu5 has joined #ocaml
delamarche has joined #ocaml
delamarche is now known as debo
Xizor has quit [Quit: So yes it's mIRC under wine under debian double peche capital. ;) I'll soon see in kfreeBSD.]
oriba_ has joined #ocaml
pkrnj has joined #ocaml
oriba has quit [Ping timeout: 240 seconds]
avsm has quit [Quit: Leaving.]
notdan has quit [Remote host closed the connection]
lolcathost has quit [Ping timeout: 252 seconds]
Snark has quit [Quit: Quitte]
Skolem has joined #ocaml
lolcathost has joined #ocaml
eikke has quit [Ping timeout: 252 seconds]
lolcathost has quit [Ping timeout: 268 seconds]
lolcathost has joined #ocaml
oriba_ has quit [Quit: oriba_]
Yoric has quit [Ping timeout: 245 seconds]
lolcathost has quit [Quit: leaving]
mye has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
ppseafield has quit [Quit: Leaving.]
Cyanure has quit [Remote host closed the connection]
theplanet^2 has quit [Ping timeout: 276 seconds]
chambart has joined #ocaml
tane has quit [Quit: Verlassend]
elixey has joined #ocaml
lolcathost has joined #ocaml
mye has quit [Quit: mye]
thomasga has joined #ocaml
thomasga has quit [Client Quit]
Skolem has quit [Quit: Skolem]
mye has joined #ocaml
avsm has joined #ocaml
lolcathost has quit [Quit: leaving]
xavierm02 has quit [Quit: Leaving]
larhat has joined #ocaml
debo has quit [Quit: debo]
chambart has quit [Ping timeout: 246 seconds]
tautologico has joined #ocaml
Anarchos has joined #ocaml
chambart has joined #ocaml
gustav__ has quit [Remote host closed the connection]
lolcathost has joined #ocaml
avsm has quit [Quit: Leaving.]
avsm has joined #ocaml
mye has quit [Quit: mye]
avsm_ has joined #ocaml
sepp2k1 has quit [*.net *.split]
shajen has quit [*.net *.split]
bobry has quit [*.net *.split]
yezariaely has quit [*.net *.split]
avsm has quit [Quit: Leaving.]
avsm_ is now known as avsm
chambart has quit [Ping timeout: 246 seconds]
Yoric has joined #ocaml
ontologiae has quit [Ping timeout: 246 seconds]
sepp2k1 has joined #ocaml
shajen has joined #ocaml
bobry has joined #ocaml
yezariaely has joined #ocaml
avsm has left #ocaml []
jamii has quit [Ping timeout: 260 seconds]
Yoric has quit [Ping timeout: 252 seconds]
mjonsson has joined #ocaml
pkrnj has quit [Quit: Computer has gone to sleep.]
travisbrady has quit [Quit: travisbrady]
tac_ has quit [Quit: Page closed]
lolcathost has quit [Remote host closed the connection]
iZsh has quit [Quit: Coyote finally caught me]
lolcathost has joined #ocaml
lolcathost has quit [Quit: leaving]
andreypopp has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
lolcathost has joined #ocaml