<palomer__>
how do I tell OMake to use ocamlc? (it's using ocamlc.opt right now)
Proteus has quit [Read error: 110 (Connection timed out)]
Proteus has joined #ocaml
netx has joined #ocaml
<palomer__>
erm
<palomer__>
it looks like I have to recompile everything if I choose to use ocaml cvs
rodge has quit ["Leaving."]
Proteus has quit [Read error: 113 (No route to host)]
jdrake has quit [Read error: 113 (No route to host)]
Proteus has joined #ocaml
middayc has quit []
hsuh has quit [Remote closed the connection]
Proteus has quit [Read error: 113 (No route to host)]
AxleLonghorn has joined #ocaml
AxleLonghorn has left #ocaml []
Jeff_123 has joined #ocaml
ygrek has joined #ocaml
structured has quit [Read error: 110 (Connection timed out)]
Proteus has joined #ocaml
ygrek has quit [Remote closed the connection]
Snrrrub has joined #ocaml
ygrek has joined #ocaml
Ugarte has quit ["Lost terminal"]
Proteus has quit [leguin.freenode.net irc.freenode.net]
Jeff_123 has quit [leguin.freenode.net irc.freenode.net]
marque has quit [leguin.freenode.net irc.freenode.net]
gim has quit [leguin.freenode.net irc.freenode.net]
cmeme has quit [leguin.freenode.net irc.freenode.net]
cmeme has joined #ocaml
Jeff_123 has joined #ocaml
gim has joined #ocaml
marque has joined #ocaml
Proteus has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
pango has quit ["I shouldn't really be here - dircproxy 1.0.5"]
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
pango has joined #ocaml
filp has joined #ocaml
Linktim has joined #ocaml
hordf has joined #ocaml
rodge has joined #ocaml
rodge has left #ocaml []
filp has quit [Read error: 110 (Connection timed out)]
<flux>
oh, cool, printexc has get_stacktrace these days
<flux>
that's excellent as my I have a program where exceptions would never terminate the program
<flux>
hm, is that an old function which I have just missed?-o
<flux>
phew, atleast 3.09 didn't have it
<flux>
nor 3.10.1, so it appears to be a recent addition
Demitar has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
Cygal has joined #ocaml
middayc has joined #ocaml
Linktim_ has joined #ocaml
Demitar has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim- has joined #ocaml
marmottine has joined #ocaml
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim_ has joined #ocaml
structured has joined #ocaml
Linktim- has quit [Read error: 110 (Connection timed out)]
<Linktim_>
koi
robyonrails has joined #ocaml
robyonrails has left #ocaml []
OChameau has quit [Read error: 113 (No route to host)]
middayc_ has joined #ocaml
bluestorm has joined #ocaml
Associat0r has joined #ocaml
middayc has quit [Read error: 110 (Connection timed out)]
Jeff_123 has quit []
al-maisan has joined #ocaml
al-maisan has quit ["Leaving."]
structured has quit [Read error: 110 (Connection timed out)]
tty56 has joined #ocaml
TheLittlePrince has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]>
hi
TheLittlePrince has quit [Client Quit]
bluestorm has quit [Remote closed the connection]
jdrake has joined #ocaml
smimou has quit ["bli"]
<rwmjones>
Yoric[DT], ping
AxleLonghorn has joined #ocaml
AxleLonghorn has left #ocaml []
tty56 has quit [Read error: 113 (No route to host)]
thelema has joined #ocaml
<thelema>
Yoric[DT]: ping
hkBst has quit [Remote closed the connection]
hkBst has joined #ocaml
<Yoric[DT]>
rwmjones: thelema: pong
<thelema>
we meet again...
<thelema>
I like the new enum code...
<Yoric[DT]>
Thanks.
<thelema>
Especially the ExceptionLess submodule (although maybe the L shouldn't be capitalized)
<Yoric[DT]>
Possibly.
<Yoric[DT]>
I was doing a lot of Java when I wrote it, I may have been influenced :)
<thelema>
and I've gone through your changes to extlib in the batteries svn tree - they look good too. I'm still working on integration - I've run into a problem where Enum doesn't show up in the toplevel
<rwmjones>
Yoric[DT], you said:
<rwmjones>
"Let me rephrase: I'm waiting for some feedback on either my planned list
<thelema>
I'll make it appear, it'll just take some work.
<rwmjones>
of contributions or my previous submission. I have no clue if my plans
<rwmjones>
are acceptable, if the size of my module is convenient, or the
<rwmjones>
formatting of comments, or anything else, for that matter.
<rwmjones>
"
<rwmjones>
what am I supposed to be looking at to give feedback?
<thelema>
rwmjones: I assume you want nice, self-contained patches each with clear intent.
<rwmjones>
that would be nice yes
<rwmjones>
I'm also worried that we either have an incompatible enum or more pollution of the toplevel module space (extlib is already bad in this regard)
<Yoric[DT]>
rwmjones: two weeks ago or so, as a reply to a question regarding my plans wrt, I sent a short summary along with the URL to a pdf containing module-by-module details.
<Yoric[DT]>
s/wrt/wrt ExtLib/
<Yoric[DT]>
Later, I posted a module.
<rwmjones>
erm my email's been fscked up, can you post the url here?
<Yoric[DT]>
I have received exactly 0 answer on either.
<Yoric[DT]>
There were also a few words in the e-mail along the lines of "I'm not going to fork ExtLib, I'm going to submit patches wrt functions and documentation and I'm going to repackage it from the outside, i.e. to give an apparently different module structure, but Batteries will mostly be a GODI meta-package".
<Yoric[DT]>
(depending on ExtLib and others)
<thelema>
Yoric[DT]: on ExtChar - there's some code in camomile that should get used for doing some of this - it's got some efficient library code.
<Yoric[DT]>
thelema: does it work with non-Unicode ?
<Yoric[DT]>
I was planning to have ExtChar package both Char and UChar.
<Yoric[DT]>
Actually, not, but I was planning to have two modules, Char and UChar.
<thelema>
yes, well that's the other thing - probably these kinds of functions don't need to be written for the ascii world - only the unicode world.
<thelema>
if you're doing this kind of thing in the ascii world, you probably should use unicode to do it right.
<Yoric[DT]>
Actually, I am preparing a parser combinator library.
<Yoric[DT]>
I want to be able to instantiate it for Latin-1 and for Unicode.
<Yoric[DT]>
So I replicate a few functions of UChar inside Char, for Latin-1.
<thelema>
hmm... all right. Have you seen the code in cflib? (core foundation)
<thelema>
I don't like the coding style, but there's some nice ideas in there.
<Yoric[DT]>
(and the answer is "no, I haven't looked at it yet")
<Yoric[DT]>
I've been looking for a parser combinator library but didn't manage to find one in OCaml.
<rwmjones>
Yoric[DT], so you've now got patches to feed back for these changes?
<Yoric[DT]>
rwmjones: not all of these yet.
<Yoric[DT]>
But yeah, many of these.
<rwmjones>
I would definitely start by sending patches early
<rwmjones>
small chunks are easier to review and apply
<thelema>
Yoric[DT]: take some time to look over this one - it's reasonably well thought out.
<Yoric[DT]>
rwmjones: which is why I've sent one patch already.
<rwmjones>
on the subject of new toplevel modules there are going to be problems ... while having toplevel Bool, Int32, etc. is a good idea, it clashes with existing libraries (janest-core) so you'd need to coordinate to get a common module
<Yoric[DT]>
I was waiting for some feedback.
<rwmjones>
Yoric[DT], you sent a patch? I didn't see one
<rwmjones>
to ocaml-lib-devel?
<Yoric[DT]>
yep
<thelema>
I've put any new numeric libraries (Bool, Int32, Float) into a Typestruct toplevel module.
<rwmjones>
what was the subject?
<Yoric[DT]>
On Wed, 7th.
<Yoric[DT]>
thelema: I was planning to put that into a Data toplevel module.
<Yoric[DT]>
(with List, etc. being in Containers)
<Yoric[DT]>
rwmjones: Re: [Ocaml-lib-devel] Batteries Included
<Yoric[DT]>
(ok, I could have chosen a better subject)
<Yoric[DT]>
4 files attached
<Yoric[DT]>
I could repost it.
<rwmjones>
just a sec, let me look to see if it's stuck in my mail queue
<Yoric[DT]>
thelema: so far, it looks like we have the same set of functions, just with different names
<thelema>
Yoric[DT]: I don't see an emails from you to ocaml-lib-devel on the 7th.
<rwmjones>
Yoric[DT], are you sure you sent it to the right list? I don't even see anything on 7 May in the archives
<Yoric[DT]>
From: David Teller <David.Teller@univ-orleans.fr>
<Yoric[DT]>
To: ocaml-lib-devel <ocaml-lib-devel@lists.sourceforge.net>
<Yoric[DT]>
Subject: Re: [Ocaml-lib-devel] Batteries Included
<Yoric[DT]>
Date: Wed, 07 May 2008 16:44:12 +0200
<thelema>
I see one on the 9th, and one on the 15th
<thelema>
I found (sorta) your "batteries included" post to ocaml-lib-devel
<Yoric[DT]>
thelema: how would you capitalize ExceptionLess ?
<thelema>
ExceptionFree
<thelema>
or Exceptionless - it's one word.
rodge has joined #ocaml
<flux>
I would prefer something like NoExn, because I usually avoid opening modules
<flux>
and it would be much less to type; I would probably make an alias for the module if the name is too long
Torment has joined #ocaml
<thelema>
flux: then I guess you'll have to do module NoExn = Exceptionless in your source code. NoExn seems too terse to me.
<flux>
I would likely go for NE ;)
<flux>
doesn't NoExn convey the sufficient information?-o
<flux>
especially being the submodule of for example List
<flux>
in any case, code list List.find foo bar I write all the time, but match List.Exceptionless.find foo bar.. well, you would basically end up aliasing the module, no?-o
<Smerdyakov>
I'm in favor of long, informative module names and aliases as a matter of course.
<flux>
so you would prefere Exceptionless over NoExn?
<thelema>
Yoric[DT]: for the simple task of 1 + 4 + 9 + ... + n*n, n=2,000,000 I get times of .136 seconds, .844 seconds and 4.9 seconds whe using a for loop, Enum.fold/map, List.fold_left/map
<flux>
btw, I definitely agree with the word "Exceptionless" over "ExceptionLess"
<flux>
also apparently it has been left to the digression of the user to do module List = struct include List include List.Exceptionless end if she wants to, I suppose that's OK
<flux>
(hm, did I use the word "digression" properly there?)
* thelema
makes a note to put that in a comment
<Smerdyakov>
flux, I would prefer [Exceptionless] over [NoExn], yes.
<hcarty>
flux: discretion, I believe
<flux>
hcarty, ah, of course
<flux>
I was thinking that something's doesn't feel right there :)
<flux>
(s/'s//)
structured has joined #ocaml
<flux>
smerdyakov, when writing functions that would use the services of the module List.Exceptionless, would you spell it out in full, open the module, or use some local alias? (and if so, which name would you pick?)
<flux>
just interested..
<flux>
(the underlying assumption being that you use such functions atleast a handful of times)
<Smerdyakov>
flux, I usually assign single letters as far as reasonable as aliases, and go to two letters when needed.
<thelema>
oh my.
Jedai has quit [Connection timed out]
<flux>
it's an interesting idea in ExtLib to use polymorphic variants for return codes indicating an error. I actually like it. (without actual experience of using them, though.)
love-pingoo has joined #ocaml
<thelema>
ah, much better -- I was getting micro-benchmark results with List performing better than Enum
<orbitz>
i don't see List.Exceptionless on th extlib website, is it hot off the presses?
<flux>
wouldn't it?-o
<thelema>
orbitz: yes - not yet accepted into extlib
<flux>
thelema, what kind of benchmark?
<orbitz>
oh
<orbitz>
how do the polymorphic variants work here?
<orbitz>
coudln't you just make something liek 'find' return an 'a option?
<flux>
val split_at : int -> 'a list -> (('a list * 'a list), [`Invalid_index of int]) Std.result
<flux>
and they do
<flux>
but in case you need to return a more informative error message
<thelema>
flux: the sum(1^2..n^2) benchmark
<orbitz>
oh ok
<orbitz>
i haven't really gotten to a use case that needs polymorphic variatns yet so i'm alittle iffy on their usage
<flux>
I think it could be a big maintenance
<flux>
/usage overhead if all such types had a separate error type
<flux>
with distinct constructor names
<flux>
etc
<orbitz>
but is there a good reason for it? Exceptions in ocaml are supposeldy upwards of 40x faster than exceptiosn in just about every other lagnuage, so it's ok to use exceptions for more trivial tasks
<flux>
of course, I think none of those functions have two different errors codes, so it's largely academincal :)
<flux>
orbitz, if your code is going to be try Some (List.assoc foo bar) with Not_found -> None in any case, it's good to put them to a library
<flux>
I've lately written a lot of exceptionless code
<flux>
it's not the performance, it's that I want to handle the case locally
<flux>
and if I propagate it, propagate it explicitly
<flux>
case in point: continuation passing style.. exceptions don't work out-of-the-box nicely.
<orbitz>
i think it' dbe less of an issue if ocaml's std exceptions didn't suck ass in terms of usefulness:)
<flux>
perhaps..
<flux>
but imo it would definitely be less of an issue if ocamlexn was up to date
<thelema>
flux: what do you want from ocamlexn?
<flux>
thelema, that I would see if I leak exceptions unexpectedly?
<thelema>
? you mean nice stack traces?
<flux>
before I run the code :)
<thelema>
nothing - the compiler doesn't warn or error out on unhandled exceptions
<flux>
which is what ocamlexn is supposed to do, right?
* rwmjones
wonders if there's a 'string_of_patt' function or 'string_of_expr' function in camlp4 ...
<flux>
I don't actually quite know what kind of output it produces (well, I read the doc but that's quite some time ago) as I've never had an ocaml version that would work with it..
<thelema>
ah, you're thinking of some sort of source code analysis tool, and I'm thinking of the Printexc module
<thelema>
I didn't know there was such a tool.
<thelema>
wow, I only find two references to it on google.
Snark has joined #ocaml
<flux>
yoric[dt], apparently batteries r10 has brought the functions Std.discard. Haskell has the same function under the name "const"; I'm wondering which one would be more established terminology?
<thelema>
flux: there's some other terminology conflicts as well - unfold = seq_hide
<thelema>
well, almosyt
<thelema>
*almost
<flux>
atleast it is based on "seq"
<flux>
although that too could be some unfold :)
<thelema>
seq_hide == non-functional unfold
<flux>
how is in non-functional?
<flux>
s/in/it/
<thelema>
the function passed to unfold normally has type 'a -> ('b * 'a) option
<flux>
val seq_hide: 'b -> ('b -> ('a * 'b) option) -> 'a t
<thelema>
... hmmm...
<thelema>
ah, from_loop confused me...
<thelema>
I saw :
<thelema>
| None -> raise No_more_elements
<thelema>
| Some x -> x )
<thelema>
and assumed x was the 'b
<flux>
yeah, it uses from_loop underneath
* thelema
skipped by that part
<thelema>
Yoric[DT]: what was the problem with Enum.init? I see you wrote it differently.
<thelema>
Yoric[DT]: and your --- doesn't work as documented: 10 --- 5 = 5 --- 10
<flux>
I actually think it's a slightly dangerous to have such a function with such a similar name; I'd prefer --! or something, but I suppose that's a minor problem :)
<rwmjones>
grrr
* rwmjones
is using 4 different version control systems to manage aspects of bitmatch
<thelema>
rwmjones: that's pretty silly.
<thelema>
get rid of CVS and SVN
* rwmjones
has no choice
<thelema>
Well, at least CVS
<rwmjones>
svn for googlecode, cvs for Fedora, hg for virt-df public repo, and git for RH internal repo
<rwmjones>
ok, time to release version 1.0 of bitmatch :-)
<Proteus>
rwmjones, which do you prefer to use, out of curiosity?
<rwmjones>
cvs actually
<rwmjones>
just because it's simple & I understand it
<rwmjones>
the other ones I can deal with, but I quickly hit complicated cases which are outside my understand (particularly with hg and git)
<rwmjones>
at least with cvs you can go in and edit the repo by hand ...
<flux>
:)
<Yoric[DT]>
thelema: the original version caused too many calls to [f] after cloning.
<Yoric[DT]>
thelema: for ---, you're right.
* Yoric[DT]
wonders which behavior he should choise.
<flux>
rwmjones, maybe it's good for the rest of us that there are those git and hg -backups around ;)
<Yoric[DT]>
s/choise/choose/
<thelema>
Yoric[DT]: the one in the docs seems more useful.
Linktim- has joined #ocaml
<rwmjones>
git is particularly crazy once you get into multiple repos and branching
<flux>
darcs is nice, too bad it has scaling issues (don't affect my personal projects, though, but I wouldn't switch to darcs at work)
hsuh has joined #ocaml
<Proteus>
I've also had good experiences with darcs - except for scaling issues, like you said
<hsuh>
is anyone familiar with the exercises on the ocaml-tutorial?
<thelema>
hsuh: no, but I can be in about 10 seconds
<thelema>
hsuh: which one?
<hsuh>
let rec build_list u a n = ;;
<hsuh>
what is u like ?
<hsuh>
Write the constructor build_list that gives n first items of the recurrent series u, a being the list of the base cases of u :
<thelema>
I'm re-reading that over and over, trying to make sense of it.
<thelema>
u has type ('a list -> int -> 'a)
<hsuh>
indeed
<thelema>
ah, I think I see. This is pretty crazy stuff.
<thelema>
lower, it writes: U(0) = 0
<thelema>
U(1) = 1
<thelema>
U(n) = U(n-1) + U(n-2) if n >= 2
<thelema>
for the fibonnaci series.
<hsuh>
yeah, factorial would be something like u(0) = 1, u(n) = n * u(n-1)
<thelema>
a = [0; 1]
<hsuh>
hm
<thelema>
u takes as argument the list of known values, the position of the next value, and returns the next value
<thelema>
so for fib, u = fun l p -> (List.at l (p-1)) + (List.at l (p-2))
* rwmjones
posts the announcement to caml-list ...
<thelema>
so to calculate fib(2), build_list would have to do (u a 2)
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim- has quit [Read error: 110 (Connection timed out)]
TheLittlePrince has quit [Client Quit]
qebab has left #ocaml []
smimou has joined #ocaml
al-maisan has joined #ocaml
al-maisan has quit ["Leaving."]
pango_ has joined #ocaml
hordf has quit [Read error: 110 (Connection timed out)]
hordf has joined #ocaml
al-maisan has joined #ocaml
* thelema
is -><- this close to having unicode ropes, translatable from latin-1 strings
al-maisan has quit ["Leaving."]
al-maisan has joined #ocaml
<Yoric[DT]>
rwmjones: patch sent again
<rwmjones>
Yoric[DT], ok thanks I'll take a look .. assuming my email works
<Yoric[DT]>
I've sent it to the mailing-list.
<Yoric[DT]>
Oops, it seems I've confused two directories.
<Yoric[DT]>
Two of the files are full source rather than unified diffs.
<Proteus>
I'm relatively new to ocaml but it seems like interest and development has been growing quickly over the past couple years. Would you fellows agree? I'd really hate to have the language languish in obscurity.
<Yoric[DT]>
Goes up and down.
<Proteus>
hrmm
<Yoric[DT]>
We're doing our best to keep the "up" :)
<Yoric[DT]>
But technologies such as Ocsigen and MLState seem like good signs.
<Proteus>
but we've got a red hat dev, financial sector devs, and even the semi-infamous Jon doing some interesting things. Not to mention the new book.
<Yoric[DT]>
new book ?
<Yoric[DT]>
I guess I missed that.
<Proteus>
I'm considering various learning projects, particularly an aspect weaver (why not?)
<Proteus>
oh, I'll give you a link
<Yoric[DT]>
OCaml should be nice for an Aspect Weaver.
<Yoric[DT]>
Or do you mean an Aspect Weaver for OCaml ?
<Proteus>
the latter
jeremiah has quit [Read error: 104 (Connection reset by peer)]
<Proteus>
but the former is doable too
<Smerdyakov>
Proteus, here's a brief snippet of unsolicited advice: don't go with "learning projects." Pick something you really wish existed and just get started building it. (Maybe your "learning project" ideas already have this flavor.)
<Proteus>
my first 'learning projects' will simply be reimplementing standard bioinformatics algorithms
<Proteus>
I want a tool set
<Proteus>
that I totally understand
<Proteus>
Smerdyakov, I _do_ wish that ocaml had aspect oriented programing, it's useful for some things
<Proteus>
or maybe I'm wrong
<Smerdyakov>
Proteus, I remain skeptical about AOP, but I've never used it, so you probably shouldn't listen to me.
<thelema>
pre and post functions? Seems like function wrappers provide that pretty reasonably... That's what I remember about aspect oriented programming.
<Proteus>
hrmm
<Yoric[DT]>
Yeah, but it might be feasible to build something to get to that point at linking-time.
<Yoric[DT]>
(and remaining type-safe)
* thelema
worries about scope in most AOP systems
<Proteus>
but, surely, it's good superficial marketing for the language, if nothing else ;-)
<thelema>
I'd avoid a language that's advertised as AOP-friendly
<Smerdyakov>
There has been a good amount of work on principled AOP systems by ICFP community people.
<Smerdyakov>
I, too, consider AOP support a net negative for a language, just as I consider OCaml's OO support a net negative.
<Proteus>
why do you consider OO a net negative? I've heard this before but I don't understand it
<Smerdyakov>
It's rarely useful but still adds complexity to the language.
<structured>
Smerdyakov: hmm very strong stance.
<Smerdyakov>
structured, I'm a strong stance kind of guy.
* thelema
considers OCaml's OO almost exactly neutral - it can be used to good effect, but usually is misused.
^authentic has joined #ocaml
Snrrrub has quit []
<Proteus>
thelema, could you elaborate a bit for a newbie?
<thelema>
Overall, I have a pretty small amount of respect for the OO paradigm - it usually leads to very poor modeling of problem spaces.
<structured>
Proteus: that book reference is very interesting. thanks for the link
<Proteus>
thelema, what about for GUI programing
<Proteus>
structured, my pleasure
<palomer__>
how do I get godi to install ocaml HEAD?
<thelema>
GUI programming does seem to fit OO models - that's about the only place I see it getting used well.
<Smerdyakov>
But you can use functional combinators to get most all of the benefits of OO GUI stuff functionally.
<thelema>
Smerdyakov: know of any stable functional combinator libraries?
<Proteus>
Smerdyakov, could you lead me to some documentation on doing that?
<Smerdyakov>
thelema, I wrote one at Jane Street, but it's never escaping. :(
<Smerdyakov>
Proteus, no, I don't think I know of any.
<thelema>
I've seen some interesting research in that direction, but nothing practical
<Smerdyakov>
thelema, I promise it's being put to use very practically at Jane Street.
<thelema>
Smerdyakov: they have that monster in a very strong cage so it can't escape?
al-maisan has quit ["Leaving."]
<Smerdyakov>
thelema, I don't know if that's a real question.
<thelema>
:)
<Proteus>
Smerdyakov, so how could I learn more about functional combinators?
<Smerdyakov>
Proteus, I don't know. I've learned what I know through being a university student.
* palomer__
wonders what a functional combinator is
<thelema>
Proteus: google fudgets
<Proteus>
Smerdyakov, the GUI toolkit written in haskell?
<palomer__>
hrmph
<Smerdyakov>
Proteus, maybe you just asked the wrong person?
<Proteus>
Smerdyakov, always a possibility
<Smerdyakov>
Proteus, it was thelema who mentioned fudgets.
<Proteus>
oh
<thelema>
Proteus: yes, that one.
<Proteus>
any chance that someone might write up a tutorial on using functional combinators in place of an object system in ocaml?
<thelema>
Smerdyakov: does your work have any relation to ocamlrt?
<Proteus>
ocaml
<Proteus>
whoops
<Smerdyakov>
thelema, no.
authentic has quit [Read error: 110 (Connection timed out)]
^authentic is now known as authentic
TaXules_ has joined #ocaml
TaXules has quit [Read error: 104 (Connection reset by peer)]
<structured>
hmm can't quite tell what the convention is for what to call a signature..I've seen all caps, I've seen "FooSig
Snark has quit ["Ex-Chat"]
<thelema>
a signature?
<thelema>
you mean a module type?
<thelema>
modules and module types should start with a capital letter.
<Smerdyakov>
[module type] instead of [signature] is one of my big peeve's with OCaml concrete syntax.
<Smerdyakov>
s/peeve's/peeves
<thelema>
other than that, you're on your own - some people camelcase
<thelema>
Smerdyakov: signature Foo = sig blah blah end ??
<Smerdyakov>
thelema, yup. That's SML.
<palomer__>
so..erm...noone knows how to install ocaml cvs HEAD with godi?
<structured>
hmm will look into camelcase thanks
Ugarte has joined #ocaml
bluestorm has joined #ocaml
<optikal>
Smerdyakov: They didn't release it with Core?
<Smerdyakov>
optikal, please provide more context.
<optikal>
The combinator library
<Smerdyakov>
optikal, no. It's not likely to be released.
<thelema>
structured: camlcase is what the Java people do -- MethodOfInputtingDataFromObjectTypeNumberTwentyThree
<thelema>
Smerdyakov: because it's so super good that they need to keep it from the rest of the world to preserve their strategic advantage?
<structured>
thelema: yeah just noticed that...but I meant more about if you have a module type, what do you call its implementation? eg.. module type FooSig, then module Foo, or moudle type FOO and module Foo ?
<Smerdyakov>
thelema, that's roughly accurate, for the whole chunk of components that it belongs to, not necessarily for my piece.
<bluestorm>
structured: the ocaml manual use FOO
* thelema
is happy calling both the module and module type the same thing
<structured>
hmm ok well enough of this deliberating.. I think I can maybe start whipping up some code
<thelema>
but I'll admit that I usually don't write module type xxx = ... unless I'm defining something different than the module I'm writing.
<thelema>
and because of the difference, different names are appropriate.
haelix has joined #ocaml
al-maisan has joined #ocaml
hsuh has quit [Remote closed the connection]
* palomer__
uses _ notation
<palomer__>
thelema, what are functional combinators?
<qwr>
(and combinator libraries are one way for creating dsl's)
* qwr
wonders about what combinator library optikal talked
al-maisan has quit [Read error: 110 (Connection timed out)]
<palomer__>
qwr, I don't think they're talking about the SK calculus
<palomer__>
qwr, you use godi?
<qwr>
palomer__: no, haven't used it...
bluestorm has quit ["Konversation terminated!"]
<Proteus>
I've been searching the list and so far I still can't figure out what 'functional combinators' are or how they can supplant an object system.
<Proteus>
<- confused
<palomer__>
Proteus, I'm not sure, but I think they're referring to using functions as values which can be combined (through application) to form more complex values. Like parsec (again, they're being very obtuse so I don't think it's possible to find out what they're talking about)
<palomer__>
man, I installed godi thinking I could get ocaml cvs from it
<flux>
palomer__, I did, except I had some trouble compiling labltk (but fixed it by not applying a patch)
ofaurax has joined #ocaml
hordf has quit ["Bye"]
abeyer has joined #ocaml
<qwr>
palomer__: if they mean something else than high-order functions for functional combinators, i have no idea, what.
<qwr>
palomer__: but the sk-calculus combinators and combinator libraries like parsec are both basically same thing, high-order functions as you said
<palomer__>
so the world combinator can mean any closed lambda term (any term that doesn't have any free variables)
<palomer__>
s/world/word
<palomer__>
it is a theorem that you can represent any combinator in the SK calculus such that application is invariant
ygrek has quit [Remote closed the connection]
<palomer__>
in haskell, they constantly talk about combinators, they would say things like " compose those two combinators " which would mean "compose those two functions"
<palomer__>
however, everything I just said doesn't enlighten anyone about anything which is relevant
<Smerdyakov>
Usually refers to a particular point-free style of programming.
<Smerdyakov>
Also usually conveys no information, but I say it anyway.
<Smerdyakov>
Maybe it's "a functional library that was designed well."
<Smerdyakov>
Also usually involves functions for building abstract types.
<Smerdyakov>
That is, values of abstract types
<palomer__>
Smerdyakov, do you mean type constructors of kind * -> *, or do you mean LF style terms?
<abeyer>
i have a quick newbie question...just want to clarify: .cmo and .cmx files are both compiled output, right? the diff being bytecode vs native?
<Smerdyakov>
palomer__, neither
<Smerdyakov>
abeyer, yes.
filp has joined #ocaml
filp has quit [Read error: 104 (Connection reset by peer)]
<abeyer>
cool, thanks
Associat0r has joined #ocaml
Associat0r has quit [Read error: 104 (Connection reset by peer)]
* qwr
. o O ( high-order functions suitable for point-free programming looks like quite good description of combinator libraries... )
filp has joined #ocaml
filp has quit [Client Quit]
<optikal>
I guess 'pointless' programming wouldn't have been a very good choice words
marmottine has quit ["Quitte"]
Yoric[DT] has quit ["Ex-Chat"]
<Proteus>
could someone clarify what 'point-free programming' means to a newbie?