<mikeX>
lack of builtin unicode support is a feature or a bug?
Lob-Sogular has joined #ocaml
<Lob-Sogular>
if I have: let f x = "boo" ^ x;; when I try to do: Printf.printf (f "hiss\n");; I get the following error: This expression has type string but is here used with type ('a, out_channel, unit) format = ('a, out_channel, unit, unit) format4 .... what am I doing wrong?
<zmdkrbou>
this is not the way of using printf
<mikeX>
Lob-Sogular: what exactly are you trying to accomplish?
<zmdkrbou>
you should write Printf.printf "%s hiss\n" "blabla"
<Lob-Sogular>
mikeX: I'd like to print out a string that's created by calling a function with another string
<zmdkrbou>
why don't you juste use print_string (f "hiss\n") ? :)
<mikeX>
you could do as zmdkrbou said, or Printf.printf "%s" (f "hish\n")
<mikeX>
or rather printf "%s\n" (f "hiss")
<Lob-Sogular>
zmdkrbou: because my example is simpler than what I'm actually doing, but I didn't want to type out everything (or paste it for that matter
<mikeX>
haha
<mikeX>
dammit, wrong window
<Lob-Sogular>
ah, yeah, I don't know why I didn't think of doing "%s\n" (f "hiss")
<mikeX>
Lob-Sogular: you can always use www.pastebin.be for long pastes
<zmdkrbou>
Lob-Sogular: because this is ugly and totally abnormal syntax :)
<zmdkrbou>
(in ML)
<Lob-Sogular>
mikeX: true
<Lob-Sogular>
zmdkrbou: I did only start reading about it yesterday :)
<zmdkrbou>
then look at the type with blabla format4 and then, get sick :)
<mikeX>
hehe
<mikeX>
what exactly is abnormal syntax zmdkrbou? (assuming the format expression was something more complicated than "%s\n")
<zmdkrbou>
the type of Printf.printf is string -> 'a -> 'b -> 'c -> ... -> string ..... (where 'a etc.depend on the string ...)
<mikeX>
I'm not sure I understand
<mikeX>
do you just mean that printf is abnormal?
<zmdkrbou>
you can write Printf.printf "%s %f" "bla" 0.3 or Printf.printf "%d %d %s %s" 2 3 "bli" "pouet"
<zmdkrbou>
i can't see how this thing can be correctly typed
<zmdkrbou>
i suppose there's a trick with the compiler
<mikeX>
well it's more convenient than print_string print_float print_int ...
<mikeX>
yes, there must be
<zmdkrbou>
yes, it's a convenient way to print but ... i would have found a bit less ugly to have a print keyword in the language (as in python as example)
<mikeX>
yeah, it has it's limitations
<zmdkrbou>
omg, i can't look at the printf.ml file :)
<mikeX>
hahaha
<mikeX>
I tried that once too
Skal has quit [Remote closed the connection]
<Lob-Sogular>
zmdkrbou: I take it you don't recommend using printf?
<zmdkrbou>
boarf ... i don't use much printf but i must admit it's really convenient when it comes to print complex stuff
<avlondono>
zmdkrbou: the thing is that the first element in that printf function is not a string
<avlondono>
not that I fully understand it...
<avlondono>
but it's not a string, it is a format type.
<zmdkrbou>
yes, the type is not string -> 'a -> etc.
<zmdkrbou>
but the format type is a joke :)
<avlondono>
what do you mean?
<mikeX>
Lob-Sogular: I find it ok, but not as flexible as one would expect
<Lob-Sogular>
mikeX: yeah... it seems to me that all I need right now is print_string, so I'll stick with that (I didn't know about it until you mentioned it)
<zmdkrbou>
Obj.magic << aah !
<zmdkrbou>
(from printf.ml)
<zmdkrbou>
avlondono: i mean the code in printf.ml uses this kind of Obj.magic tricks to get all this typed correctly
<avlondono>
I know, I was bothered some time ago because there is no way to convert an identifier from string to format.
<avlondono>
but the fact that the standard library uses tricks to achieve a type, doesn't mean that the type is a joke ...
<zmdkrbou>
jole wasn't the right word :)
<avlondono>
:-)
<zmdkrbou>
joke*
<avlondono>
jole neither ;-)
<zmdkrbou>
hehe
khaladan has quit [Read error: 104 (Connection reset by peer)]
julbouln has quit [Read error: 104 (Connection reset by peer)]
julbouln has joined #ocaml
teop has quit ["Leaving"]
mikeX has quit ["zzz"]
jcreigh has joined #ocaml
jcreigh has quit ["Do androids dream of electric sheep?"]
CHodapp has joined #ocaml
<CHodapp>
Why is C++ such a crock of shit?
* CHodapp
collapses
ketty has quit [Read error: 110 (Connection timed out)]
Smerdyakov has quit ["Leaving"]
<CHodapp>
WHY!!!!
* CHodapp
beats his head into the desk
revision17_ has quit ["Ex-Chat"]
<sieni>
CHodapp: c++ a crock of shit? try php?
<CHodapp>
When I have to write in PHP for a class, maybe then I'll address that
<CHodapp>
but GOD DAMN, I could write some of these programs faster in assembly and have fewer bugs...
<CHodapp>
I just wish for once one of these teachers could teach a language that actually has some elegance to its credit...
<sieni>
fortran iv?
* CHodapp
shrugs
<CHodapp>
it's not Object Oriented(tm) so it might not be that bad
Revision17 has quit [Read error: 110 (Connection timed out)]
Boojum has joined #ocaml
smimou has joined #ocaml
Snark has quit [Nick collision from services.]
Boojum is now known as Snark
Skal has joined #ocaml
slipstream-- has joined #ocaml
slipstream has quit [Read error: 110 (Connection timed out)]
Tachyon76 has quit ["Leaving"]
Lycurgus_ is now known as JKnecht
mikeX has joined #ocaml
love-pingoo has joined #ocaml
Snark has quit [Read error: 110 (Connection timed out)]
ski has quit [Read error: 104 (Connection reset by peer)]
ski has joined #ocaml
<flux__>
ARGH, I've been biten by the thread-unsafe interface of Str
<flux__>
actually it's probably an internal problem, not an interface problem
<flux__>
or how else would this line of code throw Invalid_argument("Str.group_end"): match Str.split_delim (Str.regexp " ") line with
<flux__>
(according to backtrace atleast)
<dylan>
it's an interface problem.
<flux__>
well, I guess with threaded code it is possible something modified the contents of line during the call, but Str.group_end suggests that Str.split_delim uses that function internall, and its non-safe
<flux__>
Str.split_delim could be implemented quite safely even with that interface
<dylan>
True.
permanente is now known as profmakx
<dylan>
what are you splitting on?
<flux__>
Str.split_delim (Str.regexp " ") line
<flux__>
I already have pcre linked in, though, so I might just as well and make that package depend on it too
<flux__>
although maybe I could just not use regexps at all in that case :)
<flux__>
I apparently only use single-character separators, so I might just as well and drop the dependency on Str..
<ktne>
It uses the wxc binding created by the wxEiffel team. wxHaskell is also using this binding.?
<ktne>
the horror..
<ktne>
:)
ktne has left #ocaml []
pango is now known as pangoafk
pangoafk is now known as pango
juhe has quit ["Leaving"]
edesarna has quit ["Connection reset by by pear"]
permanente has joined #ocaml
profmakx has quit [Read error: 110 (Connection timed out)]
permanente is now known as profmakx
khaladan has joined #ocaml
finelemon has joined #ocaml
finelemo1 has quit [Read error: 110 (Connection timed out)]
finelemon has quit [Read error: 110 (Connection timed out)]
finelemon has joined #ocaml
_JusSx_ has joined #ocaml
<_JusSx_>
i wonder why ocaml library sucks
<smimou>
?
<_JusSx_>
Standart ML is great.
<_JusSx_>
ocaml has been provided with an awful library
<_JusSx_>
i'm sorry, but they didn't learn anything from ML
<smimou>
what do you lack ?
<_JusSx_>
order, standarization
<smimou>
do you have a precise example of something wrong?
<_JusSx_>
OrderedType Module for example
<_JusSx_>
Map module
<_JusSx_>
Set Module
<_JusSx_>
Lack of Option Module
<smimou>
what's wrong with the mentionned modules?
<_JusSx_>
the lack of order
<smimou>
hum that's not very convincing
<_JusSx_>
try to compare Map ocaml module with that provided by sml
<_JusSx_>
ocaml doesn't provide option module
bourbaki has left #ocaml []
<_JusSx_>
but option type is a primitive
<smimou>
again I don't see your point
<_JusSx_>
ok first study sml standard library
<_JusSx_>
and you will see the difference
<flux__>
I personally don't have hard time believing there could be a better organized standard library than the one ocaml provides
<_JusSx_>
it seems ocaml was written years before sml
<_JusSx_>
lol
<_JusSx_>
flux__: LOL
<flux__>
atleast the order of arguments seems to vary between modules: for some the 'modules's type' is the first argument of the functions, for others it's the last
<flux__>
also as I mentioned, Str-module's seemingly thread-safe functions don't appear to be such :P
<flux__>
(and String + Str - what's up with that?)
<avlondono>
Caml was written before ML had some standardization iirc
<dylan>
'Str' should be 'Regexp', IMO.
<_JusSx_>
avlondono: sure a dialect was written before the language
<dylan>
also, there almost is a rhyme or reason to the order of arguments for modules.
<dylan>
Function ones seem to put the abstract data type last.
<dylan>
This is good for folding.
<dylan>
*Functional
<dylan>
Imperative ones put the abstract data first, as you often don't fold those things.
<flux__>
otoh it can make mapping more cumbersome?
<flux__>
actually I don't think I see why it makes folding simpler, do you have an example?
<dylan>
one second.
<flux__>
as currying was actually one thing I've always thought of to be the reason, but I really couldn't see it ;)
<flux__>
hm, construct a Map/Set by folding a list?
<dylan>
Yeah.
<flux__>
well
<dylan>
let run l x = List.fold_left (fun x f -> f x) x l
<dylan>
or, as ski said many moons ago:
<dylan>
"* ski_ guesses "add : 'key -> 'val -> t -> t" can be useful to partially apply to get "t -> t" .."
<flux__>
well, consider this: List.fold_left (fun set v -> S.add set v) S.empty [1; 2; 3];;
<flux__>
were the argument in different order, you wouldn't need to define a lousy function there ;)
<dylan>
also, it's more like list cons.
<dylan>
S.add x set is like x :: l
<flux__>
(or, written in other words: List.fold_left (flip S.add) S.empty)
<dylan>
But then it's not like list cons.
<dylan>
that run function is used like: let set = run [S.add "foo"; S.add "bar"; S.remove "pants"] set ;;
<flux__>
well, arguably they do follow the logic set by the List-module, but personally I can find more use to for example flip List.mem that List.mem when constructing horrible O(n^2) filters over data
<dylan>
List has that interface because it matches the defintion of lists and list cons.
<flux__>
how often do you actually use such lists of operations?-o
<dylan>
which is hd :: tail.
<dylan>
Never out side of test cases.
<dylan>
Yet, it seems there is a useful pattern in that.
<dylan>
Now, if you want to complain, Stack really doesn't much sense.
<flux__>
it doesn't even have fold
<dylan>
Stack is imperative, but has the order of Map.
<dylan>
same for Queue
<flux__>
too bad Set or Make (or Stack) don't provide a labeled variant, like ListLabels, which would render this problem nil ;)
<dylan>
It doesn't?
<flux__>
I can't see it?
<pango>
they do
<dylan>
I thought so.
<flux__>
a
<flux__>
ah, MoreLabels
<flux__>
great, so currying can continue with any order ;)
<flux__>
I guess there is some code breakage issues why the standard modules themselves aren't labeled
<dylan>
also there might be some optimization problems.
<flux__>
well, in the case when you don't use the native order maybe
<dylan>
btw, whoever pointed out my horrible String.sub string splitting code, thanks. I rewrote it to use blit.
<flux__>
I actually did that ;)
<dylan>
Ah, thanks.
<dylan>
It uses String.sub only for the last item.
<flux__>
how can you make use of .blit there?
<flux__>
my version created pairs or integers to point substrings and then mapped that with String.sub
<dylan>
make use of blit where?
<flux__>
"I rewrote it to use blit"
<flux__>
so your new splitting code uses String.blit?
<dylan>
yeah. It copies each left-hand-side, but not the right-hand-side.
<dylan>
Of course, if I really really cared about speed, I'd use rev_split or rewrite split to be imperative, but eh.
<flux__>
hmm.. how is String.make + String.blit better than String.sub?
<dylan>
I dunno. It seemed like the most straight-forward way.
<flux__>
:)
<dylan>
and before, it was string sub on two chunks
<dylan>
(using pair).
<dylan>
which is two memory copies.
<dylan>
this one uses only one memory copy.
<dylan>
(and that copy is needed anyway, to build the list)
<flux__>
let s' = String.sub s offset len in .. should replace the two lines, no?
<dylan>
hmm, true. but I wanted to make sure I understood blit, too. :)
<flux__>
anyway, the discussion here have me inspiration for my splitter, to first construct the list of offsets and then substrings, vaguely per your idea ;)
<flux__>
s/have/gave/
<dylan>
I wonder if that is more efficient.
<flux__>
I doubt it
<flux__>
but I maybe prefer it for clarity
<dylan>
probably requires two traversals.
<flux__>
not two traversals of the string per se, but one traversal of the string and one of the list, which is already quite short
<flux__>
(or could be long ;))
<flux__>
also if I want to filter empty substrings away, I can do it before the String.sub-stage.. which can give a marginal performance gain.
<dylan>
hmm
<dylan>
String.sub requires doing len - offset, I think.
<dylan>
d'oh, n/m
<flux__>
deforestation optimization could help with that kind of code, though
<dylan>
Just don't tell Captain Planet about it.
<dylan>
hmm, I bet a function like let catch_option f = try Some (f ()) with e -> None would be useful.
<dylan>
or even a type 'a option_exn = Result of 'a | Error of exn
<pango>
getting closer to lazy values...
<dylan>
hmm?
<dylan>
I can think of three interpretations of lazy values... :-/
<pango>
ocaml's Lazy.t can remember exceptions as well as values
<dylan>
with gcaml it might be possible to write this very nicely.
<flux__>
dylan, the latter is exceedingly nice when writing recursive functions that use exceptions
<dylan>
the latter?
<flux__>
option_exn
<dylan>
Oh.
<dylan>
yeah, exactly.
<dylan>
try ... with doesn't play nice with tail recursion, does it?
<flux__>
I call the function that returns those 'valuefy' ;)
<flux__>
nope
<pango>
SML functions seems to return option values more often (instead of raising exceptions). That means that only one kind of "exceptional case" can be handled, but that's fine for many functions
<dylan>
I use exceptions to implement the 'return' statement in my toy language.
CHodapp has quit ["Leaving"]
ski has quit [Read error: 110 (Connection timed out)]
ski has joined #ocaml
revision17_ has quit ["Ex-Chat"]
Revision17 has joined #ocaml
khaladan has quit [Read error: 110 (Connection timed out)]
Revision17 has quit ["Ex-Chat"]
|Lupin| has joined #ocaml
<|Lupin|>
Hello, there.
<|Lupin|>
I'm wondering how it is possibleTo interface OCaml with CGI.
<|Lupin|>
Is something available, and perhaps packaged for Debian ?
<pango>
ocamlnet ?
<|Lupin|>
ah this includes CGI facilities ?
<|Lupin|>
Didn't know.
<|Lupin|>
Know nothing about CGI, actually
bzzbzz has joined #ocaml
<|Lupin|>
But Gérard Huet made an impressive Demo of a library he developed and which has a web interface...
<pango>
plain CGI interface is very simple and rather slow
Revision17 has joined #ocaml
<pango>
that's why so many alternatives were invented (fastcgi, embedding interpreters in web server,...)
<pango>
don't know what ocamlnet implements exactly
<|Lupin|>
pango: ok, thanks anyway
<smimou>
|Lupin|: I think that cgi is quite dumb: you get the arguments in some way and print the result in stdout
ramkrsna has quit [Read error: 110 (Connection timed out)]
<|Lupin|>
smimou: I see. Which interface do yourecommend ?
<smimou>
never tried anyone in ocaml :(
<|Lupin|>
smimou: how many are there ? do you know ?
<smimou>
I guess it should be listed in the caml hump