dylan changed the topic of #ocaml to: OCaml 3.09.1 available! Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
mikeX has quit [Remote closed the connection]
mikeX has joined #ocaml
mikeX has quit [Client Quit]
<holo> by the way, the code i'm going to paste is from camllight
<holo> is there a problem?
<zmdkrbou> it could be yes :)
<holo> lol
<holo> i'm sure there are alot of better ways to do what i'm trying to do so bash me at will
<holo> hmm the code isn't well idented
<holo> it looks awfull in pastebin
<holo> it not on purpose (the ugliness)
<zmdkrbou> iirk :p
<holo> i think the error is in some ";;"
<zmdkrbou> you should put your nested matchings between parentheses
<zmdkrbou> or use auxiliairy functions
<holo> zmdkrbou, hmm! nice tips!
<holo> i'll try the first tip and then follow your second one as a policy
shawn has quit ["This computer has gone to sleep"]
joshcryer has joined #ocaml
Revision17 has joined #ocaml
mrsolo__ has quit [Read error: 113 (No route to host)]
mrsolo__ has joined #ocaml
ulfdoz has quit [Read error: 60 (Operation timed out)]
<holo> what is the camllight command line option to call a .ml file?
<holo> geez
<holo> ocaml alex.ml
<holo> what is wrong with this?
Submarine has quit ["Leaving"]
<holo> geez, this doens't even come with a manpage
<holo> camllight i mean
<dylan> use ocaml, then?
<holo> dylan, cat alex.ml | camllight |grep Toplevel
<holo> it was to see some errors
holo has quit ["This computer has gone to sleep"]
cricket has joined #ocaml
<cricket> anybody alive?
* lakcaj moves slightly
<lakcaj> I'm not someone to ask questions to though, before you do :)
<cricket> i c
Schmurtz has quit [Read error: 104 (Connection reset by peer)]
Smerdyakov has quit ["Leaving"]
cricket has quit ["BitchX-1.1-final -- just do it."]
ulfdoz has joined #ocaml
ulfdoz has quit [Client Quit]
ulfdoz has joined #ocaml
bohanlon has quit [Remote closed the connection]
Oejet has quit [Read error: 104 (Connection reset by peer)]
bohanlon has joined #ocaml
mrsolo__ has quit [Read error: 104 (Connection reset by peer)]
mrsolo__ has joined #ocaml
pango is now known as pangoafk
pangoafk is now known as pango
pauldia has joined #ocaml
vinceviper has quit ["Leaving"]
love-pingoo has joined #ocaml
Skal has joined #ocaml
revision17__ has joined #ocaml
andreas_ has joined #ocaml
<andreas_> hi
<andreas_> I am pretty new to ocaml and I am having some difficult time witch the type system
<andreas_> maybe somebody can help
<pango> well, don't ask to ask... what's the problem ?
andreas_ has quit []
<pango> a problem with english ?
Revision17 has quit [Connection timed out]
andreas_ has joined #ocaml
<andreas_> sorry I was disconnected
<andreas_> ok, now
<andreas_> type aa_sequence = aa array ;;
<andreas_> type char_sequence = char array ;;
<andreas_> type sequence = aa array | char array ;;
<pango> I guess you defined aa earlier ?
<andreas_> type aa =
<andreas_> A
<andreas_> | V
<andreas_> | F
<andreas_> | P
<andreas_> | M
<andreas_> | I
<andreas_> | L
<andreas_> | D
<andreas_> | E
<andreas_> | K
<andreas_> | R
<andreas_> | S
<andreas_> | T
<andreas_> | Y
<andreas_> | H
<andreas_> | C
<andreas_> | N
<andreas_> | Q
<andreas_> | W
<andreas_> | G
<andreas_> | Any
<andreas_> | Gap
<andreas_> | Endgap
<andreas_> | None ;;
<pango> ok, sequence type needs constructors too
<andreas_> yes
<andreas_> :)
* andreas_ well in principle, all i want is a type 'sequence' that can be either an array of characters or an array of aa
<ppsmimou> I would avoid redefining None
<andreas_> can you give me a code example?
<pango> type sequence = Array of aa array | Char of char array
<pango> (maybe not best constructors names, but I hope you get the idea)
<andreas_> type sequence = AASeq of aa array | CharSeq of char array
<pango> for example, yes
<andreas_> would that be possible?
<andreas_> what are the constructors good for?
<pango> as long as you start with a capital, it should be ok
<pango> to construct values ;)
<pango> let seq = AASeq [| K; R; C; N |]
<pango> match seq with
<pango> | AASeq a -> (* code for aa arrays *)
<pango> | CharSeq cs -> (* code for char arrays *)
<andreas_> many thx
<andreas_> I will try it ...
<andreas_> let a = AASeq Array.make 3 K
<andreas_> would that work?
<pango> maybe () around Array.make ...
<andreas_> let a = AASeq (Array.make 3 K)
<pango> yes
<andreas_> ok, i see
<andreas_> an irc channel is worth more than 10 books ;)
<pango> well, there's no exclusive or between the two ;)
<andreas_> ?
<pango> books are still useful to learn all the intricated details of syntax and semantic
<andreas_> you are right
<pango> sum/variant/algebraic types are *very* useful, so I recommend reading some more about them
<andreas_> I actually printed the pdf version of the book :)
<pango> it'd be great if it was updated to recent ocaml versions, some restrictions mentionned in the book are no longer true
<andreas_> I was wondering if there is a good commercial book about ocaml
<andreas_> Maybe I am mistaken but this book has never been published in english by oreilly, right?
<pango> well, this one was "commercial", it's the online version of an o'reilly book
<pango> good question
<andreas_> I could not find an oreilly book on ocaml
<andreas_> in english
<sieni> There's no such thing \o/
<sieni> except of course the web version
<andreas_> I don't understand why ocaml is still so underused
<sieni> well, there are good competitors, like Haskell, Clean and Standard ML ;-)
<pango> unusual syntax ;)
<andreas_> but performancewise
<sieni> and of course the OCaml compiler has a crappy license (QPL)
Amorphous has quit ["arg... must... shutdown... computer burnin..."]
Amorphous has joined #ocaml
<andreas_> With the new type I get some strange error messages:
<andreas_> print_char x.(i).(j);
<andreas_> This expression has type Util.sequence but is here used with type 'a array
<pango> correct, a sequence is not an array, it's a sum type
<andreas_> that is I loose all the Array functionalities
<pango> that's why you need to "deconstruct" it using pattern matching to access the array (in the case it's an AASeq)
<pango> see my "match" code example above
<andreas_> ok, I try
holo has joined #ocaml
<pango> andreas_: the benefit of this is that you cannot forget to check whether it's an AASeq or a CharSeq before using it (and get errors are runtime)
<andreas_> well the point is that I am always certain what kind of array x.(i) is, there is no ambiguity
<pango> then deconstruct it earlier, and pass the array around
<flux__> you can write a function that does it for you, so print_char (foo x.(i)).(j), where foo would throw an exception if it is something unexpected
<flux__> I would probably use pattern matching locally, though
<andreas_> for 95% of the program the array will consist of AASeq, only in the very beginning I need CharSeq
<pango> then maybe you don't want that sum type in the first place
<andreas_> Maybe it is better to use two different variables
<andreas_> exactly
<andreas_> that would save me a lot of pattern matching
<andreas_> I think I will create some help variable with type CharSeq, that should do
<pango> or only use chars in I/O functions
<andreas_> I don't understand
<pango> do you really need to build that char array, or could you directly create an aa array ?
<andreas_> I need it for a computation in another function, so I can't just skip it
<pango> create two functions, aaarray_of_chararray and chararray_of_aaarray ?
<andreas_> maybe
<pango> once you have aa_of_char and char_of_aa, it's just an Array.map away...
taw has joined #ocaml
<taw> hello
<taw> is there some standard type for resizable arrays, like STL vector<> ?
<pango> no
<pango> andreas_: let aaarray_of_chararray = Array.map aa_of_char and chararray_of_aaarray = Array.map char_of_aa
<pango> done ;)
<pango> taw: extlib has dynarrays
<andreas_> thx
<andreas_> let compress aln =
<andreas_> match par.m with
<andreas_> 1 -> (
<andreas_> let seq = Array.make aln.n_in "bla" in
<andreas_> for i = 0 to aln.n_in do
<andreas_> let seq_concat a b = function
<andreas_> '.' -> a
<andreas_> | b -> a ^ (String.make 1 b)
<andreas_> in
<andreas_> seq.(i) <- Array.fold_left seq_concat "" aln.x_char.(i);
m3ga has joined #ocaml
<andreas_> print_string seq.(i);
<andreas_> print_string "\n";
<andreas_> done;
<andreas_> )
<andreas_> | _ -> () ;;
<flux__> a paste site is very much preferred.
<andreas_> sorry
<andreas_> on line "seq.(i) <- Array.fold_left seq_concat "" aln.x_char.(i);" the compiler complains with "This expression has type string -> 'a -> char -> string
<andreas_> but is here used with type string -> 'a -> string"
<flux__> btw, those array elements will all contain the same "bla", not different "bla"s
<andreas_> I have no idea what I am doeing wrong
<andreas_> it does not matter I overwrite them all
<pango> beware of "function"
<pango> seq_concat is a function of 3 arguments, as written
<pango> a, b, and an anonymous third parameter
<andreas_> thx I see
<andreas_> let seq_concat a = function
<andreas_> :)
<flux__> andreas_, so yu're aware that let a = Array.make 2 "foo" in a.(0).[0] <- 'z'; a results in [|"zoo"; "zoo"|]?
<flux__> oh, right
<flux__> never mind ;)
<andreas_> it compiles
<flux__> it probably works then, too ;)
<pango> if performance is a concern, you could use a Buffer.t instead of catenating strings
<andreas_> that's the nice thing about ocaml, once it compiles it probably all good
<pango> let buffer = Buffer.create 5 in
<pango> Array.iter (fun b -> if b <> '.' then Buffer.add_char buffer b) aln.x_char.(i);
<pango> seq.(i) <- Buffer.contents buffer
andreas_ has quit []
taw has left #ocaml []
andreas_ has joined #ocaml
<andreas_> is it possible to do pattern matching on strings?
<andreas_> let's say I have a string that starts with ">..."
<andreas_> match line with
<andreas_> | s when s.[0] = '>'
<love-pingoo> that's possible
<love-pingoo> but it isn't a pure pattern anymore.. the side condition after the when can actually be arbitrary and the compiler's coverage check will thus skip that clause
<andreas_> could I match the line directly agains a regular expresssion?
<love-pingoo> andreas_: not that I know, unfortunately :(
<love-pingoo> you can only match constant strings
<love-pingoo> for chars, you can write intervals
<love-pingoo> | 'a'..'z' ->
<andreas_> so I would need several "| s when s.[0] = '>'" lines if I wanted to do distinguish several strings
<love-pingoo> yes.. or something more clever depending on the several kind of strings you want to recognize
Tachyon76 has joined #ocaml
<love-pingoo> like match s.[0] with ..
<love-pingoo> palomer: does micmatch perform coverage check ?
<love-pingoo> s/palomer/pano/
<love-pingoo> s/pano/pango/...
<pango> never used it
<pango> don't know if it can be done with regexps
<love-pingoo> for true regular expressions, yes
<love-pingoo> if you add more funky stuff (full perl re does) then it becomes undecidable
<love-pingoo> for example if you add grouping and the ability to match against what has been captured in a group
m3ga has quit ["disappearing into the sunset"]
<pango> sounds right
<love-pingoo> perl regexp /(.*)\1/ isn't regular for example
<pango> yes, it's no longer equivalent to an automaton
<love-pingoo> that's the point
<pango> I wonder if the same job could be done with streams
<pango> that may be enough, depending on what needs to be parsed
<andreas_> how do I have to specific regular expressions if I urse the Str module?
<andreas_> would "Str.regexp ^>aa" be ok?
<love-pingoo> # Str.string_match (Str.regexp "bl[ah]") "blh" 0 ;;
<love-pingoo> - : bool = true
<love-pingoo> andreas_: the ^ is useless, string_match requires you to fix where the match starts
<andreas_> so I have to quote the regular expression
<pango> # Str.regexp ;;
<pango> - : string -> Str.regexp = <fun>
<pango> argument is a string
<andreas_> thx
ski has quit [Read error: 110 (Connection timed out)]
ski has joined #ocaml
<holo> i have an type error in my lex analyser, the code is the following: http://pastebin.com/653384
<holo> the error output is: http://pastebin.com/653386
<holo> i'm using camllight
<dylan> why?
<holo> dylan, why using camllight?
<love-pingoo> holo: your float token seems to require a parameter
<love-pingoo> on line 62 you must provide that parameter
<pango> holo: all branches of a match must have the same type, and the other branch is "FLOAT" (and not FLOAT something)
<holo> dylan, becouse i'm learning caml, and camllight is for learning purppose
<holo> hmm
<love-pingoo> holo: if you have the choice, choose ocaml, it's as easy to learn, and there is a wider community, and you'll know a general purpose language
<love-pingoo> holo: btw #close doesn't exist
<pango> and you cannot do that mistake, because ocaml doesn't allow partially applied constructors ;)
<holo> love-pingoo, i'll put it there, the close stream. i know, but as this is for school evalution with camlight, i think its safer to use what they use to evaluate
<holo> sorry for the comments in portuguese :s
<dylan> heh, I didn't even notice.
<holo> grr, if i fix that i know i will have another error in other side
<love-pingoo> holo: if it's for school, then there's nothing to say.. you'll move to ocaml later, and live a long and happy life ;)
<love-pingoo> I actually didn't know that constructors had that function-like behaviour in camllight.. I'd prefer that in OCaml
ski_ has joined #ocaml
ski has quit [Nick collision from services.]
ski_ is now known as ski
<holo> weird
<holo> it has type char and is used with type char stream, but in the option ":" below he doesn't complain with that
<holo> ok and i removed the #close :s
<holo> they aren't in the same match with already
<love-pingoo> holo: your i is a stream, so it's not a char
<love-pingoo> just as you said
<love-pingoo> you must explicitely peek the first char of the stream
<love-pingoo> or whatever
<love-pingoo> in the second branch it doesn't complain because you're not trying to string_of_char(i)
descender has joined #ocaml
<holo> thanks love-pingoo!
<holo> i haven't fixed yet but i know know the reason
<holo> the secret is to interpret correctly the errors
<holo> among other stuff :s
<holo> is there any explicit conversion from stream to other type?
<holo> if not i have to fix the algorithm ;s
<holo> |[<'(`.`|`=`|`(`|`)`|`-`|`+`|`/`|`:`|`>`|`<`|`*`) as c;
<holo> (ident_symbol(string_of_char c)) i >] -> [< 'i ; alex code>]
<holo> the "c" is being interpreted as a char
<holo> and is converted to a string
<holo> "love-pingooyou must explicitely peek the first char of the stream"
<flux__> am I imagining things, as has there been lately been an influx of ocaml-newcomers to the channel?
<flux__> I'm not complaining, definitely ;)
<holo> flux__, just school work for me, maybe some serious work in the future who knows.. but this is hard, i dunno
andreas_ has quit []
<flux__> (I was thinking of a natural reason, yes, for instance a bunch of people going the same course would join)
andreas_ has joined #ocaml
<holo> lolol
andreas_ has quit []
<holo> how do i make from 0 to 9 as integers?
<holo> i tried 0..9 but its syntax error
<mellum> there's no special syntax for that
<mellum> or do you mean a loop?
<holo> `0`..`9`
<holo> this is charsl
<holo> i want integers
<mellum> Oh. No idea.
<holo> np
<holo> :)
<holo> any one with idea? :x
<flux__> you could write a function range low high
<love-pingoo> holo: if your range is not too wide you can write | 0 | 1 | 2 | 3 | 4 -> ...
<pango> or use guards
<pango> | x when x >= min && x <= max ->
<holo> love-pingoo, yeah that's what i did and it worked
<holo> pango, that's a good idea
TaXules has quit [Remote closed the connection]
TaXules has joined #ocaml
Smerdyakov has joined #ocaml
Tachyon76 has quit ["Leaving"]
descender has quit [zelazny.freenode.net irc.freenode.net]
descender has joined #ocaml
palomer has left #ocaml []
love-pingoo has quit ["Leaving"]
Snark has joined #ocaml
cjeris has joined #ocaml
Schmurtz has joined #ocaml
<cjeris> If a, b, c : (float, float64_elt, c_layout) Bigarray.Array2.t, and I do a.{i,j} <- b.{i,j} + c.{i,j}, how many intermediate boxed floats are generated?
Submarine has joined #ocaml
<pango> check asm
Amorphous has quit [zelazny.freenode.net irc.freenode.net]
mellum has quit [zelazny.freenode.net irc.freenode.net]
jgrimes has quit [zelazny.freenode.net irc.freenode.net]
Amorphous has joined #ocaml
mellum has joined #ocaml
jgrimes has joined #ocaml
<cjeris> can't tell if it's 2 or 3, but at least 2.
ski has quit [Connection timed out]
<pango> I'm not an asm guru, but I see no boxing
pango is now known as pangoafk
cjeris has quit [Read error: 104 (Connection reset by peer)]
love-pingoo has joined #ocaml
pangoafk is now known as pango
Narrenschiff has joined #ocaml
piggybox has quit [Connection timed out]
_JusSx_ has joined #ocaml
<holo> why can't i do what is pasted there
<holo> when i add:
<holo> |"-" -> (match i with
<holo> [<'`>`>] -> FLECHA
<holo> [<'i>] -> raise(alex_error "Unknown symbol")
<holo> [<>] -> MINUS );;
<holo> the program gives unbound function in the end of the program.. this always happens when i touch the program
<holo> did i forgot () ?
<flux__> don't you have a few | -characters missing?
<flux__> like, for each matched case
<flux__> s/case/pattern/
<holo> yeah, it isn't exaustive
<holo> but i doesn't need to be in this case
<flux__> I don't mean that
<holo> becouse it will get in only stuff to be accepted
<holo> oh
<holo> then what?
<flux__> you want to put |-characters before those [-characters for that to be valid syntax, just like above?
<holo> LOL
<holo> dude
<holo> you're right
<holo> ok fixed
<holo> now, why this isn't exaustive?:
<holo> (match i with
<holo> [<'`=`>]-> ASSIGN
<holo> |[<'i>]-> raise(alex_error "Unknown symbol")
<holo> |[<>] -> raise(alex_error "Unknown symbol"))
<holo> every stuf i do like this says it isn't exaustive
<holo> ok nevermind, this isn't crucial anyway
<holo> :)
Snark has quit ["Leaving"]
<holo> what's wrong with this?
<holo> |"." -> (match i with
<holo> [<'(`a`..`z`|`A`..`Z`)>] -> DOT
<holo> |_ -> (match i with
<holo> [<'c>] -> ident_kwd (string_of_char i)
<holo> |[<>] -> ident_kwd (string_of_char i) ))
<holo> it says it has a syntax error in "|_"
<holo> here is more explicit the context
<holo> ok this is the whole code: http://pastebin.com/654214
_JusSx_ has quit ["leaving"]
<holo> its a syntax error! its easy to fix (but not for as it seems).. anyone?
<pango> shouldn't it be [<>] ?
slipstream has joined #ocaml
pauldia has quit [Read error: 110 (Connection timed out)]
<holo> pango, [<'_>]
<holo> this worked
<holo> but i don't know yet if it is what is supposed to be
<holo> is it?
<holo> any other caracter
<holo> or [<'`_`>]
<holo> it looks like a stupid guy with large ears smiling at something stupid
slipstream-- has quit [Read error: 110 (Connection timed out)]
<holo> ok, this isn't going anywhere
<holo> if i used flex+bison it would be finished by now
<holo> or not
<pango> well, I haven't used streams yet, so I'm just guessing too ;)
<pango> I think the problem with [<'_>] is that is will consume a symbol
<pango> why not merge the two matches anyway ?
<holo> pango, i can't
<holo> becouse match with doesn't aprove different types of returns
<holo> and the ones that are on the 3rd nested match are different types
<pango> well, inner match value is the same as its branches too, so I must be missing something
<pango> match is an expression
<holo> oh
<holo> i didn't know
<pango> well, it's simple, everything is an expression ;)
<holo> pango, you're sounding like "oh, everything is an object"
<holo> "oh, everything is a file" -plan9
<holo> :p
<holo> "oh, everything are molecules"
<pango> doesn't ident_kwd return a token ?
<holo> pango, yeah
<pango> all branches look of the same type then... (?)
<holo> or kwds or IDENT or FLOAT
<holo> well, yes
<holo> but tokens of different types
<pango> all those are token constructors
<pango> no, token is the type
<holo> like FLOAT of float
<pango> constructors are different ;)
<holo> ok ok
<pango> so it should be ok
<holo> i disnested them
<holo> i have several options that are the same
<holo> but have different matches
<pango> won't work, I think
<pango> first case will match an consume the token
<pango> other case will never be considered
<pango> actually, the problem is not that the character will be consumed, but that match is "deterministic" : once a branch matches, other branches will never be visited
<holo> yes! i don't them to revisited
<holo> pango, first one will be consumed if it matches
<holo> pango, right?
<pango> from what I understand from stream docs, yes
<holo> till now it has been working
<holo> > .... ......match i with
<holo> > [<'i>] -> ident_kwd (string_of_char i).
<holo> This expression has type char stream -> token,
<holo> but is used with type token.
<holo> |"-" -> (match i with
<holo> [<'`>`>] -> FLECHA
<holo> |[<'i>] -> raise(alex_error "Unknown symbol")
<holo> this one doesn't cause problem
love-pingoo has quit ["Connection reset by by pear"]
<pango> ident_kwd expects two arguments
<pango> str, and the anonymous argument for 'function'
<pango> maybe you meant 'match str with' instead of 'function' ?
<pango> mmmh no, I'm not sure what you wanted ;)
<holo> pango, ident_kwd(string_of_char c)
<pango> currently ident_kwd type is string -> Stream.t -> token
<holo> almost in the end of the code
<holo> so it's string he is expecting
<holo> and only one parameter
<pango> then replace 'function' with 'match str with' and remove streams handling parts from ident_kwd
<holo> hmm i can't!
<pango> function creates an anonymous function of one parameter
<holo> that is very important for the IDENT and FLOAT
<pango> # let rec fact = function
<pango> | 0 -> 1
<pango> | n -> fact (n-1) * n ;;
<pango> val fact : int -> int = <fun>
<pango> it adds an anonymous parameter, and pattern matching over that parameter
<pango> so in 'let rec ident_kwd str = function ...', ident_kwd is a function of 3 parameters!
<pango> sorry 2
<pango> str, and the anonymous one for function
<holo> ha
<pango> it's as if you wrote 'let rec ident_kwd str stream = match stream with ...'
holo has quit ["Leaving"]
smimou has joined #ocaml
revision17__ has quit ["Ex-Chat"]
Submarine has quit ["Leaving"]
<pango> 'function' should have been given a more cryptic name... 'landmine', or something ;)
Skal has quit [Remote closed the connection]
<sieni> btw. what's the etymology of the term "function"
<zmdkrbou> from latin word 'functio' : achieving, execution
krypt1 has joined #ocaml
smimou has quit ["bli"]