Submarine has joined #ocaml
mellum has joined #ocaml
<mellum> hi
ni has joined #ocaml
<ni> I'm looking for a string (or buffer) without the sys.max_string_size (I think) limit. Does anyone know of any options?
<ni> The unlimited numeric arrays referred to at (http://www.azstarnet.com/~dmcclain/homepage.htm) might be an option, but the link is dead, and I can't find it elsewhere.
<smkl> perhaps bigarrays?
<ni> Yeah, I discovered them eventually, thanks.
smkl has quit [Connection reset by peer]
smkl has joined #ocaml
jemfinch has joined #ocaml
mellum has quit ["zzz"]
<jemfinch> 8 people? wow...
<jemfinch> anyone here?
<Submarine> !
vect is now known as gl
<jemfinch> hmm.
<jemfinch> I have some pure-ocaml code that causes a segmentation fault.
* Submarine has trouble with LAPACK
<Submarine> Really?
<Submarine> Have you by chanced compiled ocamlc with gcc 2.96 ?
<jemfinch> no, I think FreeBSD still uses 2.95.2
<jemfinch> (the standard pre-3.0 one)
<jemfinch> it's in an interpreter I wrote in O'Caml.
<Submarine> Mmmh. And what is your code like? What libraries do you use?
<jemfinch> well, it's linked with Unix and Pcre, but it doesn't use them (yet).
<jemfinch> it's also linked with Markus Mottl's "Res" library for resizable arrays.
<jemfinch> (which is pure ocaml, to my knowledge)
<jemfinch> I've isolated the specific test-case in the interpreted language that causes the segfault.
<Submarine> Well, congratulations.
<Submarine> I guess you have to bug INRIA about it.
<Submarine> PCRE is cool, but I started developing something even cooler:
<jemfinch> what's that?
<Submarine> using regexp as pattern matchers, binding variables as subexpressions.
<jemfinch> (I know Perl, so Pcre is comfortable for me...and fast)
<jemfinch> Submarine: can you show me what you mean, I don't quite understand it from your description...
<Submarine> let regexp =
<Submarine> let k = "zzz" (* notice the support for embedded
<Submarine> variables and expressions *)
<Submarine> and k2 = "rr" and k3="uu" in
<Submarine> REPL { "X" (foo: (['0'-'9']+))? bar:(['a'-'z']+) "Y" k }
<Submarine> { "ga" "bu" ~foo { k2 ^ k3 } "zo" } ;;
<Submarine> let str = "+++X45aaabYzzzMMUMU";;
<Submarine> (* Now the actual pattern matching *)
<Submarine> REmatch str with
<Submarine> regexp as contents ~bar ~foo ->
<Submarine> Printf.printf "str=%s bar=%s foo=%s\n" contents bar
<Submarine> (match foo with Some x -> x | None -> "<NONE>")
<Submarine> | _ -> Printf.printf "Not found!\n";;
<jemfinch> so you're doing stuff with camlp4, I assume.
<Submarine> Right.
<Submarine> So it includes an ocamllex-like syntax for regexps.
<Submarine> In which you can specify binding names to get back at the data.
<Submarine> At the time I developped this, PCRE was not yet quite finished, so it uses the normal Str lib (first problem).
<Submarine> Second problem: with CamlP4, it's very difficult to do take constants to the toplevel.
<Submarine> (i.e. if the regexp is constant, you'd want to compile it once)
caml has joined #ocaml
<jemfinch> what do you mean, "take constants to the toplevel"
<Submarine> I'm tempted to do this using hash tables, but...
<Submarine> well, in:
<jemfinch> (as a note, caml is the irc bot I've written in O'Caml)
<Submarine> let f x = REmatch str with RE {...} -> ..., you compile the regexp every time.
<Submarine> This is useless.
<jemfinch> (he's not nearly done, but he works...he's actually a rewrite, which is why he's not fully-functional...I haven't finished rewriting him yet :))
<Submarine> So you'd want this regexp done this way:
<Submarine> let f = let re = RE { ... } in fun x -> REmatch ...
<Submarine> Btw, are you one of the guys of the caml mailing-list?
<jemfinch> yeah, but you probably haven't seen much of me.
<jemfinch> I've changed email addys recently (had a temporary one over the summer) and I haven't sent much mail recently.
<Submarine> I'm D. Monniaux (mlgmp, mlgtk).
<jemfinch> oh, cool :)
<jemfinch> I love it when the famous O'Caml people on here :)
<jemfinch> s/on/come/
<jemfinch> I'm just a piddly little guy who programs as a hobby...
<Submarine> I'm not famous at all.
<Submarine> Xavier is famous.
<jemfinch> you've actually released software, though.
<Submarine> Well, you wrote an irc bot.
<jemfinch> gosh...I can't remember how to spell all the famous people's names.
<jemfinch> if it's on The Hump, it's pretty famous, at least in my eyes :)
<Submarine> I'm currently working with Markus Mottl's LAPACK interface.
<Submarine> But I'm facing trouble, and don't know whether it's me or LAPACK.
<jemfinch> (my irc bot hasn't been released, though...so you and I are thus far the only people on the mailing list who know about it :))
<jemfinch> LAPACK is a Fortran linear algebra library, right?
<jemfinch> I have to say, I've been almost tempted by Lisp lately...
<Submarine> Right.
<Submarine> FORTRAN is horrible.
<jemfinch> yeah, it seems so.
<jemfinch> it's fast, though :)
<jemfinch> @cpustats
<caml> I have used 0.0390625 seconds of system time and 0.1796875 seconds of user time. My children have used 0 seconds of system time and 0 seconds of user time. I have allocated 694472 bytes of memory since I was started and currently have 1015808 bytes on my heap.
<jemfinch> that's another thing I can't figure out.
<Submarine> Afaik, there's little reason to use FORTRAN when you have C99.
<jemfinch> how in the world "bytes allocated" is less than "bytes in the heap" is beyond me...
<jemfinch> doesn't fortran have something like 4 possible representations of floats?
<Submarine> Perhaps because it increases the size of the heap beyond the current allocation needs.
<Submarine> 1015808 is troublingly close to 1M, so I guess it goes in some power of two increments or similar.
<jemfinch> you've worked with camlp4 -- how hard would it be to "write a new syntax" for O'Caml?
<Submarine> It's been done.
<Submarine> It ships with an SML-like syntax.
<jemfinch> well, I looked at some of the stuff that in the standard distribution.
<jemfinch> I think it actually shows a lisp-like syntax too. But I'd love to see O'Caml with a much more closer-to-lisp syntax.
<jemfinch> (or at least try it out)
<Submarine> oh maybe it does not ship with it
<Submarine> it may be on Daniel de Rauglaudre's page at INRIA
<jemfinch> one thing that always annoys me is the inability to nest match/try clauses without parentheses or begin/end pairs.
<Submarine> hehe
<Submarine> Caml's syntax is notoriously bad.
<jemfinch> yeah, it is :)
<jemfinch> and the syntax combines poorly with the strict typing semantics, which leads to making it *really* hard for me to get newbies hooked on O'Caml :)
<jemfinch> when Python was my preferred language, I had no problem getting people who said, "What language should I program in?" to write in Python.
<Submarine> Well, everybody knows the syntax is funky, but it's near impossible to fix it without breaking tons of code.
<Submarine> Or at least they could give a converter (possible with camlp4).
<jemfinch> yeah, it is pretty impossible to "fix" -- and honestly, I don't think I'd want the *main* syntax to break, but some really high quality alternate syntaxes would be awesome, especially if you could translate one syntax into another.
<Submarine> There are more troubling issues.
<jemfinch> like what?
<Submarine> For instance, there are several encapsulation constructs (classes, modules).
<jemfinch> oh, yeah...definitely.
<jemfinch> I had to use the "parameterization trick" in my interpreter.
<jemfinch> since you can't declare types and classes in the same "phrase"
<Submarine> Several type definition (classes, inductive...).
<Submarine> Several ways of doing polymorphism.
<jemfinch> what do you mean by that last one, "several ways to do polymorphism"?
<Submarine> functors + normal polymorphism
<Submarine> plus they're adding generalized polymorphism
<jemfinch> uh oh...that's a new term. what's that?
<Submarine> well, I don't remember the exact appropriate term, but
<Submarine> currently, you may use polymorphism only with an implicit head quantifier
<jemfinch> like 'a.
<Submarine> apparently, they want to introduce explicit polymorphism where you say where you quantify on 'a
<Submarine> if only for polymorphic object methods
<jemfinch> like haskell's kinds.
<Submarine> maybe
<Submarine> Like in system F if you prefer.
<jemfinch> I can't say I know what system F is :)
* jemfinch doesn't even program in haskell, he's just read some about it.
<jemfinch> O'Caml won the fourth contest for favored programming language, and hasn't lost its crown yet, so I haven't learned any other languages since O'Caml.
<Submarine> 2nd order lambda-calculus if you prefer
<jemfinch> now you're getting into math, which is even more beyond me than programming :)
<jemfinch> (sorry to be so...uneducated, if a concept is too hard to put into layman's terms, you can just say so and I won't be offended :))
<Submarine> Oh, it's far less complex than the term supposes.
<Submarine> It just says that you can do things like that:
<Submarine> let f (g : forall 'a ('a -> 'a) -> ('a -> 'a)) (g succ 0),(g (fun x -> x +. 1.) 0.)
<Submarine> In OCaml, it's not possible to do this: you can't apply g with two different parameter types in the same term.
<jemfinch> ah...I may have run into that restriction before...
<Submarine> But if you could specify manually that indeed the parameter g is a polymorphic function, then it would work.
<Submarine> Indeed, f (fun h x -> h (h x)) makes sense
<Submarine> it should evaluate to 2, 2.
<Submarine> since parameter g is just the function that takes a function h and returns h o h (o being composition)
<jemfinch> ah, ok.
<jemfinch> most of the *really* functional programming stuff is beyond me still.
<jemfinch> for instance, the utility of function composition and whatnot.
<jemfinch> I translated the "functional unparsing" stuff into O'Caml so I wouldn't have to use Printf, and that uses function composition, but I can't say I *completely* understand stuff like that.
<jemfinch> I looked into Modula-3 recently, too.
<jemfinch> (what other languages do you know, btw?)
<Submarine> Various assemblers.
<Submarine> C, C++ (pre 95)
<Submarine> Some Lisp
<jemfinch> what does the "pre 95" part mean?
<Submarine> Some Basic
<Submarine> Before templates really worked, before namespaces...
<Submarine> Pascal
<Submarine> Perl
<jemfinch> also, what do you use to manage compilation for your O'Caml projects?
<Submarine> Make
<jemfinch> any special makefiles?
<Submarine> I am very conservative.
<jemfinch> what do you mean?
<Submarine> Just a bunch of implicit rules.
<Submarine> I mean that I've not tested the new-fangled systems proposed recently... IDEs and the like.
<Submarine> The last IDE I liked was Turbo Pascal 6.
<jemfinch> oh, ok...I was really asking, "how do you use make to compile your projects in O'Caml" so I could see if there are any tricks I could learn :)
<jemfinch> I assumed you used make, actually :)
<Submarine> Well, always make your ocamllex/ocamlyacc-generated files a prerequisite for "depend".
<Submarine> Use GNU Make and the ${VAR:%.ml=%.cmo} facility
* jemfinch just has to find where xchat puts the Makefile now...
<jemfinch> I wish this OcamlExc would compile without Tk for me...
<Submarine> It's the exception analyser, right?
<jemfinch> yeah.
<jemfinch> I'd also like to figure out Fort, and make it work with C libraries like Pcre and Unix (which it apparently doesn't current work with)
<Submarine> Fort ?
<jemfinch> Framework for O'Caml Regression Testing.
<jemfinch> it's a small unit-testing framework for O'Caml.
<Submarine> where is it?
<jemfinch> should be fort.sourceforge.net
<jemfinch> as I've rewritten my IRC bot, I've really focused on making it unit-testable, but I haven't been able to actually do the unit tests yet.
<jemfinch> I use Markus Mottl's OcamlMakefile, which is great, but has one major restriction: it only really does *one* executable well.
<jemfinch> I'd like to have multiple executables, say, one for testing, one for debugging, one for production...etc.
<jemfinch> there's also something else I've discovered that I don't like about O'Caml.
<Submarine> what?
<jemfinch> oftentimes, when *I* know a case won't show up in a match expression but I don't want the warning for incomplete matching, I do something like, "| _ -> assert false"
<jemfinch> but even compiled with -noassert, it still asserts false there, which means the whole branch is in there.
<jemfinch> I think it should remove that branch if -noassert is specified, thus taking it out of production code (not that that really matters to me, it's academic for my purposes, but I just don't like it ;))
<Submarine> feature wish
<Submarine> But I doubt it is possible.
<jemfinch> it's no biggie...it'd just be nice, though :)
<jemfinch> perhaps they could write an optimizer to just snip something like that out of the abstract syntax tree.
<Submarine> The point is that I don't really think it makes sense.
<jemfinch> what do you mean?
<Submarine> The compiler has no proof that this case does not happen.
<Submarine> The only thing they could do is replace this branch by ()
<jemfinch> ok.
<jemfinch> so what's on your wishlist for O'Caml?
<jemfinch> @cpustats
<caml> I have used 0.171875 seconds of system time and 0.734375 seconds of user time. My children have used 0 seconds of system time and 0 seconds of user time. I have allocated 1779616 bytes of memory since I was started and currently have 1015808 bytes on my heap.
<jemfinch> @uptime
<caml> I have been alive for 0 days, 1 hour, 25 minutes, and 59 seconds.
<jemfinch> hmm...it's using more cpu time than it has previously.
<Submarine> Well... There are no strides in BigArray, for instance.
<jemfinch> strides?
<Submarine> Welll...
<Submarine> Accessing a multidimensional array with indices is done like this, right:
<jemfinch> :)
<Submarine> a*i + b*j + c*k
<jemfinch> sure.
<Submarine> most often, a=1 b=first dimension c=product of first and second dimensions
<jemfinch> that would be like array.(a).(b).(c).
<Submarine> but you may use a=2 for instance if you were to consider the sub-array of even elements
<jemfinch> ah, hmm.
<Submarine> add a displacement like this a*i + b*j + c*k + d and you can consider the sub-array of odd elements
<Submarine> that's useful for instance for fft
<jemfinch> and probably for complex number arrays and stuff too.
<Submarine> too
<Submarine> it also makes extracting subarrays trivial
<Submarine> you can say "I want the bottom right part of this matrix, with lengths foo and bar"
<jemfinch> ok, that could be useful.
<Submarine> Also for image treatment.
<Submarine> Unfortunately, BigArray 1/ does not offer strides 2/ offers very limited subarray extracting
<jemfinch> and, I hear, it's slow.
<Submarine> I can understand some motivations for it, but...
<jemfinch> any other pet peeves?
<Submarine> Funky syntax
<Submarine> There should be an unification of the various classes of polymorphism and types etc...
<Submarine> Modules and functors have some issues (some of them have been fixed)
<jemfinch> I wish functors could be done at compiletime.
<jemfinch> (what are the issues?)
<Submarine> You mean with cross-inlining?
<jemfinch> with modules.
<jemfinch> (yeah, and inlining across modules would be cool too)
<Submarine> Technically, functors are implemented as functions over records.
<jemfinch> but couldn't they be implemented like C++ templates are, and expanded at compile time?
<jemfinch> one *other* thing that kind of bothers me, kind of doesn't, and I don't really have a solution to, is that universality of some exceptions.
<jemfinch> for instance, when Unix.gethostbyname can't look something up, it raises Not_found.
<jemfinch> which is all cool, but it's hard to find when all your program says is "uncaught exception: Not_found".
<jemfinch> I actually used the backtrace facility for the first time today, and it really helped catch that error.
<Submarine> jemfinch: The only interest of doing so is inlining. Maybe also it'd simplify some black magic that Caml does with float arrays.
<Submarine> jemfinch: Wrap around any part launching exceptions if you want to be more specify.
<jemfinch> well, C++ templates are *really* fast...
<jemfinch> Submarine: yeah, but then that gets ugly, which is unfortunate.
<Submarine> Sure. But they are fast because they use specialization.
<jemfinch> what do you mean by that?
<Submarine> Well... code written using templates is specialized wrt the parameters.
<Submarine> A generic "add" function is replaced by the specific "add" operator.
<jemfinch> yeah, at compile time.
<jemfinch> shouldn't functors be able to do that?
<Submarine> If this operator is inline and is really the "+" over integers, you get a big performance boost.
<Submarine> First argument why compiling as templates is useful when you do cross-module inlining.
<Submarine> Second is that the types are specialized: the length of a template struct is not know until the template is instanciated.
<Submarine> That is not the case in Caml, since all types have the same length.
<Submarine> Thus the only remaining reason to compile as templates is cross-module instanciation.
<Submarine> Other reasons may include the specialization of certain polytypic functions like comparison.
<jemfinch> yeah, I'd like for there to be monotypic versions of compare, so I could functorize Map with something better than just "type t = int let compare = compare"
<Submarine> (i.e.: if you write if x < y when the type of x and y is generic, it calls a generic comparison function that operates by recursion on the data structures; but if the compiler knows that x is integer, I believe it applies integer comparison directly)
<Submarine> Yeah, that's one of my features wishes: there should be magic that detects monotypic instances of "compare".
<Submarine> I believe there is for < and >, why not for compare?
<jemfinch> I always assumed < and > were defined in terms of compare.
<Submarine> I don't think so.
<Submarine> I think that, technically, they are all defined using external and "%special_function".
<Submarine> O'Caml treats certain "external" identifiers (starting with %) as references to specially compiled constructs.
<Submarine> For instance, there's "%identity".
<jemfinch> oh, hmmm.
<jemfinch> I always wondered about that.
<jemfinch> what's the % for?
<Submarine> Well, otherwise it's a generic C function.
<Submarine> if you do external f: 'a->'a = "%identity" it will call the builtin "identity"
<Submarine> I believe this builtin is defined as "do nothing".
<jemfinch> (which is useful for a remarkable number of functions...Obj.magic, etc.)
<Submarine> It's how Obj.magic is implemented.
<Submarine> The really weird things are things like && and ||
<jemfinch> yeah, I remembered that from browsing the code :)
<Submarine> They are lazy.
<jemfinch> I haven't figured out yet how to implement short-circuit operators in my interpreted language yet either.
<jemfinch> oh, another suggestion I think I'm going to actually email to the O'Caml list: I think Set and Map should have polymorphic version integrated just like Hashtbl does.
<Submarine> Well, you have to compile them specially.
<Submarine> Using the default "compare" ? I agree.
<Submarine> In 99% of cases, people just apply them with "compare".
<jemfinch> yeah.
<Submarine> bye (work)
Submarine has quit ["Client Exiting"]
<jemfinch> @aststats
<caml> 0.211750626564 seconds spent lexing, parsing, and evaluating Ast code.
<jemfinch> @cpustats
<caml> I have used 0.296875 seconds of system time and 1.1328125 seconds of user time. My children have used 0 seconds of system time and 0 seconds of user time. I have allocated 2572312 bytes of memory since I was started and currently have 1015808 bytes on my heap.
caml has quit [Remote closed the connection]
mellum has joined #ocaml
ni has quit [Remote closed the connection]
teek has joined #ocaml
x99 has joined #ocaml
foobarquux has joined #ocaml
foobarquux changed the topic of #ocaml to: www.ocaml.org
graydon has joined #ocaml
<jemfinch> whoa, 11 people!
* jemfinch is amazed.
foobarquux has quit [Remote closed the connection]
gl has quit ["Sic transit gloria mundi"]
gl has joined #ocaml
* graydon tries to do something amazing, for the sake of further amazement
* graydon also notes that clog is a bot
<jemfinch> clog is a bot?
<jemfinch> what kind of bot is it?
<graydon> (nef@bespin.org) : CLOG (Channel LOGger) www.tunes.org/~nef/logs/
<graydon> #ocaml #haskell #assembler #compilers #functional #osdev #diktuon #squeak @#forth #pldi #lisp #{} #tunes
<samx> morning
<graydon> it appears to be something the tunes people put in place to help effect their plans for global programming supremacy :)
<jemfinch> hehe :)
<jemfinch> who are the tunes people?
teek has left #ocaml []
teek has joined #ocaml
teek has quit ["Coffee break"]
mellum has quit [Read error: 110 (Connection timed out)]
<graydon> jemfinch: tunes is a long-lived meta project to produce some sort of "reflective" computing environment; they've been collecting ideas and sketching out grand plans for many years. nobody knows whether it will ever turn into anything, but they collect a fair amount of useful links and information.
<graydon> generally their most useful contribution thus far has been a really tremendous collection of hyperlinks: http://tunes.org/Review/index.html
<graydon> it seemed to get started in the heady days of the early 90s when everyone with a net connection, an ego, and an undergraduate assignment to postpone was keen on writing something ambitious like (but better than) linux, X, C++, etc. I'm as guilty in this category as any :)
<graydon> the guy behint it, fare, is rather more dedicated to (or obsessed with) computers than most, for better or worse. his site makes an interesting read.
<graydon> s/behint/behind/
malc has joined #ocaml