mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.0 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
leoni has joined #ocaml
leoni has quit ["Leaving"]
danly has quit [Remote closed the connection]
pango has quit [Remote closed the connection]
pango has joined #ocaml
qwwqe has joined #ocaml
pantsd has joined #ocaml
Smerdy has joined #ocaml
Smerdy has quit [Read error: 104 (Connection reset by peer)]
pango has quit [Remote closed the connection]
pango has joined #ocaml
buluca has quit [Read error: 113 (No route to host)]
screwt8 has quit [Remote closed the connection]
screwt8 has joined #ocaml
slipstream-- has joined #ocaml
slipstream has quit [Read error: 110 (Connection timed out)]
joshcryer has quit [anthony.freenode.net irc.freenode.net]
jlouis has quit [anthony.freenode.net irc.freenode.net]
etnt has joined #ocaml
screwt852 has joined #ocaml
jlouis has joined #ocaml
barnydan has joined #ocaml
<barnydan> ooooo!
<barnydan> o0O0O0Ooo!
<barnydan> o0Oo0ooO0oOoo!
<barnydan> wo0Oo0ooO0oOooT!
screwt852 has left #ocaml []
barnydan is now known as shmoo
shmoo is now known as barnydan
screwt8 has quit [Read error: 104 (Connection reset by peer)]
joshcryer has joined #ocaml
etnt has quit [Remote closed the connection]
etnt has joined #ocaml
buluca has joined #ocaml
barnydan has left #ocaml []
etnt has quit [Remote closed the connection]
etnt has joined #ocaml
kosmikus_ has joined #ocaml
kosmikus has quit [Read error: 104 (Connection reset by peer)]
kosmikus_ is now known as kosmikus
screwt8 has joined #ocaml
vorago has joined #ocaml
kelaouchi has joined #ocaml
xavierbot has joined #ocaml
ygrek_ has joined #ocaml
smimou has joined #ocaml
noteventime has joined #ocaml
smimou has quit ["bli"]
Nutssh has quit ["Client exiting"]
<bluestorm> have you looked at the Deriving thing ?
<bluestorm> from my novice point of view, it seems interesting
xavierbot has quit [Remote closed the connection]
xavierbot has joined #ocaml
<rwmjones> bluestorm, what is that?
<rwmjones> f ();;
<xavierbot> Characters 0-1:
<xavierbot> f ();;
<xavierbot> ^
<xavierbot> Unbound value f
* rwmjones got about 10% of the way through that oleg email
screwt8 has quit [Read error: 104 (Connection reset by peer)]
love-pingoo has joined #ocaml
cap has joined #ocaml
screwt8 has joined #ocaml
leo037 has joined #ocaml
_ke has joined #ocaml
<_ke> hi there
cap` has joined #ocaml
<_ke> is it possible to create an own type, where a certain element (e.g. int) is set to a certain value (e.g. = 0)?
cap` has quit [Remote closed the connection]
<rwmjones> _ke, not in basic OCaml, but there are camlp4 extensions, or other ways to do it
<rwmjones> for example, you can hide the type behind a signature to stop callers from making values directly (but only through your functions which ensure the invariants you want)
<_ke> ok
<_ke> no i will stay with ocaml, thanks
<rwmjones> _ke, something like this ...
<_ke> rwmjones, if i use a list, is there a simple to way to iterate through that list and set that int?
<rwmjones> module Test : sig type t val make_t : unit -> t val inc_t : t -> t val print_t end = struct type t = int let make_t = 0 let inc_t t = t+1 let print_t t = print_endline (string_of_int t) end ;;
<xavierbot> Characters 72-79:
<xavierbot> Parse error: [a_LIDENT] expected after [value_val] (in [sig_item])
<xavierbot> module Test : sig type t val make_t : unit -> t val inc_t : t -> t val print_t end = struct type t = int let make_t = 0 let inc_t t = t+1 let print_t t = print_endline (string_of_int t) end ;;
<xavierbot> ^^^^^^^
<rwmjones> grrr
<rwmjones> module Test : sig type t val make_t : unit -> t val inc_t : t -> t val print_t : t -> unit end = struct type t = int let make_t = 0 let inc_t t = t+1 let print_t t = print_endline (string_of_int t) end ;;
<xavierbot> Characters 98-202:
<xavierbot> module Test : sig type t val make_t : unit -> t val inc_t : t -> t val print_t : t -> unit end = struct type t = int let make_t = 0 let inc_t t = t+1 let print_t t = print_endline (string_of_int t) end ;;
<xavierbot> ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
<xavierbot> Signature mismatch:
<xavierbot> Modules do not match:
<xavierbot> sig
<xavierbot> type t = int
<xavierbot> val make_t : int
<xavierbot> val inc_t : int -> int
<xavierbot> val print_t : int -> unit
<rwmjones> module Test : sig type t val make_t : unit -> t val inc_t : t -> t val print_t : t -> unit end = struct type t = int let make_t () = 0 let inc_t t = t+1 let print_t t = print_endline (string_of_int t) end ;;
<xavierbot> module Test :
<xavierbot> sig
<xavierbot> type t
<xavierbot> val make_t : unit -> t
<xavierbot> val inc_t : t -> t
<xavierbot> val print_t : t -> unit
<xavierbot> end
<_ke> hehe
<rwmjones> let t = Test.make_t ();;
<xavierbot> val t : Test.t = <abstr>
<rwmjones> Test.print_t t ;;
<xavierbot> 0
<xavierbot> - : unit = ()
<rwmjones> let t = Test.inc_t t ;;
<xavierbot> val t : Test.t = <abstr>
<rwmjones> let t = Test.inc_t t ;;
<xavierbot> val t : Test.t = <abstr>
<rwmjones> Test.print_t t ;;
<xavierbot> 2
<xavierbot> - : unit = ()
<rwmjones> so that's an example of a constrained type - it's an integer, but callers can't mess with it, they can only do limited stuff
<_ke> i understand
<_ke> but i think thats too complicated for that i want to do
fmadero has left #ocaml []
<rwmjones> _ke, so camlp4 is not possible?
<_ke> rwmjones, no, it has to be ocaml only
<rwmjones> there is something called "private rows" which I've not used
cap has quit ["ERC Version 5.2 (IRC client for Emacs)"]
<rwmjones> _ke, right at the bottom of this page http://caml.inria.fr/pub/docs/manual-ocaml/manual021.html
<_ke> rwmjones, i think i will let that int, as the function i have to write will overwrite it
<rwmjones> another way is to define a "default value" for the type, and then let users use it
<rwmjones> like this:
<rwmjones> type t = { m1 : int; m2 : string };;
<xavierbot> type t = { m1 : int; m2 : string; }
<rwmjones> let default_t = { m1 = 0; m2 = "" } ;;
<xavierbot> val default_t : t = {m1 = 0; m2 = ""}
<rwmjones> and then people can form new types by doing:
<rwmjones> sorry, new values by doing:
<rwmjones> { default_t with m2 = "only the string is modified" };;
<xavierbot> - : t = {m1 = 0; m2 = "only the string is modified"}
<rwmjones> of course, this isn't safe - people can still construct types directly
<_ke> ok
<_ke> rwmjones, what about iterating through list? i couldnt find something about that on google
<_ke> (ehm i mean, i couldnt find something which i understand on google) ;)
<rwmjones> _ke, iterating through a list? You mean, List.iter etc.?
<rwmjones> List.iter print_endline [ "a"; "b"; "c" ];;
<xavierbot> a
<xavierbot> b
<xavierbot> c
<xavierbot> - : unit = ()
<_ke> rwmjones, type presentation = Chart of folie list * int;;
<xavierbot> Characters 1-9:
<xavierbot> rwmjones, type presentation = Chart of folie list * int;;
<xavierbot> ^^^^^^^^
<xavierbot> Unbound value rwmjones
<rwmjones> type presentation = Chart of folie list * int;;
<_ke> rwmjones, now i want to set all int of that type
<xavierbot> Characters 1-5:
<xavierbot> Parse error: [type_declaration] expected after "type" (in [str_item])
<xavierbot> type presentation = Chart of folie list * int;;
<xavierbot> ^^^^
<_ke> folie is defined above
<rwmjones> it doesn't know what 'folie' is
<_ke> a folie contains some strings
<rwmjones> _ke, not sure I understand the question
<_ke> ok again ;)
<_ke> i have that type presentation. a presentation contains several "sheets" and each sheet several strings
<_ke> now, each sheet has a number
<_ke> i want to write a function, which goes through all sheets and enumerates it
<rwmjones> so, in concrete terms then:
<rwmjones> type folie = string * string ;;
<xavierbot> type folie = string * string
<rwmjones> type presentation = Chart of folie list * int;;
<xavierbot> type presentation = Chart of folie list * int
<rwmjones> open Printf;;
<rwmjones> let iterate_over_sheets (Chart (sheets, _)) = List.iter (fun (str1, str2) -> printf "str1 = %s, str2 = %s\n") sheets ;;
<xavierbot> Characters 85-109:
<xavierbot> let iterate_over_sheets (Chart (sheets, _)) = List.iter (fun (str1, str2) -> printf "str1 = %s, str2 = %s\n") sheets ;;
<xavierbot> ^^^^^^^^^^^^^^^^^^^^^^^^
<xavierbot> This expression has type string -> string -> unit but is here used with type
<xavierbot> unit
<rwmjones> let iterate_over_sheets (Chart (sheets, _)) = List.iter (fun (str1, str2) -> printf "str1 = %s, str2 = %s\n" str1 str2) sheets ;;
<xavierbot> val iterate_over_sheets : presentation -> unit = <fun>
<rwmjones> let presentation = let sheets = [ "a", "b"; "c", "d" ] in Chart (sheets, 0);;
<xavierbot> val presentation : presentation = Chart ([("a", "b"); ("c", "d")], 0)
<_ke> ah the List.iter does all the work for me?
<rwmjones> iterate_over_sheets presentation;;
<xavierbot> str1 = a, str2 = b
<xavierbot> str1 = c, str2 = d
<xavierbot> - : unit = ()
<rwmjones> well, List.iter iterates over a list
<_ke> cool
<_ke> do i have access to the iterator?
<_ke> i mean something like this:
<rwmjones> you mean the number?
<_ke> for (int i=0; i < presentation.length; i++)
gene9 has joined #ocaml
<_ke> chart.number = i
<_ke> end
<rwmjones> well, if you use Extlib, then there is a List.iteri function which gives you the iterator
<rwmjones> in the stdlib, there is only Array.iteri, so a nasty hack is to do:
<rwmjones> let iterate_over_sheets (Chart (sheets, _)) = Array.iteri (fun i (str1, str2) -> printf "i = %d, str1 = %s, str2 = %s\n" i str1 str2) (Array.of_list sheets) ;;
<xavierbot> val iterate_over_sheets : presentation -> unit = <fun>
<rwmjones> iterate_over_sheets presentation;;
<xavierbot> i = 0, str1 = a, str2 = b
<xavierbot> i = 1, str1 = c, str2 = d
<xavierbot> - : unit = ()
<rwmjones> I'm using Array.of_list to convert the list into an array, so I can then use Array.iteri on it.
<rwmjones> better to use extlib if possible
<_ke> and to have an own counter?
<_ke> something like the "i" in the program-code above?
<rwmjones> I'm not sure what you mean
<_ke> i will explain it in pseudo-code:
<_ke> counter = 0
<_ke> for (presentation.first to presentation.last)
<_ke> presentation.sheet.int = counter
<_ke> counter++
<_ke> end
<rwmjones> Array.iteri / Extlib's List.iteri gives you a counter - see the most recent definition of iterate_over_sheets above
ygrek__ has joined #ocaml
<rwmjones> you could also maintain an counter outside the loop, but once you start doing that you're not really programming functionally
<_ke> hmm
<_ke> well i need a function which numbers all my sheets of a presentation. what would you do?
<rwmjones> I'd use Array.iteri or List.iteri !
<_ke> ok thanks
visage has joined #ocaml
ygrek_ has quit [Remote closed the connection]
gunark has joined #ocaml
li` has joined #ocaml
gene9 has quit ["Leaving"]
buluca has quit ["Leaving."]
<li`> let hello () = print_endline "hello, world";;
<xavierbot> val hello : unit -> unit = <fun>
<li`> hello ();;
<xavierbot> hello, world
<xavierbot> - : unit = ()
<Smerdyakov> print_endline "My nick probably makes a certain project leader mildly uncomfortable.";;
<xavierbot> My nick probably makes a certain project leader mildly uncomfortable.
<xavierbot> - : unit = ()
<li`> #list;;
<li`> #quit;;
<li`> 3;;
<xavierbot> - : int = 3
<rwmjones> xavierbot, restart yourself
<li`> Unix.getpid;;
<xavierbot> Characters 1-12:
<xavierbot> Unix.getpid;;
<xavierbot> ^^^^^^^^^^^
<xavierbot> Unbound value Unix.getpid
<li`> #load "unix.cma";;
<li`> Obj.repr;;
<xavierbot> Characters 1-9:
<xavierbot> Obj.repr;;
<xavierbot> ^^^^^^^^
<xavierbot> Unbound value Obj.repr
<leo037> exit;;
<xavierbot> - : unit = ()
<leo037> exit 0;;
<xavierbot> Characters 1-5:
<xavierbot> exit 0;;
<xavierbot> ^^^^
<xavierbot> This expression is not a function, it cannot be applied
<li`> Filename.temp_dir_name;;
<xavierbot> Characters 1-23:
<xavierbot> Filename.temp_dir_name;;
<xavierbot> ^^^^^^^^^^^^^^^^^^^^^^
<xavierbot> Unbound value Filename.temp_dir_name
<leo037> let rec t = print_endline "a"; t ;;
<xavierbot> Characters 27-33:
<xavierbot> let rec t = print_endline "a"; t ;;
<xavierbot> ^^^^^^
<xavierbot> This kind of expression is not allowed as right-hand side of `let rec'
* Smerdyakov humbly suggests that testing REPL bots is not a good use of channel bandwidth.
<leo037> let rec t a = print_endline "a"; t a ;;
<xavierbot> val t : 'a -> 'b = <fun>
<leo037> t 1;;
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<xavierbot> a
<Smerdyakov> And THAT definitely isn't..
<li`> xavierbot help
<xavierbot> hello li`, I am xavierbot 0.6, an OCaml toplevel
<xavierbot> expr ;; evaluate expr in toplevel and print result
<xavierbot> help help message
<xavierbot> restart restart the toplevel
<xavierbot> sleep go to sleep
<xavierbot> wake wake me up from sleep
<leo037> li`: good !
<rwmjones> the restart command is borked at the moment
<leo037> what is the problem with channel bandwidth ?
<leo037> xavierbot: restart
<Smerdyakov> Blocking regular conversation is no good.
xavierbot has quit [Remote closed the connection]
<rwmjones> that might fix it
<leo037> Smerdyakov: I didn't saw one here
xavierbot has joined #ocaml
<Smerdyakov> It would be easy to miss a new question amidst the flurry of a...a....a....
<rwmjones> xavierbot, restart yourself
<xavierbot> Objective Caml version 3.10.0
<xavierbot> Camlp4 Parsing version 3.10.0
<li`> query doesn't work with xavierbot ?
<rwmjones> ?
<li`> I mean msg or query, to chat secretly
<Smerdyakov> Why don't you chat secretly with your own 'ocaml'?
<rwmjones> no ... mainly because I didn't bother to read the instructions to POE::Component::IRC very closely
<rwmjones> just enough to get it working
<rwmjones> please contribute patches though :-)
li` has left #ocaml []
pango has quit [Remote closed the connection]
<oracle1> if you are doing floating point calculations, how can you get a "nan" ?
<rwmjones> isn't it built in to Pervasives?
<rwmjones> nan;;
<xavierbot> - : float = nan
<rwmjones> or you want a calculation that returns nan?
<rwmjones> 0./.0.;;
<xavierbot> - : float = nan
<oracle1> yes, i just wonder what causes in calculations end up in nan
<oracle1> hm
<rwmjones> 0/0;;
<xavierbot> Exception: Division_by_zero.
<oracle1> only division?
<rwmjones> NaNs get passed through a calculation
<rwmjones> I don't think there's anything particularly special to OCaml
pango has joined #ocaml
<oracle1> ok interesting
<oracle1> thx
descender has quit ["Elegance has the disadvantage that hard work is needed to achieve it and a good education to appreciate it. - E. W. Dijkstra"]
leo037 has quit ["Leaving"]
love-pingoo has quit ["Connection reset by pear"]
<_ke> is there a easy way to find the same entries in a list? e.g. if i have "a", "b", "c", "a", i want to find the second "a"
<rwmjones> _ke, and what do you want to do with it? just return its position in the list? return the duplicated element? what if there is more than one duplicate?
<rwmjones> or no duplicates?
<_ke> rwmjones, i have a list of tuples, e.g. "a" and 1, "b" and 1, "c" and 2, "a" and 2. now i want to finde the same strings, and put the number behind it togheter. in that example i want to get "a" and 1,2, "b" and 1, "c" and 2
etnt has quit ["bye"]
<rwmjones> it sounds like you want the "group_by" function
<rwmjones> let me just find it for you ...
<rwmjones> let group_by ?(cmp = Pervasives.compare) ls =
<rwmjones> let ls' =
<rwmjones> List.fold_left
<rwmjones> (fun acc (day1, x1) ->
<rwmjones> match acc with
<rwmjones> [] -> [day1, [x1]]
<rwmjones> | (day2, ls2) :: acctl ->
<_ke> thanks a lot
<rwmjones> if cmp day1 day2 = 0
<rwmjones> then (day1, x1 :: ls2) :: acctl
<rwmjones> else (day1, [x1]) :: acc)
<rwmjones> []
<rwmjones> ls
<rwmjones> in
<rwmjones> let ls' = List.rev ls' in
<rwmjones> List.map (fun (x, xs) -> x, List.rev xs) ls'
<rwmjones> let group_by ?(cmp = Pervasives.compare) ls = let ls' = List.fold_left (fun acc (day1, x1) -> match acc with [] -> [day1, [x1]] | (day2, ls2) :: acctl -> if cmp day1 day2 = 0 then (day1, x1 :: ls2) :: acctl else (day1, [x1]) :: acc) [] ls in let ls' = List.rev ls' in List.map (fun (x, xs) -> x, List.rev xs) ls' ;;
<xavierbot> Characters 22-40:
<xavierbot> let group_by ?(cmp = Pervasives.compare) ls = let ls' = List.fold_left (fun acc (day1, x1) -> match acc with [] -> [day1, [x1]] | (day2, ls2) :: acctl -> if cmp day1 day2 = 0 then (day1, x1 :: ls2) :: acctl else (day1, [x1]) :: acc) [] ls in let ls' = List.rev ls' in List.map (fun (x, xs) -> x, List.rev xs) ls' ;;
<xavierbot> ^^^^^^^^^^^^^^^^^^
<xavierbot> Unbound value Pervasives.compare
<rwmjones> grrr!!!
<rwmjones> let group_by ?(cmp = compare) ls = let ls' = List.fold_left (fun acc (day1, x1) -> match acc with [] -> [day1, [x1]] | (day2, ls2) :: acctl -> if cmp day1 day2 = 0 then (day1, x1 :: ls2) :: acctl else (day1, [x1]) :: acc) [] ls in let ls' = List.rev ls' in List.map (fun (x, xs) -> x, List.rev xs) ls' ;;
<xavierbot> val group_by :
<xavierbot> ?cmp:('a -> 'a -> int) -> ('a * 'b) list -> ('a * 'b list) list = <fun>
<rwmjones> group_by ["a",1; "b",1; "c",2; "a",2] ;;
<xavierbot> - : (string * int list) list =
<xavierbot> [("a", [1]); ("b", [1]); ("c", [2]); ("a", [2])]
<rwmjones> no, that's not right
<rwmjones> group_by (List.sort compare ["a",1; "b",1; "c",2; "a",2]) ;;
<xavierbot> - : (string * int list) list = [("a", [1; 2]); ("b", [1]); ("c", [2])]
<rwmjones> yup, that group_by only works if the list is sorted first
<_ke> its not ;)
<rwmjones> well, sort it then!
<rwmjones> you could do it imperatively, using an intermediate Hashtbl, if you didn't want to sort it
smimou has joined #ocaml
<_ke> rwmjones, could you tell me more about that Hashtbl-method?
<rwmjones> well, the general plan would be to create a Hashtbl (Hashtbl.create), then go over the list adding each (key, value) pair into the hashtable.
<rwmjones> Note that OCaml Hashtbl allows multiple values for a single key, which is why this would work.
<rwmjones> Then when you've gone over the list, using Hashtbl.fold to pull out the keys.
<rwmjones> Then for each key, get all the values.
<rwmjones> and construct a list from that (key, list-of-values)
marc has quit [Read error: 113 (No route to host)]
marc has joined #ocaml
_ke has quit ["umount /mnt/me"]
pango has quit [Remote closed the connection]
pango has joined #ocaml
edwardk has joined #ocaml
love-pingoo has joined #ocaml
buluca has joined #ocaml
marc has quit [Nick collision from services.]
marc___ has joined #ocaml
Len1 has joined #ocaml
rwmjones has quit ["Closed connection"]
rwmjones has joined #ocaml
buluca has quit [Read error: 110 (Connection timed out)]
<TFK> Excuse me for the noobish question, but with what Linux distributions I can get OCaml running in the most painless fashion? Will Ubuntu do?
<Smerdyakov> I've only ever tried Debian, but it's totally painless there.
pantsd has quit [Read error: 110 (Connection timed out)]
visage has quit []
descender has joined #ocaml
<rwmjones> TFK, I'm afraid to say that at the moment it's Debian, who have great support
<rwmjones> but I'm trying to get Fedora to have an equal level of support
<TFK> And other distros?
<rwmjones> and if you like you can get my packages (which work on FC6, F7 and F8) here:
<rwmjones> TFK, what Linux distro did you have in mind?
<rwmjones> it's a slow business, but hopefully Fedora will have excellent OCaml support in a few months
<TFK> Well, Ubuntu :-P that's because I've been brainwashed. But I suppose I can try Debian and Fedora as well.
<rwmjones> Ubuntu has ..... issues ....... although at the moment it does work
* rwmjones boots laptop, back in a second
rwmjones_ has joined #ocaml
rwmjones_ is now known as rwmjones_laptop
<rwmjones_laptop> did I miss anything?
* TFK shakes head
<TFK> What kind of issues does ubuntu have? I think I only need the debugger and profiler.
<rwmjones_laptop> the issues are (and this is highly my personal opinion btw):
<rwmjones_laptop> (1) upstream Debian don't like them much, and so won't deal with bug reports and other problems
pantsd has joined #ocaml
<rwmjones_laptop> (2) Ubuntu takes OCaml packages at random points, which can lead to inconsistencies
<rwmjones_laptop> (eg. in Ubuntu 6.06 there was originally a load of inconsistencies which meant you could compile programs which used libraries from different .debs at all)
<rwmjones_laptop> (3) Ubuntu is usually one release behind Debian
<rwmjones_laptop> however, if all you want is the basic OCaml package, then it will most likely work
<TFK> yup, that's what I want.
<Smerdyakov> In conclusion, if you want a usable Linux system, use Debian. :P
<TFK> And then maybe everything else the stdlib lacks :-P
<Smerdyakov> It just has waaaay more effort going into it than anything else.
<rwmjones_laptop> well go for it! did you try to grab & install the ocaml-native-compilers package/?
<TFK> Well, I don't even have Linux yet!
buluca has joined #ocaml
<rwmjones_laptop> this is true, Debian have an excellent team of something like 5-10 people working on OCaml
<TFK> How hard is it to port the profiler and debugger to Windows?
<Smerdyakov> rwmjones, and _that's_ for a (relatively) obscure package!
<rwmjones_laptop> however, Fedora will have great support!
<rwmjones_laptop> TFK, save yourself time and use Linux, it's considerably better than Windows in so many ways when it comes to serious development
<TFK> I don't want to start a flame war of any sort :-)
<TFK> But I still wonder about possibilities for portability.
<Smerdyakov> Regardless of what rwmjones hopes to achieve some day, I think we agree that Debian wins today.
<rwmjones_laptop> TFK, I actually have some direct experience there
<rwmjones_laptop> see:
<Smerdyakov> That is, Debian Linux wins over all OS/distro choices for developers.
* TFK crawls
<rwmjones_laptop> TFK, really use Debian, just use Windows as a fancy & expensive terminal server to connect to your Debian boxes
<TFK> rwmjones_laptop, ah, but this is OCaml code? Are the profiler and debugger also written in pure OCaml?
<rwmjones_laptop> that site above is a project that I conducted in 2003
<rwmjones_laptop> to build a cross-platform graphical simulation tool for a contract for the UK govt
<rwmjones_laptop> we developed it mainly on Linux, and it was deployed mainly on Windows & Solaris
<TFK> How did they like it?
<rwmjones_laptop> it was written in OCaml, Makefile, bash shell script, and NSIS (the Windows installer) script
<rwmjones_laptop> fine, but it was of course a very vertical application
<TFK> "vertical"?
<rwmjones_laptop> probably not suitable for a horizontal consumer market
<rwmjones_laptop> vertical ...
<TFK> I see. But what about the OCaml toolchain?
<rwmjones_laptop> well it all works on windows
<rwmjones_laptop> what's the problem?
pantsd has quit [Read error: 104 (Connection reset by peer)]
<TFK> Not the debugger or profiler, to the best of my knowledge.
<rwmjones_laptop> I've never tried to run them under Windows. I'd be surprised if at least the debugger didn't work. Anyway, seriously install Linux.
pantsd has joined #ocaml
<TFK> Ah, I'm not the first one to ask such a question.
<TFK> Well, if the MS Research guy didn't do it, I guess not much point in me trying, either ;-)
<rwmjones_laptop> xavierbot, hello
<rwmjones_laptop> xavierbot, help
<xavierbot> hello rwmjones_laptop, I am xavierbot 0.7, an OCaml toplevel
<xavierbot> expr ;; evaluate expr in toplevel and print result
<xavierbot> help help message
<xavierbot> restart restart the toplevel
<xavierbot> sleep go to sleep
<xavierbot> wake wake me up from sleep
* rwmjones_laptop would like to have multiline input for xavierbot ...
<rwmjones_laptop> let rec a () = b () and b () = a () in a () ;;
<xavierbot> Objective Caml version 3.10.0
<xavierbot> Camlp4 Parsing version 3.10.0
edwardk has left #ocaml []
Len1 has quit ["Leaving."]
marc___ has quit [Read error: 110 (Connection timed out)]
buluca has quit ["Leaving."]
buluca has joined #ocaml
pantsd has quit [Read error: 104 (Connection reset by peer)]
pantsd has joined #ocaml
love-pingoo has quit ["zzzou"]
visage has joined #ocaml
psnively has joined #ocaml
visage has quit []
pantsd has quit ["Leaving."]
buluca has quit [Remote closed the connection]
joshcryer has quit [Read error: 104 (Connection reset by peer)]
buluca has joined #ocaml
G_ has joined #ocaml
G has quit [Read error: 110 (Connection timed out)]
noteventime has quit ["Leaving"]
rwmjones_laptop has quit ["This computer has gone to sleep"]
joshcryer has joined #ocaml