flux__ changed the topic of #ocaml to: OCaml 3.09.2 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/
<ketty> no
<metaperl> I'm getting a syntax error on the blank lines of this file... no text there at all: http://ocaml.metaperl.com/ora-book/lextree.ml
<ketty> metaperl: you mean the last line?
<metaperl> ketty: no... just in blank lines well after the last line of text
<ketty> yes..
<ketty> what i meant
<ketty> you cant end with ;
<ketty> it is a separator
<metaperl> oh yeah
<ketty> it is not needed at all here
<ketty> neither are the ;; needed
<ketty> just remove all ; and ;;
<ketty> :)
<ketty> hmm.. they are needed inside of lists thou.. so maybe not really all...^^'
<Lob-Sogular> gah... syntax is still tripping me up... it's complaining on the highlighted line: http://pastebin.com/723736
<ketty> Lob-Sogular: the problem is "let ... in"
<ketty> it is not a complete expression
<Lob-Sogular> oh?
<ketty> it is allways used as "let ... in [expression]"
<ketty> and the binding is not global
<ketty> but local
<Lob-Sogular> that code, btw, is in a function (don't know if that matters)
<ketty> you will never be able to access the result
<ketty> since it is only bound localy
<ketty> Lob-Sogular: http://pastebin.com/723743
<ketty> eh.h. sorry
<ketty> me stupid :)
<ketty> like this: http://pastebin.com/723746
<Lob-Sogular> I need result for later... maybe I should just paste the whole function...
<ketty> ok
<Lob-Sogular> which is of course slightly different as I've been playing with the code
<ketty> Lob-Sogular: http://pastebin.com/723753
<Lob-Sogular> ah hmmm i see!
<ketty> good :)
<Lob-Sogular> so in that instance, what I'm really doing is defining a function 'result' that gets passed to the template class's constructor? (ignoring eager vs. lazy evaluation)
<ketty> hmmm
<ketty> not really
<ketty> you bind 'result' to what the following expression evaluates too..
<ketty> s/too/to
<ketty> and regarding functions.. "let f x = ..." is just syntactic sugar for: "let f = fun x -> ..."
<Lob-Sogular> ahhh
<Lob-Sogular> that clears it up a bit for me
<ketty> nice :)
<mikeX> isn't fun x syntactic sugar for 'function x' too?
<Lob-Sogular> (I'm starting to think ocaml-tutorial.org is not the best resource)
<ketty> Lob-Sogular: the manual is the best resource :)
<mikeX> indeed, it seems a bit outdated, and confusing at times
hikozaemon has joined #ocaml
<Lob-Sogular> ketty: yeah, I just need to unlearn all the wrong concepts I seem to have learned and replace them with correct concepts
<ketty> hehe :)
<Lob-Sogular> heh... this all makes a lot more sense now
<Lob-Sogular> thanks
<ketty> np
mellum has quit [kornbluth.freenode.net irc.freenode.net]
mellum has joined #ocaml
Purice has joined #ocaml
Purice has quit [Remote closed the connection]
sidewinder has joined #ocaml
khaladan has quit [Read error: 104 (Connection reset by peer)]
gim__ has quit []
mikeX has quit ["leaving"]
jcreigh has joined #ocaml
<metaperl> hello ... I need some help writing a function exists() that looks through a dictionary for a word: http://ocaml.metaperl.com/ora-book/lextree.ml
<metaperl> I'm actually afk - playing Myth right now...
<metaperl> I'll be back in some time later...
<metaperl> :)
dark_light has quit [Remote closed the connection]
jcreigh has quit ["Do androids dream of electric sheep?"]
jokoroo has joined #ocaml
jokoroo has left #ocaml []
Smerdyakov has quit ["Leaving"]
Skal has joined #ocaml
slipstream-- has joined #ocaml
khaladan has joined #ocaml
slipstream has quit [Read error: 110 (Connection timed out)]
khaladan_ has joined #ocaml
khaladan has quit [Read error: 110 (Connection timed out)]
khaladan_ is now known as khaladan
pango is now known as pangoafk
pangoafk is now known as pango
hikozaemon has quit ["Leaving..."]
mikeX has joined #ocaml
Tachyon76 has joined #ocaml
sidewinder has quit [Read error: 110 (Connection timed out)]
mikeX_ has joined #ocaml
mikeX has quit [Nick collision from services.]
mikeX_ is now known as mikeX
Snark has joined #ocaml
Revision17 has quit [Connection timed out]
<ketty> metaperl: you still need help?
mikeX has quit ["leaving"]
<metaperl> ketty: yes, but I'm about to take bath... I'm back here in about 30 mins
<ketty> ok :)
<dylan> pssh, real programmers don't bath.
* ketty ain't a real programmer either :)
<dylan> I guess I'm not either.
girodt has joined #ocaml
<girodt> hi there. i'm trying to use Arg.parse for the first time, but it seems like i don't get something. here is my code : http://ocaml.pastebin.com/724584
<girodt> this doesn't work - here at least.
<ketty> hmm.. it's some time since i used Arg now...
<girodt> what it does is : whether i do ./test or ./test -v it always print "verbose : false"
<ketty> the type of Arg.parse is: val parse : (key * spec * doc) list -> anon_fun -> usage_msg -> unit
chessguy has joined #ocaml
<ketty> but you just give it one argument...
<girodt> hmm ...
<ketty> anon_fun is (string -> unit) and usage_msg is string
<girodt> are you sure ? i'm giving it a list with one tuple containing "-v", Arg.Set and "activer ..."
<girodt> it is 3 args isn't it ?
<ketty> no, you give it one list as an argument
<girodt> damnit
<girodt> ok
<ketty> :)
<girodt> i see what you mean
kral_ has joined #ocaml
kral_ is now known as kral
<girodt> yeeahahhhhh :)
<girodt> thank you
<ketty> :)
reltuk has joined #ocaml
Amorphous has quit [kornbluth.freenode.net irc.freenode.net]
descender has quit [kornbluth.freenode.net irc.freenode.net]
Amorphous has joined #ocaml
descender has joined #ocaml
Smerdyakov has joined #ocaml
shawn_ has quit [Connection timed out]
girodt has quit ["leaving"]
mikeX has joined #ocaml
<metaperl> ketty: I'm back
<metaperl> hello ... I need some help writing a function exists() that looks through a dictionary for a word: http://ocaml.metaperl.com/ora-book/lextree.ml
<ketty> lets see...
<ketty> it doesn't complie, right?
<ketty> this line: (c:cs) -> dic == [] && List.size(word) > 0 -> false
mikeX has quit ["leaving"]
<ketty> metaperl: your function is supposed to be recursive, isn't it? but there is no recursive call inside it...
<metaperl> ketty: I havent even tried to compile it.
<ketty> ok :)
<metaperl> I was just pseudo-ocaml programming
<Smerdyakov> metaperl, wow. Didn't you ask about this yesterday? =D
<metaperl> I then said I was leaving to play games
<dylan> metaperl has made some pretty good progress in the few days he's been here, I think.
<metaperl> but I'm a beginner. I dont know how to code this function
<Smerdyakov> metaperl, every exercise in a book should be doable using only what was already introduced.
<metaperl> Smerdyakov: you speak words of truth my friend
<Smerdyakov> I don't know the book, so I don't know if you're trying to use features that didn't show up yet there.
* metaperl considers buying the book
<Smerdyakov> If you are, think again.
<Smerdyakov> And never ask if code will work without compiling it first.
<ketty> about the '->'.. it is used between a [pattern] and an [expression]..
<ketty> well, he didn't ask if it would work
<dylan> Smerdyakov: Even if it involves calls to Unix.unlink?
<ketty> he wanted help with it :)
<metaperl> lol
<Smerdyakov> dylan, yes. I didn't say *run* it.
<dylan> compile, ask #ocaml, run?
<dylan> That sounds like a good idea.
<metaperl> my code is the comment section... because I am not confident enough to write the functoin
<metaperl> I have two patterns, [] and (c:cs)
<Smerdyakov> It's just stupid not to take advantage of an automatic sanity checker at the most basic level before burdening the channel with a question.
<metaperl> oops that's Haskell syntax
<dylan> I think that's c :: cs
<metaperl> yes, fixed
<ketty> :)
<metaperl> you can use List functions on strings right?
<dylan> Nope
<metaperl> how is OCaml's unicode support?
<metaperl> and utf8 support?
<dylan> Strings are not lists.
<metaperl> List.size(string_name) won't work?
<dylan> nope
<dylan> String.length
<ketty> you'll have to convert them into list in that case...
<ketty> which is possible but maybe not a good idea...
<Smerdyakov> Use SML instead. There, strings are char vectors!
<Smerdyakov> And you get the equivalents of the standard higher-order functions for vectors.
<dylan> ugh.
<Smerdyakov> dylan, ??
<dylan> This reminds me of the questions on my lug, that go: "Q: How can I get apache2 configured properly on debian? A: install Fedora"
<Smerdyakov> Dumb question. Configuring Apache on Debian is easy.
<dylan> Not for someone that has just switched from using windows.
* ketty don't have problem with apache on debian either
<dylan> it was a bit more complicated, something about URL rewriting.
finelemo1 has joined #ocaml
<dylan> which is also easy. But the point is recommending an orange to sovle a problem with an apple.
<dylan> *solve.
<metaperl> how is OCaml's unicode support?
<dylan> metaperl: there are libraries that add support for it.
<ketty> metaperl: what do you want from it?
<ketty> strings are just bytestrings in ocaml
<metaperl> nothing at the moment... Perl has a utf-8 mode for unicode support
<ketty> there are such modules for ocaml too..
<dylan> Camomile provides UTF8 stuff, I believe.
<ketty> yes, and so does extlib, lablgtk, etc...
<dylan> and ocaml strings are 8-bit clean, so there should be no problem.
<metaperl> HOw do you pattern match on a string? separating it into first and rest?
<dylan> you can't really.
<ketty> metaperl: regular expressions?
<dylan> you can match whole strings, and that's about it.
<metaperl> so an if then else is better
<dylan> there is a camlp4 thing to allow pattern matching to use regexp, though
<metaperl> using String.length instead of [] and (c::cs)
<dylan> well,
<dylan> you can match the empty string with ""
<dylan> match "bunnies" with "" -> "blaa" | s -> s ^ s
<metaperl> Ocaml is notably lacking in parametric polymorphism.... String.length and List.size ... the same sort of incongruity that I see in Perl.. why not have a single function length that operates on String and List?
<dylan> Because a string is not a list.
<pango> type inference ?
<dylan> they're not the same type.
<dylan> A string *should* be an array, but sadly it's not.
Demitar has quit [Read error: 110 (Connection timed out)]
<Smerdyakov> dylan, S M L ..... ;)
Demitar has joined #ocaml
<dylan> Smerdyakov: A M D 6 4
<Smerdyakov> dylan, I'm talking about a language, goofball.
<ketty> dylan: how does amd64 solve things?
<dylan> I am talking about mlton not compiling to my arch.
<ketty> ahhh..
* ketty is using amd64 too
<dylan> I'm also quite fond of ocaml's syntax. I suspect the next language I use will be haskell.
<metaperl> could I get some help with this exists() function? It's not compiling: http://ocaml.metaperl.com/ora-book/lextree.ml
<dylan> and I think it is dishonest to turn away #ocaml newbies to SML
<Smerdyakov> dylan, "dishonest"?
<metaperl> Smerdyakov and I go back a long way. I know about him very well...
<metaperl> I can't be deceived by his tactics
<dylan> Hehe.
finelemon has quit [Read error: 110 (Connection timed out)]
<metaperl> anyway, can I get some help with this function
<dylan> Smerdyakov: I cannot find an english word for it, that's close.
<ketty> metaperl: please post the compiler errors too..
<metaperl> oh
<metaperl> # #use "lextree.ml";;
<metaperl> File "lextree.ml", line 49, characters 4-5:
<metaperl> Syntax error
<ketty> (and if you use pastebin, you get syntax highlightning too, which helps)
<metaperl> _ -> (dic == []) ;; (* line 49 so to speak *)
<ketty> as well as line numbering :)
* dylan vanishes in a puff of cereal.
<ketty> metaperl: and where is the file in question?
<metaperl> ketty: where is it?
<metaperl> what do you mean?
<ski> look above
<ketty> the link you gave does not contain such a line
<ketty> sorry
<metaperl> it is actually line 38 now
<ketty> stupid caching :)
<metaperl> I need to think this out a bit more...
<metaperl> dic is not a list
<ketty> metaperl: there is still no recursive call
<metaperl> it is Letter char * book * lex_node list
<metaperl> yes....
<ketty> if you wan't you can pretend strings are list
<ketty> and just convert them to lists before you use them
<metaperl> ketty: that is irrelavant
<ketty> if that helps you
<ski> i think you don't want to separate match branches by commas
<metaperl> jsut convert to strings you mean
<pango> metaperl: actually dict is supposed to be a lex_tree, so it is a list
Tachyon76 has quit ["Leaving"]
<ketty> if dict is empty and the string is not, shouldn't you return false?
<metaperl> hold on. How do I extract parts of the the dictionary which is of type Letter char * ... PHONE .. brb
<ketty> metaperl: i am not sure what you mean, but i think the answer is pattern matching :)
<metaperl> i'm on phone
<metaperl> brb
<metaperl> ketty: yes... I was working on how to formulate "empty dictionary"
<ketty> well, since dictionary is a list, [] would be an empty dictionary
<ketty> but here you do: (dict == [])
<ketty> which should really be: (dict = [])
<ketty> and it returns true if the dictionary _is_ empty
<ketty> but that is not what you want right?
<metaperl> well the problem is this
<metaperl> a dictionary is a list of lex nodes... hmmm
<metaperl> type lex_node = Letter of char * bool * lex_tree
<metaperl> and lex_tree = lex_node list;;
<metaperl> yes
<metaperl> so as long as a dictionary is a lex_tree, then I just do list operations on it to see if it is empty. I need to rework my build of the trie above so that it is a lex_node list
<ketty> ok
smimou has joined #ocaml
girodt has joined #ocaml
<girodt> hey again. this one : http://ocaml.pastebin.com/724774 -- This expression has type string but is here used with type unit -- I don't understand why -- when my read_line is not inside my if statement, everything is okay. (I think i'm getting tired).
<metaperl> yes, Ocaml does a great job of pretty-printed extended lists...http://ocaml.pastebin.com/724780
<metaperl> what does "open Printf" mean?
<metaperl> use the Printf library, importing the functions?
<ketty> girodt: read_line has type "unit -> string", right?
<metaperl> why is there a semicolon after "done" instead of 2 semicolons
<metaperl> let manual = ref true ;; (* what does this do *)
<girodt> ketty: yes
<girodt> metaperl: open Printf --> to avoid typing Printf.printf each time
<ketty> an expressino inside of an if statment without an else clause needs to have type unit
<girodt> ketty: oh.
<girodt> :)
<ketty> minus spelling errors :)
<metaperl> let manual = ref true ;; (* what does this do *)
<metaperl> what does that do?
<girodt> metaperl: it defines a boolean ref
<girodt> it is just a flag to enable or disable an option in my code
<ketty> it is evil imperative stuff...
<girodt> indeed.
<metaperl> why not let manual = true ;;
<girodt> because it may change, as it is set with Arg.parse
<ketty> metaperl: references are mutable
<girodt> metaperl: as you may have guessed, this is *not* my whole code, just a chunk i put out of it ...
<girodt> ketty: so i've got this unit thing ...
<ketty> girodt: you need to remember that ';' is just a separator..
<girodt> i'm turning really slow now ... is it possible to avoid my problem ?
<ketty> girodt: you can allways use "ignore" to convert values of any type into unit
<girodt> ok
<ketty> ignore has type: 'a -> unit
<girodt> hmm
<girodt> so all i have to do is ignore (read_line ()) !!
<girodt> woooohooo :)
<girodt> thanks again ketty you're really helpful !
<ketty> yes, if you don't care about the return value of read_line
<girodt> i do :)
<ketty> then you need to bind it somewhere :)
<girodt> this is just a "press return to continue"thing
<ketty> ahh..
<ketty> then it is ok :)
<ketty> are not all those extra ';' giving you compile errors?
<girodt> well, it does not seems to.
<ketty> weird...
<girodt> by the way, another question : i'm using Str.regexp to parse some data and i've got a lot of warning about wrong backslashes ... is it possible to avoid this ?
<ketty> hmmm...
<ketty> you need to put _a lot_ of "\" in your strings :)
<girodt> ok so I have to backslah my backslashes or something like that ... d'oh :)
<ketty> yes, several times eaven
<girodt> thanks again for your help - got to go. see you tomorrow, maybe ...
khaladan has quit [Read error: 104 (Connection reset by peer)]
<girodt> bye
<ketty> bye
girodt has quit ["leaving"]
<metaperl> I really would appreciate some help right here: http://ocaml.metaperl.com/ora-book/lextree.ml
<metaperl> line 38 syntax error
<metaperl> the logic is fine.. but my match syntax and if then else syntax is failing
<ketty> matches needs to be separated by |
<ketty> :)
<metaperl> oh
<metaperl> lets say I have a list of data items: ls = [d1, d2, ... dn]... I want to apply f to each item of ls in turn. f applied to dn will return a boolean. I want to short-circuit-or these results
<ketty> let rec apply f ls = match ls with [] -> () | hd::tl -> if f hd then apply f tl
<ketty> metaperl: like this?
<metaperl> actually it should return true on if f hd
<metaperl> short-circuit or
<metaperl> once true the function is true
<metaperl> if f hd then truel else apply f tl
<metaperl> agree?
<metaperl> just think
<ketty> let rec apply f ls = match ls with [] -> assert false | [hd] -> f hd | hd::tl -> if f hd then apply f tl else false
<metaperl> no
<metaperl> why if f hd then apply f tl
<metaperl> if f head then true
<metaperl> there must be an any() function in Ocaml
<metaperl> List.any
<metaperl> ?
<ketty> hmm... you wanted the chain to stop if "f hd" was false, right?
<zmdkrbou> nope
<metaperl> ketty: no the other way around
<metaperl> I said "short-ciruit or"
<ketty> ok
<ketty> i am sorry
<metaperl> an or will stop, returning true once a true element is found
<ketty> i see..
<metaperl> You mean there is no List.any?
<ketty> there is List.fold_left
<metaperl> that was the first thing I thought of but I could not see how it fit into my plan
<ketty> List.fold_left (||) false (List.map f ls)
<metaperl> the strict nature of Ocaml makes that inefficient
<metaperl> the whole list will be mapped
<metaperl> and then folded
<metaperl> instead of only taking from the map what is needed
<metaperl> just think if that list had 1 million items each taking 1 second
<Snark> List.has ?
<ketty> let rec apply f ls = match ls with [] -> false | hd::tl -> if f ls then true else apply f tl
<metaperl> no such thing
<ketty> Snark: there is a List.exists
<Snark> no, List.exists
<Snark> yes
<metaperl> what webpage documents the Ocaml libraries?
<ketty> but then you allso would have to map the whole list
<pango> ketty: no, List.exists takes a predicate
<metaperl> Lists.exists does not exit upon find the element?
<ketty> ahh..
<ketty> sorry :)
<pango> metaperl: it does
* metaperl heaves a sigh of relief
<pango> you can check its implementation, it uses ||, that's shortcircuited
<metaperl> could someone please help. I have a syntax error in my if-then-else: http://ocaml.metaperl.com/ora-book/lextree.ml
<metaperl> very last line of program... I'm getting close :)
<ketty> where does end come from?
<ketty> the syntax is: if [boolean expression] then [expression of type 'a] else [expression of type 'a]
<metaperl> oh
<ketty> end does List.head really exist?
<ketty> s/end/and
<pango> it's List.hd, but it's seldom used ;)
<ketty> this looks very suspisious: Letter(c, boolean, children) = List.head dic
<pango> in this context, Letter(c, boolean, children) = List.head dic is a boolean expression
<ketty> that does not even compile
<ketty> c, boolean and children are unbound variables
<metaperl> ketty: yes, I dont know how to pattern match there. That is my latest error: http://ocaml.metaperl.com/ora-book/lextree.ml
<metaperl> but the elements of hte list are Letter of char * bool * lex_node list
<ketty> metaperl: let Letter(_,_, children) = List.hd dic in
<metaperl> so why cant I get the head
<metaperl> but I need the character
<pango> I suppose you meant let Letter (...) = List.hd ... in ...
<ketty> metaperl: let Letter(ch,_, children) = List.hd dic in
<metaperl> yeah, but I need the components of ... ok that will work... thanks
<metaperl> how do you pattern match a string into it's first char and the rest of it's characters?
<ketty> you dont :)
<ketty> but there is String.sub
<pango> well, you can do pattern matching on s.[0], which is a char
<pango> or on s.[i], and thread i along recursive calls, so you don't have to extract substrings. More efficient, less readable ;)
<metaperl> My List.head call is now not working... http://ocaml.metaperl.com/ora-book/lextree.ml
<metaperl> some help is appreciated
<pango> it's List.hd
<ketty> "Unbound value List.head" means that there is no such thing as List.head
<ketty> metaperl: the implementation of lists makes it very efficient to get the first element and the rest, of the list. but i don't think that is the case with strings...
<metaperl> oh
<metaperl> I'm starting to wonder if I should be recursing along the dictionary or along the word
<ketty> metaperl: both?
<metaperl> yes, that is true
* ketty takes a 20 minute break :)
* pango think metaperl should have a look at List.find
<metaperl> string_after s n returns the substring of all characters of s that follow position n
<metaperl> so to do a "rest" on a string would n be 1 or 2? let me play with it at the cmdline... that's easiest
* metaperl looks at List.find
<pango> strings are arrays are 0-based
<pango> s/are/and/
<metaperl> yes that fn is good, but it raises an exception!
<pango> yes... :j
<metaperl> they already covered catching exceptions though
arno_ has joined #ocaml
pango is now known as pangoafk
kral has quit ["Live fast, die young."]
chessguy has quit [" HydraIRC -> http://www.hydrairc.com <- Leading Edge IRC"]
pangoafk is now known as pango
cyyoung has joined #ocaml
multani has joined #ocaml
chessguy has joined #ocaml
cyyoung has quit ["This computer has gone to sleep"]
Skal has quit [Read error: 104 (Connection reset by peer)]
danly has quit [Read error: 113 (No route to host)]
Skal has joined #ocaml
cyyoung has joined #ocaml
Revision17 has joined #ocaml
shawn has joined #ocaml
cyyoung has quit ["This computer has gone to sleep"]
sidewinder has joined #ocaml
jcreigh has joined #ocaml
jcreigh has quit ["Do androids dream of electric sheep?"]
khaladan has joined #ocaml
chessguy has quit [" HydraIRC -> http://www.hydrairc.com <- Go on, try it!"]
Snark has quit ["Leaving"]
kral has joined #ocaml
cyyoung has joined #ocaml
chessguy has joined #ocaml
<metaperl> re: String pattern-matching. "" matches 0 chars.. is there a pattern for matching a string of 1 character?
<pango> you can match a string against a constant string, structurally
<pango> what you can do is use guards... match s with s1 when String.length s1 = 1 -> ... but that's about it
<kral> qualcuno di voi ha avuto esperienze con telefoni motorola?
<kral> sorry, wrong channel
* kral damns irssi, sometimes :)
Revision17 has quit [Read error: 110 (Connection timed out)]
<metaperl> # Str.string_after "hello" 1 ;;
<metaperl> Reference to undefined global `Str'
<metaperl> # str.string_after "hello" 1 ;;
<metaperl> Characters 0-3:
<metaperl> str.string_after "hello" 1 ;;
<metaperl> ^^^
<metaperl> Unbound value str
<metaperl> I can't get the Str library to work
cyyoung has quit ["This computer has gone to sleep"]
<ketty> metaperl: #load "str.cma"
<ketty> or start ocaml with str.cma in the command line
<metaperl> I need that in my program too I suppose.
<ketty> Str is not part of the basic library, so you need to link against it...
<metaperl> #use "str.cma";;
<metaperl> File "C:\cygwin\usr\local\bin\ObjectiveCaml\lib/str.cma", line 1, characters 12-13:
<metaperl> Illegal character (\000)
<metaperl> # #use "str.cma";;
<metaperl> File "C:\cygwin\usr\local\bin\ObjectiveCaml\lib/str.cma", line 1, characters 12-13:
<metaperl> Illegal character (\000)
<metaperl> #
<metaperl> the cygwin version is b0kred: the cygwin version is b0rked
<ketty> metaperl: not #use... #load
<ketty> '#use' includes an *.ml file textually
<ketty> '#load' dynamically links something...
<ketty> or loads or whatever :)
<metaperl> is that a compiled file? I tried to read it
<metaperl> oh
<metaperl> ok
<metaperl> let me try
<ketty> yes, it is a compiled library
<metaperl> oh heck
<metaperl> Administrator@LIFEBOOK:~/MyDocuments/metaperl.com/ocaml/ora-book$ ocaml str.cma
<metaperl> Cannot load required shared library dllstr.
<metaperl> Reason: dynamic loading not supported on this platform.
<ketty> hehe :)
<metaperl> it's not funny to me :)
<metaperl> i'm the one suffering :)
<ketty> look at ocamlmktop
* ketty just found out about ocamlmklib
* ketty is SOOOO happy =)
<metaperl> I'm trying out the native Cygwin ocaml. I dont know where by version came from.
<ketty> metaperl: you should be fine by just using ocamlmktop
<metaperl> I dont know what to do with it ... it seems to be just ocamlc
<ketty> it makes a staticaly linked interactive toplevel
<metaperl> so you mean ocamlmktop -o /usr/local/bin/myocaml
<ketty> ocamlmktop str.cma -o /usr/local/bin/myocaml
<metaperl> oh ok
<metaperl> no. same error
* metaperl resorts to google
* ketty gives metaperl a debian installer ^^
<metaperl> not on Windows.
<metaperl> i'm a hardware/os amateur. I like using Unix, but having a person debian box was hard... hard to operate with the internet company. hard to be in hotels
<metaperl> and GUI much less attractive than windows
<metaperl> and useability much less
* ketty thinks gnome is attractive
kral has quit ["Live fast, die young."]
<metaperl> Release notes on the MS Windows ports of Objective Caml ...
chessguy has quit [" Try HydraIRC -> http://www.hydrairc.com <-"]
<metaperl> Dynamic loading of DLLs is supported out of the box, without additional software
<metaperl> is anyone using Ocaml under Cygwin/Windows?
<metaperl> am I the only weenie in this entire channel?
<ketty> i did manage to compile something on windows a long while ago :)
<ketty> but i usually stay clear from it :)
<dylan> mingw version of ocaml is nicer
khaladan_ has joined #ocaml
khaladan_ has quit [Read error: 104 (Connection reset by peer)]
khaladan has quit [kornbluth.freenode.net irc.freenode.net]
descender has quit [kornbluth.freenode.net irc.freenode.net]
Amorphous has quit [kornbluth.freenode.net irc.freenode.net]
ramza3__ has joined #ocaml
chessguy has joined #ocaml
khaladan has joined #ocaml
Amorphous has joined #ocaml
descender has joined #ocaml
<metaperl> I just built ocaml for cygwin and I only have string.cmi and string.cmx files... no string.cma ...
<metaperl> ocamlmktop -o myexe string.cma
<metaperl> wont work because I dont have string.cma
<ketty> hmm... weird..
<ketty> did you try the mingw version?
khaladan has quit [Connection timed out]
Skal has quit [Remote closed the connection]
ski has quit [Read error: 110 (Connection timed out)]
chessguy has quit [" HydraIRC -> http://www.hydrairc.com <- Leading Edge IRC"]
ski has joined #ocaml
<metaperl> no, I built it from source
<metaperl> at least not in /usr/lib/ocaml/lib/
<metaperl> ah, it has str.cma
<metaperl> sa-weet!!!!
<metaperl> # Str.string_after;;
<metaperl> - : string -> int -> string = <fun>
<ketty> nice :)
<metaperl> i'm cooking with water now .... as my Dad says (don't ask me why)
<metaperl> what command exists the ocaml shell?
<metaperl> when I type ocaml I get a shell... but I don't know how to return to the unix shell and leave the ocaml shell
<metaperl> besides killing the process
<pango> ^D (well, under Unix, at least), or #quit ;;
<metaperl> the Cygwin ocaml I built does not support dynamic loading... the Windows version does... so I run the Windows version under cygwin with my own exe
love-pingoo has joined #ocaml
arno_ has quit ["..."]
descender has quit [kornbluth.freenode.net irc.freenode.net]
Amorphous has quit [kornbluth.freenode.net irc.freenode.net]
mikeX has joined #ocaml
Amorphous has joined #ocaml
descender has joined #ocaml
metaperl has quit ["KVIrc 3.2.1 Anomalies http://www.kvirc.net/"]
zmdkrbou has quit ["Lost terminal"]
dark_light has joined #ocaml
metaperl has joined #ocaml
avlondono has joined #ocaml
Amorphous has quit ["arg... must... shutdown... computer burnin..."]
Amorphous has joined #ocaml
pattern has quit [Read error: 148 (No route to host)]
pattern has joined #ocaml
smimou has quit ["bli"]
<metaperl> Jo O
<metaperl> Hi I'm trying to catch an exception but getting a syntax error when trying to do so. Any help is appreciated: http://ocaml.metaperl.com/ora-book/lextree.ml
<ketty> metaperl: preblem is.. false if [...]
<ketty> it makes no sence :)
<metaperl> ah, so how do we fix that?
<ketty> you could do: ignore (false); if [...]
<metaperl> yes, I see the try ... with is melding into the if after it
<ketty> but that makes even less sence :)
<metaperl> I dont understand that
<metaperl> Ihavent gotten to ignore
<ketty> ignore turns anything into unit
<metaperl> yeah , but this function is to return a bool
<metaperl> not unit
<ketty> yes..
<ketty> maybe move the if ... else part inside the try part?
<metaperl> oh yea, that kinda makes since
<ketty> :)
<metaperl> ok still have the same error: http://ocaml.metaperl.com/ora-book/lextree.ml
dvorak_ has quit ["Reconnecting"]
dvorak has joined #ocaml
<ketty> :)
<ketty> the syntax is: let [declaration] in [expression]
<dylan> put a semi-colon after dic
zmdkrbou has joined #ocaml
<metaperl> I know I have an issue with the let but am not sure how to fix it... maybe by adding an "in"
<dylan> or, 'in', actually