Hadaka has quit [Read error: 60 (Operation timed out)]
Hadaka has joined #ocaml
<wolgo>
hi
rhar has quit ["This computer has gone to sleep"]
lasts has joined #ocaml
<bluestorm>
seems i just missed a big "jdh event"
lde has quit [Read error: 104 (Connection reset by peer)]
pango_ has quit [Remote closed the connection]
pango_ has joined #ocaml
twobitwork has quit [Read error: 104 (Connection reset by peer)]
asmanur has quit [Read error: 110 (Connection timed out)]
twobitwork has joined #ocaml
<wolgo>
So a global expression in Ocaml is just a let binding defined in a non-nested context?
<bluestorm>
yes
<bluestorm>
we tend to say "at top level"
<wolgo>
Oh okay.
<wolgo>
I will use that then.
<bluestorm>
(it is actually more subtle as it is a module structure item, as there is an implicit enclosing module, but if you're beginning, never mind)
<wolgo>
I am beginning.
<wolgo>
low programming experience too
<bluestorm>
hm
<bluestorm>
i'm not sure what you mean by now, but from your use of "global expression" and "nested context", i would say you have a bit of experience already
<bluestorm>
s/now/low/
<wolgo>
I mean little.
<wolgo>
when I say low
<wolgo>
I have read some books.
<wolgo>
Well, I have read a shitload of programming books. I am not sure why I have chosen to never stick to and write programs in a specific language though.
<bluestorm>
(that was a polite way to say : bullshit, you're using non-trivial terms the good way, i know you've been hiding a Java/C/Python/whatever book somewhere all that long, you nasty boy)
<wolgo>
I am serious.
<wolgo>
I am not lying. I have read a lot of programming books.
<bluestorm>
OCaml is probably a good language for trying differents things (and this is #ocaml, so free ocaml advertising for all)
<wolgo>
Yeah I like it.
<wolgo>
There are some items that are a bit confusing but I enjoy them.
<wolgo>
Does everyone here work professional with ocaml?
<bluestorm>
yeah, some people at jane street mostly
<mbishop>
I don't
<wolgo>
Oh
<wolgo>
I wonder if they to arbitrage trading or wtf ever that is called.
jeddhaberstro has quit []
jeddhaberstro has joined #ocaml
bluestorm has quit [Remote closed the connection]
<jeddhaberstro>
walgo, you there?
<wolgo>
yes
<wolgo>
I am now
<wolgo>
When is it appropriate to use ;. I have examples of when to not use it
<wolgo>
I can look at the stdlib
<jeddhaberstro>
Usually you use it when you're doing imperative programming in OCaml and need consecutive expressions.
<jeddhaberstro>
where the each expression changes state (memory)
<jeddhaberstro>
like I/O
<wolgo>
like assigning a new value to a reference variable?
<mbishop>
yes
<wolgo>
Oh okay
<wolgo>
but never after a let binding
<wolgo>
I tried to search pervasives.mli for ; but just got a bunch of ; in sentences
<wolgo>
I see.
<mbishop>
Where is the proper (system-wide) place to put some ocaml code so that ocaml knows where it is?
<wolgo>
I have another question -> I just read http://tech.groups.yahoo.com/group/ocaml_beginners/message/9843, and they give a several line explanation on how to return a unit after displaying a greeting (I barely know wtf that is). I did this: let greetings name = print_string "Greetings" ; print_string (((^) " ") name);; is my version is the proper way to do this?
<wolgo>
barely know what a unit is, not a greeting. Sorry for my grammar.
<wolgo>
mine is better, it displays how I am able to curry a function
<wolgo>
that is better for me
<jeddhaberstro>
let greetings name = print_string ("Greetings" ^ name ^ "\n");;
<jeddhaberstro>
should work
<jeddhaberstro>
oops, add a space after Greetings and then it works ;)
<wolgo>
right, I want to use the features of the language though like currying
<jeddhaberstro>
Why?
<wolgo>
man I do not know wtf I am doing haha
<wolgo>
So I understand it better
<jeddhaberstro>
Makes no sense to complicate a simple concept
<jeddhaberstro>
Find a better reason then printing strings to use currying :P
<wolgo>
You are right but it allowed me to use somethinig simple and illustrate something that was bending my brain
<wolgo>
Haha okay.
<jeddhaberstro>
k, lol
<wolgo>
I am mildly retarded if you haven't noticed
<wolgo>
This is curried let sum_list = List.fold_left ( + ) 0
<jeddhaberstro>
currying is usually very helpful when combined with higher order functions and general abstraction (which is the point of functional programming really...)
<wolgo>
See, they try to sneak these things under the radar
<jeddhaberstro>
yep
<wolgo>
What is a HOF?
<jeddhaberstro>
a function that takes a function as a parameter
<wolgo>
Oh okay
<jeddhaberstro>
I think it's also a function that returns a function as it's value
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
rwmjones_ has joined #ocaml
Yoric[DT] has joined #ocaml
Asmadeus has joined #ocaml
filp has joined #ocaml
filp has quit [Client Quit]
mishok13 has joined #ocaml
mishok13 has quit [Read error: 54 (Connection reset by peer)]
mishok13 has joined #ocaml
bluestorm has joined #ocaml
<MelanomaSky>
Question -- Is there a way I can share a single ocamllex file with two different parsers? (eg two different ocamlyacc files)?
<MelanomaSky>
I see in the tutorials that one usually does an "open ParseModule" in the header section of the ocamllex file.
<MelanomaSky>
But this doesn't play nicely if I want to use the same ocamllex file across more than one parser.
lde has joined #ocaml
bluestorm has quit [Remote closed the connection]
<mfp>
wolgo: there's a theoretically unexciting, but very convenient in practice way to do formatted printing, unique (?) to OCaml. Ask the top-level for the type of this expression: Printf.printf "Greetings %s.\n". Now try with another format string... (you said you've read many books so you doubtlessly know printf already, but OCaml's got a twist.)
seafood_ has joined #ocaml
<Yoric[DT]>
Yeah, actually, OCaml printf is quite nice.
seafood has quit [Read error: 104 (Connection reset by peer)]
<Yoric[DT]>
Now, if it only were possible to extend it easily (say, with either overloading or through Camlp4).
seafood_ has quit []
seafood has joined #ocaml
bluestorm has joined #ocaml
seafood has quit [Client Quit]
filp has joined #ocaml
filp has quit [Client Quit]
seafood has joined #ocaml
rwmjones_ has quit ["Closed connection"]
seafood has quit [Client Quit]
<flux>
I'm not sure if extending printf would be a great idea, if you mean extending the format string. wouldn't it lead to code that's more difficult to understand, even if you already understood printf and its format strings?
<flux>
at present you can sortof-extend it with printf "%t .. " (print_asdf foo)
<flux>
although I don't think you can pass format qualifiers that way
lde has left #ocaml []
Yoric[DT] has quit ["Ex-Chat"]
asmanur has joined #ocaml
lde has joined #ocaml
lde has quit [Remote closed the connection]
lde has joined #ocaml
<vixey>
mfp: C and C++ do this too I think
munga_ has joined #ocaml
Mr_Awesome has quit [Remote closed the connection]
asmanur has quit [Read error: 110 (Connection timed out)]
<mfp>
vixey: it's not type-safe. At most, you get a warning. With gcc, no complains about printf("%d\n", 54.34); unless given -Wall.
<mfp>
type-safety is what distinguishes OCaml's printf
Mr_Awesome has joined #ocaml
asmanur has joined #ocaml
mishok13 has quit [Read error: 104 (Connection reset by peer)]
mishok13 has joined #ocaml
<flux>
well, but gcc sort of can do it too, as you said
<flux>
what really distinguishes ocaml's printf from others is that it can check let c = format_of_string "%d" in printf c 42 in compile time
<flux>
but I'm not sure how useful that is :)
<mfp>
and this let prendline fmt = Printf.printf (fmt ^^ "\n")
<flux>
yeah, I suppose that's already more useful
<mfp>
what about this:
<mfp>
let scan_timestamped fmt s = Scanf.sscanf s ("[%d-%d-%d %d:%d] " ^^ fmt)
<mfp>
# scan_timestamped "%s" "[2008-08-13 12:47] sdfsfd" (fun y m d hh mm s -> Printf.printf "You said %s at %d:%d\n" s hh mm);;
<mfp>
You said sdfsfd at 12:47
<mfp>
- : unit = ()
<flux>
btw, I never realized why scanf works that we until reading mlton.org/Printf and associated white paper
<flux>
but I suppose you might already be familiar with that
<flux>
(I found the white paper easier to follow)
<mfp>
Danvy's and others?
<flux>
yes
<flux>
"Functional Unparsing"
<mfp>
that's a classic
<mfp>
there's a related functional pearl > "Do we need dependent types"
seafood has joined #ocaml
<Asmadeus>
BTW, since you're trying stuff on the toplevel, would you be interested in having a xavierbot here ? It ignores anything that doesn't end by ';;' so shouldn't be too much of a bother; only takes single-line of code though, but that'd work for your scantimestamped example
<flux>
I think xavierbot is ok, I believe it's been more a matter of someone bothering to run in rather than it not being allowed :)
<flux>
I do believe the bot originated on this channel
<mfp>
I've never seen anybody object to xavierbot here; there's not that much traffic anyway
<Asmadeus>
Well, I'm more asking if it interests you than if it bothers :P
<vixey>
Are you able to run it ?
<Asmadeus>
I don't mind running it, I'd just like to know if it'd be useful
<flux>
someone(TM) should add persistent storage facilities to it ;)
<flux>
I think it could be useful, perhaps even missed at times
xavierbot has joined #ocaml
<mfp>
:-)
<Asmadeus>
I'll have it set up on a permanent shell later, I just had the thing up from a few months ago
<Asmadeus>
and flux, what do you mean by persistent storage ? mean it should retains the defined functions ?
<mfp>
how hard would it be to add a tell "somebody" "message" extension?
<vixey>
let meaning = 42;;
<xavierbot>
val meaning : int = 42
<vixey>
meaning;;
<xavierbot>
- : int = 42
<mfp>
(privmsg to somebody when (s)he comes back)
<Asmadeus>
Ah
<flux>
asmadeus, yes, retaining information over restarts
<flux>
it could be used as a simple faq storage bot seen on many channels
<Asmadeus>
mfp: I've written a bot in ocaml recently, and although that one's in perl I don't think it'd be too hard
<flux>
not functions per se, though. and it might even need priviledges etc complicated stuff.
<Asmadeus>
What flux said sohuldn't be too hard if you store the lines and reexec them
<mfp>
That (tell) would be quite useful. Somebody asked for help with his C++ bindings and I saw a couple problems with his code, but I missed him for 3 days in a row.
<Asmadeus>
the perl script isn't complicated; most of xavierbot's work was to make the toplevel secure, so I can probably add it to my own bot and make that (tell) function too. It's quite interesting
aeolist has joined #ocaml
<aeolist>
hello everyone... i has a question...
<aeolist>
ocaml is supposed to not have any operator overloading right?
<aeolist>
for example * is strictly for ints and .* for floats
<aeolist>
however
<aeolist>
= can operate both on ints and strings.... how so?
<Asmadeus>
= is a bit special; it also is used with lets and lots of other things
<mfp>
(=) is a polymorphic function provided by the system
<aeolist>
then my issue is understanding overloading vs polymorphism ?
<vixey>
I don't think you have any issue
<mfp>
you've got it right already; (=) works thanks to parametric polymorphism, and there's no ad-hoc polymorphism (overloading)
<aeolist>
oh cool :) thanks
<Asmadeus>
Aww. xavierbot requires ocaml >= 3.10.0 to run, and I don't have control on that box's softwares (the one I planned to have xavierbot running in), they only have debian's package which is 3.09.2
<Asmadeus>
(it's required for camlp4-safety-things, can't ignore it really :/)
<mfp>
Asmadeus: I'll try to backport it to 3.09's camlp4
<Asmadeus>
thanks
<Asmadeus>
I've got your "tell" command ready though, using an hashtable and looking at join messages
<Asmadeus>
it compiles. Almost done doing the wrapping on the bot, will try it then
<bluestorm>
actually, = is overloaded under the hood
<mfp>
ssssh :)
<bluestorm>
so while it is true that there is no ad-hoc polymorphism in OCaml, (=) is still an exception (~hack) for convenience
<bluestorm>
the other solution is to enrich the type system (as SML did, and wich can be generalized into Haskell type classes) but that's probably more complicated
<flux>
how is (=) exception?
<flux>
it just is defined for all types, and can produce a runtime error at times..
<bluestorm>
well
<flux>
ocaml doesn't need to handle (=) in any special fashion
<flux>
other than having it implemented in C..
<bluestorm>
yes, that's what i mean
<bluestorm>
of course programmers can use C or Obj. to inspect the value representation
<bluestorm>
that's still exceptional imho
<bluestorm>
and (in general) certainly not a good idea
<flux>
you could have it work with objects
<flux>
but it's difficult as an integer literal isn't an object..
<bluestorm>
btw, i think there are some exceptional cases of type specializations of comparisons in the compilers, still :-'
<flux>
optimizations?
<bluestorm>
yes
xavierbot has quit [Remote closed the connection]
<bluestorm>
that was a bad way to support my point of exceptionality, no relation to the current topic
Asmadeus has quit [Remote closed the connection]
Asmadeus has joined #ocaml
sporkmonger has joined #ocaml
sporkmonger has quit [Remote closed the connection]
sporkmonger has joined #ocaml
<Asmadeus>
mfp: When starting the ocamlbotwrapper program, I get this :
<Asmadeus>
File "init", line 175, characters 7-59:
<Asmadeus>
Unbound type constructor format6
<Asmadeus>
Know what else to change ?
<Asmadeus>
nvm, found out
<Camarade_Tux>
would someone happen to have an implementation of a patricia tree over strings ?
<Camarade_Tux>
Reins and the one by JCF are over integers
ocamlbob has joined #ocaml
<Asmadeus>
5;;
<Asmadeus>
Guess it doesn't work just yet :p
YlzzirG has joined #ocaml
YlzzirG has left #ocaml []
ocamlbob has quit [Remote closed the connection]
guillem_ has joined #ocaml
Jedai has joined #ocaml
<rwmjones>
Asmadeus, you're trying to backport xavierbot?
<Asmadeus>
rwmjones: mfp did the camlp4 part actually, the rest was just scanf's type which changed
<Asmadeus>
(meaning the "ocamlbotwrapper" part is done, and I've already integrated it in my own bot, but I've got some problem somewhere I can't quite figure :P)
jlouis has joined #ocaml
xavierbot has joined #ocaml
<rwmjones>
xavierbot hello
<rwmjones>
xavierbot, help
<xavierbot>
hello rwmjones, I am xavierbot 0.8, 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
<bluestorm>
hm
<rwmjones>
everyone complained about xavierbot last time ...
<flux>
really?
<flux>
I don't recall :)
<bluestorm>
i just write a medium-sized post comparing Haskell and OCaml to answer the question on the mailing-list
<bluestorm>
s/i/o/
<bluestorm>
fail
<bluestorm>
in the same time, Brian Hurt basically closed the discussion by saying "no flamewar here"
<bluestorm>
do you think i could post that anyway ?
<flux>
there's no website dedicated to the subject?
<flux>
posting an url for such a thing would hardly be a flamewar.
<bluestorm>
(and i'm actually not uninterested in a discussion on the subjet)
<bluestorm>
+c
<flux>
the caml-list is not a very high-volume list anyway. but who I'm to judge, I've never posted there :)
<tsuyoshi>
let s = String.create 20 in for i = 0 to 10 do s.[i] <- '/'; s.[i + 1] <- '\' done; s;;
<xavierbot>
Characters 74-77:
<xavierbot>
let s = String.create 20 in for i = 0 to 10 do s.[i] <- '/'; s.[i + 1] <- '\' done; s;;
<xavierbot>
^^^
<xavierbot>
Illegal backslash escape in string or character (')
<tsuyoshi>
oops
<tsuyoshi>
I guess that is the problem with writing one-liners...
<bluestorm>
(everybody knows printers support pdf these days, but they haven't tried on their toasters yet !)
munga_ has quit [Read error: 113 (No route to host)]
<flux>
pdfs are a pain to read from the screen
<flux>
atleast with xpdf, evince or gv
<flux>
unless your display happens to be a4
<flux>
(and accurate too to read so that it fits all in once)
<bluestorm>
hm
<bluestorm>
i'm not sure
<twobitwork>
there's also the fact the PDFs are anarchonistic, they try to emulate pages in an age where documents can be arbitrarily lengthed
<bluestorm>
text is easier to read when it's not too wide
<twobitwork>
and of course the restriction to A4 sizes
<bluestorm>
so the 4/3 screen is fundamentally worse than a vertical A4 screen
<bluestorm>
pdf or not
<flux>
pdfs with two columns especially are painful
<bluestorm>
twobitwork: use xpdf -cont , dude
<flux>
does that de-columnize the data and remove page breaks?
<bluestorm>
doesn't
<twobitwork>
bluestorm: ohh, never knew of that... but still, we're talking about why people choose to use PDF as opposed to just publishing it in HTML... I mean, your hosting it on the web already, why not just make it HTML?
<twobitwork>
you're*
<bluestorm>
well
<bluestorm>
maths or everything related on HTML is sooo painful
<bluestorm>
we're in 2008 and the UTF-8 support is still hazardous
<twobitwork>
that is true
landonf has joined #ocaml
<bluestorm>
MathML is clearly unthinkable
<landonf>
Howdy
<twobitwork>
I'm not really a proponent of HTML for authoring...
<twobitwork>
but from the users perspective its much simpler than pdf
<twobitwork>
I like how wikipedia allows for embedded TeX
<bluestorm>
that's not bad but a pdf is actually much better
<bluestorm>
for example you can zoom in and out easily
<twobitwork>
you can increase font sizes of web pages in most modern browsers, which is usually what you want anyways
<bluestorm>
well
<twobitwork>
at least, usually what I want
<bluestorm>
you'll have the font size increased, but not the pnged formulas
<bluestorm>
that kind of sucks
wolgo_ has joined #ocaml
<wolgo_>
hi
<bluestorm>
it could be possible to adapt pdf readers to have a more continuous (pageless) presentation of PDF
<twobitwork>
true... which is why web technology needs to adopt SVG
<bluestorm>
coupled with a good integration of the reader inside the web browser (konquer + kpdf/okular are really decent), you can have something pretty good actually
<twobitwork>
er... actually, most browsers support SVG, but the authoring community hasn't adopted it yet
jeddhaberstro has joined #ocaml
<twobitwork>
neither are great solutions, but from a user perspective I prefer HTML
<twobitwork>
at least for documents... however I despise how web technology is being stretched beyond its intended limits and used for applications, etc
<twobitwork>
I mean, things like gmail were never intended when HTML/HTTP/etc where developped
<twobitwork>
it all needs to be thrown out the window
<wolgo_>
If anyone has a second to look at this: http://www.pastebin.ca/1169962 I am trying to untie the knots of eval/apply order in ocaml and this is a good exercise for me. I think I have it.
<twobitwork>
sorry... </rant>
<vixey>
wolgo: eval/apply as in SICP?
<landonf>
twobitwork: I'd be interested to know where web applications can go with canvas + javascript
<wolgo_>
no as in how is this evaluated and how is it applied haha
<wolgo_>
wait
<twobitwork>
landonf: I think js is part of the problem... we need something more like a standardized virtual machine for web apps to run on, then we can target more then one language to this vm... kind of java intended (but never worked out)
<vixey>
wolgo: Where did you hear about eval/apply ?
<wolgo_>
this is evaluated at the very last second because it is lazy
<landonf>
As languages go JS could be a lot worse, but sure.
<bluestorm>
twobitwork: bonus question : without checking in the toplevel, what is the type of nest ?
<bluestorm>
err
<twobitwork>
bluestorm: ?
<bluestorm>
that was addressed to wolgo_ , sorry
<wolgo_>
vixey: I dunno, it just seems to make some sense in that an expression is evaluated for errors then applied if there are none found. Is that incorrect?
<twobitwork>
heh, ok :)
<vixey>
wolgo: it is correct, I just found it strange
<wolgo_>
Is there something more accurate?
<vixey>
no it is perfectly accurate
<vixey>
wolgo: Usually people who are starting to program don't use correct terms ...
<bluestorm>
wolgo_: line 23 is wrong i think
<wolgo_>
Oh
<wolgo_>
well that is the only way to do it no?
<bluestorm>
it's not ... ((^) ("Testing" ^ "Testing") "123") but ((^) "Testing") "Testing 123"
<wolgo_>
I also have this: ((^) (((^) "testing ") "testing ")) "123";;
<xavierbot>
Characters 3-7:
<xavierbot>
I also have this: ((^) (((^) "testing ") "testing ")) "123";;
<xavierbot>
^^^^
<xavierbot>
Parse error: currified constructor
<vixey>
:/
<wolgo_>
what the hell?
<wolgo_>
haha
<vixey>
xavierbot should be silent on parse errros
<wolgo_>
that evaluates successfully in the top level
<bluestorm>
vixey: not sure, feedback is good
<landonf>
twobitwork: Hmm, I think adobe might start arguing that Flash (9) is that common VM runtime =)
<bluestorm>
wolgo_: probably not with the "I also have this :" prefix
<wolgo_>
oh yeah
<twobitwork>
landonf: that's great, but it's proprietary :)
<mfp>
maybe lambdabot's > whatever is better than the curr phrase terminator
<twobitwork>
landonf: and we still have the javascript (activescript) problem :)
<landonf>
Indeed. Also remarkably bad code to treat as a core VM.
<landonf>
twobitwork: Well to be fair, you can compile most anything to AS bytecode
<twobitwork>
landonf: this question has actually plagued me for years... I've had dozens of false-start attempts at trying to come up with a good solution
<twobitwork>
landonf: true...
<twobitwork>
landonf: there are several open source abstract virtual machines... like parrot and llvm
<twobitwork>
there's also .net, but I refuse to allow MS to be the ones who replace the web :P
<landonf>
heh
<landonf>
I've been toying with the idea of toying with F# + Mono
<twobitwork>
and there are a multitude of problems with .net still... it doesn't provide a standard "client" from which I can point to a url to access a web app
<bluestorm>
well landonf
<bluestorm>
haven't you heard last jdh backward-flamewar ?
<bluestorm>
seems F# is not so hot anymore
<twobitwork>
bluestorm: how/why's that?
<bluestorm>
yesterday, on this chan, he came and complained about lots of things, including F# and Mono
<landonf>
Is JDH that Flying Frog Guy?
<mfp>
bluestorm: ? did he troll some F# list?
<bluestorm>
(as always, it's john harrop, so quite interesting actually, but to be used with great care)
<landonf>
Ah right.
<landonf>
He's prolific in his writing, I've come across his posts when searching on almost any subject related to OCaml.
<bluestorm>
(i may have the irc logs around, but i'm not sure this a polite way to quote people)
<bluestorm>
in substance it seems that MS got interested in F# finally, and it is not so quite quite-open anymore
<mfp>
landonf: I think he spends more time on c.l.lisp than in caml-list... ;)
<bluestorm>
(i didn't understand correctly but he wanted to do something a bit near of the F# internals and was answered they're gonna close that)
<mfp>
ah yesterday's conversation
<bluestorm>
so he got frustrated and began to let some of the criticism of F#/.NET/Mono we would never have heard in the "F# all the way" time go
<mfp>
yeah he essentially said MS decided to hide some stuff that used to be open so that nothing can compete against their devel tools
<bluestorm>
seems the lack of module/signatures/functors in F# is not so unimportant anymore, and people actually buy OCaml fork-parallelism
<wolgo_>
line 23 is "testing 123" because ((^) "testing") returns a partially applied function with testing as its 1st arg and 123 as its second arg
<wolgo_>
I understand now
<bluestorm>
(and Mono is slow and hell the JVM should support tail-recursion and Visual Studio is flawed and what not)
<wolgo_>
assignment is immutable
<wolgo_>
this is insane
<bluestorm>
wolgo_: i'm not sure why you want to see partially applied function everywhere
<wolgo_>
probably because I don't know what the hell I am doing or talking about
<wolgo_>
haha
<bluestorm>
there are two point of view : either you consider f x y z to be a call with 3 parameters (higher-level view), and none of your calls are partially-applied
<bluestorm>
or you consider f = fun x -> fun y -> fun z -> .., one argument each time
<bluestorm>
and then there is no partial application : an parameter is applied or not, never partially
<bluestorm>
this is the lower-level view, wich is sometimes interesting (when you build closures for example) but probably not the simpler for the beginner
<bluestorm>
ocamlers tend to mix the two quite often, but if you define let rec nest n f x, and call nest (n-1) f (f x), you shouldn't bother with partial application
<bluestorm>
you have total application of the parameters in both senses
<wolgo_>
so the type of nest is int -> fun -> string?
<wolgo_>
lets check
<wolgo_>
wow that was wrong
<mfp>
let rec nest n f x = if n=0 then x else nest (n-1) f (f x);;
<xavierbot>
val nest : int -> ('a -> 'a) -> 'a -> 'a = <fun>
<bluestorm>
mfp: hey, you just gave the solution, wich is bad
<bluestorm>
wolgo_: "fun" doesn't exist and string isn't generic enough
<mfp>
bluestorm: I suppose he checked in his top-level already, just meant to show him there's xavierbot
<bluestorm>
do you understand the type given by ocaml ? why can't f be ('a -> 'b) (wich is the more general type for a function) ?
<wolgo_>
because 'b is not the same type as 'a?
<bluestorm>
of course
<bluestorm>
but for example
<bluestorm>
let app f x = f x
<bluestorm>
is ('a -> 'b) -> 'a -> 'b
<bluestorm>
why is the function f of nest inferred to be ('a -> 'a) ?
<wolgo_>
because f needs to be applied to terms of the same type?
<bluestorm>
yes
<wolgo_>
Oh
<wolgo_>
Okay.
<Asmadeus>
bluestorm's gonna be hell of a good computer sciences teacher :P
<bluestorm>
(i'm so lame at that socratic things, i should just keep answering question)
<wolgo_>
this is awesome
<wolgo_>
Sorry, please do not feel obligated to teach me the basics of ocaml
<wolgo_>
I do not want to take your time.
<wolgo_>
I appreciate the schooling though.
guillem_ has quit [Remote closed the connection]
asmanur has joined #ocaml
wolgo_ has quit ["leaving"]
<bluestorm>
those intuitionistic mathematics posts on the planet are so cool
<vixey>
I would like to write a parallel gc for ocaml
<bluestorm>
that does not seems so reasonable for a start
<flux>
how's the parallel gc project for ocaml going, btw? or is it going at all?
<bluestorm>
last year iirc there was a meeting at the top with everybody presenting his work
<bluestorm>
that might explain the lack of communication in the last week
<mfp>
vixey: it's a "OCaml Summer Project" from Jane St.
<mfp>
not google's summer of code
<vixey>
:/
<vixey>
I wish I had got on that boat
<mfp>
yep, next meeting on Sept 11-12th
Linktim_ has joined #ocaml
Yoric[DT] has joined #ocaml
<landonf>
Anyone used OCaml with SWIG?
Linktim has quit [Read error: 110 (Connection timed out)]
mishok13 has joined #ocaml
comglz has joined #ocaml
asmanur has quit [Remote closed the connection]
Linktim has joined #ocaml
Linktim_ has quit [Read error: 110 (Connection timed out)]
comglz has quit ["je re"]
comglz has joined #ocaml
<wolgo>
hi
<hcarty>
mfp: I did briefly, but didn't like the generated interface
<hcarty>
Sorry, that was meant for landonf
<twobitwork>
is there a built-in way to do function composition in ocaml?
<twobitwork>
(other than "fun x -> f (g x)"
<twobitwork>
)
Dzlk has joined #ocaml
<hcarty>
twobitwork: There is no built in syntax or operator
<hcarty>
Beyond f (g x)
<vixey>
can you use 'o' as an infix operator like in SML?
<hcarty>
vixey: The Jane St. OSP Delimited Overloading project has a pa_infix module which is supposed to allow that. But vanilla OCaml does not.
<mbishop>
hcarty: was it you who talked about uintlib yesterday?
<hcarty>
mbishop: Possibly? I think I mentioned that it exists
<mbishop>
hcarty: have you used it? I don't know how to properly install it (I have the cmx/cma/o files built, just not sure where to put them to get ocaml to recognize it)
<mbishop>
I tried moving them into /usr/lib/ocaml/3.10.0/ myself, but that didn't work
<bluestorm>
hcarty: moreover, this is bad style imho
<bluestorm>
how is a reader supposed to understand f o g ?
<Asmadeus>
Well, like in maths I'd say; g then f
<Asmadeus>
You can't make letters infix though, anyway
<bluestorm>
such kind of semantic interpretation should not be context-dependent
<bluestorm>
Asmadeus: the problem is, that extension can
<bluestorm>
and there are already some alphabetic infixes
<bluestorm>
( mod, and the bitwise operators )
<Asmadeus>
Ah. Well, I wouldn't understand it if I didn't know then, I'd think the function f takes o and g as arguments
<bluestorm>
a more sensible thing to do would be an ugly hack to allow for a "gone-infix" notation
<bluestorm>
comparable to haskell `foo`
<vixey>
yucky
<bluestorm>
it is possible by pure syntaxic means ( yoric's evil /* .. .*/ ), but a bit heavy
<bluestorm>
and infix notations should not be abused anyway
<hcarty>
bluestorm: How difficult would it be to make an extension to translate "f $ g x" or "x |> g |> fto "f (g x)" to avoid the function overhead? I've read complaints about the overhead, but have not tested its impact..
<twobitwork>
wouldn't that be "syntactic"?
<bluestorm>
hcarty: pa_infix can probably already do that
<mbishop>
bluestorm: do you know how to install some ocaml code "by hand", so that I can open it using OPEN?
<bluestorm>
what do you mean ?
<bluestorm>
(OPEN ?)
<hcarty>
mbishop: You can #load the .cmo directly in the toplevel
<bluestorm>
twobitwork: sorry, i meant "using the unmodified OCaml syntax"
<mbishop>
bluestorm: as in, open Pervasives, etc
<bluestorm>
ah
<hcarty>
mbishop: Or you can use compiler directives to tell ocaml(c|opt) where the library files are
<bluestorm>
mbishop: those are modules
<bluestorm>
and every ocaml file you write is implicitly a module
<twobitwork>
mbishop is in #scheme, and lispers like to refer to functions in conversation with all caps, like MAP refers to (map ...)
<bluestorm>
eg. if you have a file "foo.ml" with declarations inside
<bluestorm>
you can use them (eg. a value "bar") from the outside : Foo.bar
<bluestorm>
then "open Foo" and voila
<hcarty>
bluestorm: pa_infix probably can... I think that may be one of the more useful applications of the extension.
<mbishop>
bluestorm: right, I tried to place the cmxa/cma files into /usr/lib/ocaml/3.10.0/ but ocaml couldn't find them
<bluestorm>
aah
<bluestorm>
you want to put it in the stdlib ?
<mbishop>
and I tried to include them when compiling, but it still complained
<bluestorm>
hcarty: yeah
<bluestorm>
we should put Yoric[DT] on the subject :-'
<bluestorm>
mbishop: you probably did something wrong
<mbishop>
bluestorm: I just want them somewhere that ocaml knows to look (like other modules)
<bluestorm>
you can tell him were to look with -I ...
<bluestorm>
and you can create your own toplevel wich embed some -I ...
<twobitwork>
do the ocaml compilers read an environment variable for extra libs? I think some compilers do that kind of stuff
<bluestorm>
i think ocamlfind is a more flexible way though
<hcarty>
twobitwork: ocamlfind does
<bluestorm>
(you use a META file, install it in the ocamlfind repository, then ocamlfind ocamlopt -package your_lib ....)
Jedai has quit [Read error: 110 (Connection timed out)]
<bluestorm>
hcarty: did you suggest them the "open in" behavior ?
<wolgo>
I wonder how you would do that, write a function that composes functions.
<wolgo>
it is built in though so I guess I shouldnt care
<bluestorm>
it is not
<vixey>
wolgo: see above
<vixey>
(people were just talking about that)
<wolgo>
Oh okay.
<mbishop>
bluestorm: I tried ocamlopt -I /foo/ code.ml but ocamlopt complains about a "syntax error" on line one (trying to open the module)
<hcarty>
bluestorm: I did, and it has been added, at least in some form
<bluestorm>
mbishop: it probably means you did a syntax error
<bluestorm>
hcarty: good
<hcarty>
bluestorm: I think it is on a module-by-module basis though. I may ask for a way to turn it on globally.
<mbishop>
bluestorm: don't think so, the "error" it claims to find is the name of the module
<mbishop>
it doesn't know the module so claims it's an error
<bluestorm>
was that really a syntax error ?
<hcarty>
wolgo: let ( & ) f x = f x in print_endline & string_of_int 1;; or something along those lines
<bluestorm>
(this is maybe the time to show your code ( http://pastebin.be or anywhere you like) and/or paste the full error)
<bluestorm>
let comp f g = fun x -> f (g x)
<wolgo>
let compose f g x = ((f) g x);; like this?
<bluestorm>
your parenthesis are wrong
<wolgo>
Oh I see
<wolgo>
I think
<hcarty>
bluestorm: Do you think it is worth requesting the ability to enable openin globally? I think having it set on a module-by-module basis may become difficult to follow.
Dzlk has left #ocaml []
<bluestorm>
hcarty: yes i do
<hcarty>
bluestorm: Ok, I'll submit another feature request for that
<bluestorm>
the Foo.(...) syntax is really the embodiment of the "open in" idea, it would be a shame to miss it
<bluestorm>
(it is so natural imho that it could even become a surprise to the user that it does not behave this way)
<bluestorm>
Foo.bar and Foo.(bar) should be equivalent when they both make sense
<hcarty>
I agree
<bluestorm>
hm
<hcarty>
Foo.(bar) -- what is the proper term for "bar"? An expression?
<mbishop>
The external function `to_string16' is not available
<Asmadeus>
term is fine, but I don't know
<landonf>
Is OCaml-Java getting any traction? I could see how it would be a bit of an odd duck in the ocaml world, but access to so many libraries ...
<bluestorm>
the ocaml manual use the term "value path"
<bluestorm>
« Expressions consisting in an access path evaluate to the value bound to this path in the current evaluation environment. The path can be either a value name or an access path to a value component of a module. »
<bluestorm>
landonf: if you want so you have to give it traction yourself : use it, talk about it, blog about it
<rwmjones>
landonf, I've played with it a bit, had a go at packaging it for fedora, and it does what it says on the tin
<mbishop>
rwmjones: any chance you've used Shaw's uintlib? I can't get it to work
<rwmjones>
mbishop, hey ... saw your posting on caml-list today & nearly replies
<rwmjones>
replied
<landonf>
bluestorm: Indeed
<rwmjones>
erm, no I haven't used it, but it's on my list of things to try "at some point in the future"
<mbishop>
I'm about to just email the man himself to ask :P
<hcarty>
mbishop: That looks like it is a problem with linking/loading the C portion of the library
<rwmjones>
mbishop, my reply was going to say along the lines of use "ocamlfind install <packagename> *.cmo *.cma ..." to install it
<mbishop>
hcarty: yeah, I don't know why, the C code for that function looks ok to me
<hcarty>
mbishop: Can you #load the .cma?
<mbishop>
hcarty: well, it didn't error
<hcarty>
I think the .cma has extra information in it to help with such things
<mbishop>
but now how do I use it? heh
<hcarty>
mbishop: It should be ready to use now
<mbishop>
well uInt32.foo says uInt32 is a syntax error, and open uInt32 is also a syntax error
<mbishop>
I'm spoiled by easily installable code, never done this myself before
<rwmjones>
mbishop, all module names must start with a capital letter
<mbishop>
rwmjones: ah, well these have lowercase names...does it uppercase by default or something?
<mbishop>
looks like it does
<rwmjones>
mbishop, aiui it won't even parse correctly
<rwmjones>
I mean,
<rwmjones>
open abc
<rwmjones>
isn't valid ocaml
<mbishop>
the filenames all use uInt32 or uInt64, but open UInt32 worked
<rwmjones>
mbishop, ah I understand
<rwmjones>
mbishop, ocaml turns a file called abc.ml into a module called Abc
<rwmjones>
so the modules are UInt32
<rwmjones>
et
<rwmjones>
etc
<mbishop>
ah, that's somewhat confusing, he should probably rename them :P
<mbishop>
rwmjones: (and everyone else) thanks, seems to be working now
<Asmadeus>
mbishop: actually, I don't like to have filenames begining by a capital letter; like lablgtk stuff are called gEdit or the likes, I find it good enough this way. Too bad it caused you trouble, though
<rwmjones>
it confused the heck out of me at first .. there's a section in the ocaml-tutorial.org specifically about this
<Yoric[DT]>
bluestorm: sorry, I was afk.
<Yoric[DT]>
What were you talking about?
<bluestorm>
hm
<bluestorm>
about the pa_do project
<bluestorm>
wich is remotely related to your camlp4+monad work
<bluestorm>
hcarty was asking about using camlp4 to inline simple operators (in his case function composition)
<bluestorm>
and we think that pa_do may provide a general framework to do that kind of thing
<bluestorm>
(possibly with a bit of feature pushing from our side)
comglz_ has joined #ocaml
<Yoric[DT]>
Sounds familiar.
<bluestorm>
hm
<bluestorm>
i just thought you were about to say "Actually, i am the project mentor of pa_do"
<mbishop>
Hmm, what makes "123l" know that "123" is of type int32? and is it possible to add my own?
<bluestorm>
mbishop: it is lexer-level knowledge
<bluestorm>
and it is not really easy to add your own
<bluestorm>
though an intricated camlp4 solution is imaginable
<mbishop>
hmm
<mbishop>
I think I should just ask Jeff Shaw for a proper usage of uInt32
<rwmjones>
mbishop, it's in the compiler, and no .. I wanted to add a syntax for "int63" (if you search on caml-list) but n ojoy
<mbishop>
I think they should seriously consider adding a number of datatypes to ocaml, it's one of the nicest parts of F# (having all the .Net types with "abbreviations")
<hcarty>
bluestorm: Does that mean that openin is enabled by default?
<hcarty>
I think it may just be the default for modules with overloading enabled
twobitwork has quit [Read error: 104 (Connection reset by peer)]
sporkmonger has quit []
<bluestorm>
h
<bluestorm>
hcarty: i guess that mean it is the default
<bluestorm>
the best is still to look at the code
<bluestorm>
(btw, the responsiveness to suggestions is impressive)
<bluestorm>
(and also : it is never bad to show interest too soon)
<hcarty>
Yes, I was amazed at how quickly they responded with an implementation
<hcarty>
A brief, though possibly inaccurate, test in the toplevel indicates that using Foo.(bar) under pa-do when no overloading is defined for the module Foo will give an error
guillem_ has joined #ocaml
<bluestorm>
hcarty: my brief and probably innacurate tests showed that trying to use pa_do in the topfind-enhanced toplevel with no further indication inevitably lead to an error
<bluestorm>
so your side does not look so bad :p
seafood has joined #ocaml
<hcarty>
I had errors, ignored them, and then got what looked like a legitimate pa-do generated error :-)
<hcarty>
I emailed the developers to ask if "x |> g |> f" --> "f (g x)" is outside of the scope of pa-do. If not, then I will submit a feature request for that as well.
<bluestorm>
might be even better to submit a patch
<bluestorm>
(if i'm given working source example with working compilation command, i could even help)
<hcarty>
bluestorm: I'm heading out for now, but assuming I have time I will take you up on your offer for help
seafood has quit []
Yoric[DT] has quit ["Ex-Chat"]
lde has quit [Remote closed the connection]
lde has joined #ocaml
Toonto_del_alma has quit [Read error: 110 (Connection timed out)]
Toonto_del_alma has joined #ocaml
Linktim has quit ["Quitte"]
code17 has joined #ocaml
lde has quit [Remote closed the connection]
lde has joined #ocaml
lde has quit [Remote closed the connection]
lde has joined #ocaml
zheng has joined #ocaml
zheng has left #ocaml []
redocdam has quit [Remote closed the connection]
sporkmonger has joined #ocaml
jlouis has quit ["Leaving"]
marmotine has quit ["mv marmotine Laurie"]
munga_ has joined #ocaml
coucou747 has quit ["bye ca veut dire tchao en anglais"]
dibblego has quit [Remote closed the connection]
dibblego has joined #ocaml
sporkmonger has quit [Read error: 110 (Connection timed out)]
code17 has quit [Read error: 104 (Connection reset by peer)]
code17 has joined #ocaml
code17 has quit [Client Quit]
code17 has joined #ocaml
code17 has quit [Client Quit]
code17 has joined #ocaml
code17 has quit [Read error: 104 (Connection reset by peer)]
code17 has joined #ocaml
Asmadeus has quit ["nighters"]
vixey has quit [Read error: 113 (No route to host)]
Morphous has quit [Read error: 113 (No route to host)]
munga_ has quit [Read error: 113 (No route to host)]