gl changed the topic of #ocaml to: OCaml 3.07 ! -- Archive of Caml Weekly News: http://pauillac.inria.fr/~aschmitt/cwn , A tutorial: http://merjis.com/richj/computers/ocaml/tutorial/ , A free book: http://cristal.inria.fr/~remy/cours/appsem, Mailing List (best ml ever for any computer language): http://caml.inria.fr/bin/wilma/caml-list | http://icfpcontest.org/ !!
sundeep has quit ["Client exiting"]
cjohnson has quit [Read error: 104 (Connection reset by peer)]
maihem has quit ["Read error: 54 (Connection reset by chocolate)"]
cjohnson has joined #ocaml
dobrek has quit ["leaving"]
gim has quit ["++ (rentrage)"]
smimou has quit ["?"]
bzzbzz has left #ocaml []
cjohnson has quit [Read error: 110 (Connection timed out)]
cjohnson has joined #ocaml
bk_ has quit ["Leaving IRC - dircproxy 1.1.0"]
kinners has joined #ocaml
cjohnson has quit [Connection timed out]
cjohnson has joined #ocaml
KrispyKringle has joined #ocaml
CosmicRay has quit ["Leaving"]
Herrchen_ has joined #ocaml
Herrchen has quit [Read error: 60 (Operation timed out)]
KrispyKringle has quit ["Lost terminal"]
kinners has quit ["leaving"]
KrispyKringle has joined #ocaml
mrsolo has joined #ocaml
GreyLensman has quit ["Leaving"]
monotonom has quit ["Don't talk to those who talk to themselves."]
KrispyKringle has quit ["leaving"]
vezenchio has joined #ocaml
Nutssh has joined #ocaml
cjohnson has quit [Success]
cjohnson has joined #ocaml
mrsolo has quit [Read error: 113 (No route to host)]
cjohnson has quit [Success]
cjohnson has joined #ocaml
dobrek has joined #ocaml
mrsolo has joined #ocaml
<dobrek> hi. Is there any clear way to make some sort of checked exceptions. I imagine that the compiler could infers the list of exception which can be thrown by module and print it on demand. Now if I have just 20 differenc files and modules I'm already affraid I had missean smth.?
<Nutssh> ?
<Nutssh> dobrek, what do you mean?
<dobrek> Nutssh: I mean. I would like to see what kind of exceptions can be thrown by each function of the module
<Nutssh> Thats not possible.
<dobrek> Nutssh: why ?
<Nutssh> Ocaml supports higher order functions, what exceptions might '' val foo: (int -> int) -> int '' throw?
<Lemmih> _
<dobrek> Nutssh: ok. This is true. But I could I think argue that I will worry only about the exceptions in foo:
<dobrek> Nutssh: later when I : let foo_too = foo (fun x -> x ) ;
<Nutssh> It is possible to add to the type system to allow it check assertions about what might be thrown, but it would not work well.
<dobrek> ok. I will still think about it. Somehow it at first glance looked like easy. But I probably as alway don't it well.
<Nutssh> How about '' let foo x = fun _ -> raise Something '' ''let bar x y = raise Something'' when you partially apply it?
<dobrek> I would say thet both are giving a danger of throwing an exception.
<Nutssh> ''let baz x = raise Something ; fun y -> raise SomethingElse ''
<dobrek> baz is a function which can throw "Something" ;
<Nutssh> It depends on what you want. What question are you asking?
<dobrek> Nutssh: I would like to have a tool which helps me to code. It is I develope a module. And I would like to now what kind of exceptions this module might throw.
<dobrek> Nutssh: in order to cope with it properly latter. I could ofcourse do " with _ -> " but I don't want.
<dobrek> Nutssh: anyway I will still thing about it. because I see that I don't see it so clear.
* Nutssh nods
<Nutssh> BBIAS.
Nutssh has quit ["Client exiting"]
<dobrek> ?
Nutssh has joined #ocaml
buggs^z is now known as buggs
<buggs> dobrek, that would be nice indead
<dobrek> buggs: yep. And I must confess I still don't see the problem with it so clear. But now I have to go for an hour.
<Nutssh> Do you want it done syntatically, (does 'raise' exist within the textual extent of a function)? Or do want it done semantically?
<dobrek> Nutssh: I would prefere semantically.
<Nutssh> Do you want it as feedback, or as something built into the type system --- something verified?
<dobrek> Nutssh: I am not a theoretition. I am physicist, but I simply cannot imagine that If I can infere type I cannot infere exception type. I should be simpler. But as I said I am just a user.
<dobrek> Nutssh: for me it can be a separated tool, what ever.
<Nutssh> let foo fn = (fn 12) + (fn 14)
<dobrek> fun foo: int -> int
<dobrek> :))
<dobrek> no
<Nutssh> let bar x = if x=14 then raise Something else 2*x
<dobrek> I see.
<Nutssh> let baz x y = x y ;; let ding () = baz foo bar ;;
<vincenz> I love the naming
<vincenz> I tend to stick to just foo an dbar
<Nutssh> I go foo bar baz, but wing anything beyond that.
<vincenz> I notice you like cartoon sounds
<vincenz> "ding" "baz"
<Nutssh> Ding! Thanks. Thats a good one.
<vincenz> You just used it
<vincenz> 12:42 < Nutssh> let baz x y = x y ;; let ding () = baz foo bar ;;
* vincenz is more boring when he needs multi vars
<Nutssh> Ya know, its *too* damned early in the morning.
<dobrek> I know, that I am pretty stupid, but where is the problem. bar can throw exception. and ding too.
<vincenz> let f x y=...
<vincenz> let g a b=..
<Nutssh> My preference for variable names and functions is like:
<Nutssh> let l1i l11 li1 = ...
<vincenz> oh yeah, ultra readable
<Nutssh> let il1 i1l lll = ...
<vincenz> you sick bastard
<Nutssh> :) Some day, I should write a translator to turn all function&var names into that.
<vincenz> shouldn't be -too- hard
<vincenz> read in your prog into ast
<vincenz> and then dump it again
<Nutssh> let iI1 iIl iIl = ....
<Nutssh> Yup.
<vincenz> then to assign, find the the total number of vars necesasry at any given point
<vincenz> (shadowed vars not used don't count)
<vincenz> and seeing you have i I 1 and l as bits, you can easily figure out the number of 'bits' needed in a var name
<vincenz> that way they're all equal lengths
<vincenz> plus you reuse names as much as possible
<Nutssh> Actually, I like the idea of just translating everything into fixed-length vars.. Lets see, if its n chars long, there are 2*4^(i-1) [il][iIl1]*
<vincenz> let rec f x = ...
<vincenz> let f x = ... f y....
<Nutssh> :)
<vincenz> (two different funcs, but the second is defined after the first)
<vincenz> it's actually quite amazing you can't call g from f in
<vincenz> let f = ...
<vincenz> let g = ...
<vincenz> after all they're in the same scope -> same environment
<vincenz> that's something they really should fix in many langs
<dobrek> I guess I have to try to write smthing like that. Than I will understand the problem:) Anyway thanks.
<dobrek> vincenz: isn't it related with the type inferer.
<Nutssh> dobrek: Identifying that requires global flow who-calls analysis. The 4 functions could be in different modules.
<Nutssh> vincenz: ??
<Nutssh> You can do that
<vincenz> you can?
<vincenz> no you' can't
<vincenz> otherwise there would be no need for recursively defined funcs
<Nutssh> let f = ... and g = ...
<vincenz> yes
<vincenz> but not without the and
<Nutssh> correct.
<dobrek> Nutssh: shure. But in *principle* it could be done.
<vincenz> if you use let f = .... nad g = ...
<vincenz> can you simulate a recursive func even though you're not using rec?
<Nutssh> No, You need to have a cycle in the definition/scope space to have recursion.
<vincenz> so ...
<vincenz> f still can't call g
<vincenz> otherwise
<vincenz> let f = ...g... and g = ...f...
<Nutssh> dobrek: Yes, about the easiest is to assume that any function can handle any exception... Why do you want to do a try .... with _ -> ...
* vincenz raises his eyebrow
<Nutssh> vincenz, That last definition should work.
<dobrek> let rec will work. let itself will not IMHO.
<Nutssh> Ah, my mistake.
<dobrek> vincenz: you need a special construct for recursion in this sort of languages. Becouse you cannot infer type otherwise.
<dobrek> Or. If you define a recursion operator, it will have not type or smthing.
<Nutssh> You don't need any construct for recursion. Unification will find the most general type.
<dobrek> ok. I probably missunderstood smthing I read. Now i am trying to find it out again
<dobrek> ok so this fixpoint combinator has no type. And I am quoting" In fact no fixpoint combinator is typabe in ASL. This is why we need a special primitive or synatctic construct in order to express recursivity"
<dobrek> I lost title page.
<dobrek> so there will be no proper bibref.
<dobrek> ok now I understand.
<Nutssh> ok.
<dobrek> you are right ofcourse and I am wrong ofcourse :))
<dobrek> but I should have been gone 1/2h ago. Now I really have to. and thanks for help I am learning always a lot from you guys. by by
<Nutssh> later and good luck.
cjohnson has quit [Connection timed out]
cjohnson has joined #ocaml
smimou has joined #ocaml
cjohnson has quit [Connection timed out]
cjohnson has joined #ocaml
cjohnson has quit [Read error: 60 (Operation timed out)]
gim has joined #ocaml
mattam_ is now known as mattam
bk_ has joined #ocaml
buggs^z has joined #ocaml
buggs has quit [Connection timed out]
Nutssh has quit ["Client exiting"]
cjohnson has joined #ocaml
segphault has joined #ocaml
<segphault> is there a way to have val elements in a class that arent defined at initialization?
<segphault> i'm guessing I have to do something funky to the class signature to give it type hints.
<Riastradh> You can use the option type.
<segphault> I just figured out that I can use "val mutable x = ([]:myClass list)"
<segphault> is there a better way to do it?
<Riastradh> You can use the option type.
<segphault> thx. just looked it up. thats a bit cleaner.
buggs^z is now known as buggs
greenrd has joined #ocaml
cjohnson has quit [Connection timed out]
cjohnson has joined #ocaml
Nutssh has joined #ocaml
maihem has joined #ocaml
maihem has quit [Read error: 104 (Connection reset by peer)]
monotonom has joined #ocaml
mattam_ has joined #ocaml
mattam has quit [Read error: 60 (Operation timed out)]
gim has quit ["reboot"]
pattern has quit [Read error: 110 (Connection timed out)]
<greenrd> How do I declare a zero-argument function with fun?
<greenrd> I tried (fun -> false) which produced a syntax error
<Riastradh> There are no zero-argument functions in OCaml.
<greenrd> Ah
<Riastradh> All functions accept exactly one argument.
<greenrd> So I'll just have to pass a dummy argument then I guess
<Riastradh> Yes. () is the typical value for that dummy.
<greenrd> Thanks
pattern has joined #ocaml
<greenrd> Wow, it compiled. OCaml's type inference blow my mind!
<vegai> in a good way, I hope?
<Riastradh> Ew. You got chunks of it on my arm.
<Nutssh> Riastradh, I thought ocaml supported zero-arg methods, though it advised against them.
<Riastradh> Methods don't count.
<greenrd> Nutssh: Methods are functions with an implicit "self" argument, surely?
<Nutssh> :) to both
<greenrd> Another q: In this code: http://www.greenrd.org/tmp/example.ml
<greenrd> Is it possible to avoid the 2-stage initialization of cyclicMemo?
<greenrd> I tried to put (fun unit -> s#isCyclic0) in the definition of cyclicMemo, but it wouldn't have it because it said you can't reference an instance variable from the definition of another.
<monotonom> fun () -> s#isCyclic0
<greenrd> ta
<greenrd> But that doesn't avoid the 2-stage init.
<greenrd> Is there no way to define parts of a class recursively with respect to one another?
<mellum> Looks like you're implementing graphs... are you sure classes is the way to go for that?
mattam_ is now known as mattam
<greenrd> mellum: I'm an OO man. I come from a Java background and I've just started learning OCaml.
<smimou> objects are the the first thing you should try to learn in OCaml
<smimou> most of the time you don't need them
<smimou> and they are much less efficient thant modules
<monotonom> OOP = object obsessity pomposity
<smimou> :)
<mellum> greenrd: IMHO you only need classes if you have heavy method overloading. I don't see that for graphs.
<mellum> greenrd: you could also look at the ocamlgraph library. They don't use classes, either.
<Nutssh> I use classes when I want either inheritance of implementation or more frequently, subtyping. If I want aggregates, I use records, sum types for sum types, modularity, modules.
demitar__ is now known as Demitar
CosmicRay has joined #ocaml
vezenchio has quit ["According to [a processor for game design], you statistically have a better chance of becoming a rock star than you do of suc]
<greenrd> Wow, the debugger even supports time travel.
<greenrd> I'm impressed!
<mellum> gdb has that, too
<mellum> although quite limited and slow
<greenrd> Yeah, I can imagine - hard to track the history of something that can manipulate memory arbitrarily, I'd think
<buggs> hmm how can i use a record type defined in another module ?
Nutssh has quit ["Client exiting"]
<mellum> buggs: Module.t
<buggs> # let m:Trie.trie = {id = 1; symbol = 'b'; parent = None; transitions = Hashtbl.create 5; };;
<buggs> Unbound record field label id
<buggs> when i open Trie then it works
<mattam> you should prefix each field name with Trie
<mattam> if you don't open it
<buggs> that's harsh
<mattam> write a constructor function in Trie
<buggs> mattam, i have
<buggs> but then i still have to access cia : m.Trie.id
<buggs> *via
<mattam> why don't you open it ?
<buggs> i don't want to clutter my namespace
<monotonom> {Trie.id = 1; Trie.symbol = 'b'; etc.}
<monotonom> It sucks but I suppose any alternative has bigger problems.
<buggs> i don't bother it thatmuch in the constructor but in the access
<buggs> my_trie.Trie.id
<mattam> let tid = Trie.id
<mattam> and write accessors in Trie ?
<buggs> :/
dobrek has quit ["leaving"]
ithkuil has joined #ocaml
bk_ has quit ["Leaving IRC - dircproxy 1.1.0"]
<ithkuil> hello
<ithkuil> i was wondering a couple of things. does ocaml optimise recursive functions when it compiles them and
<ithkuil> why dont you need monads ?
<ithkuil> thats ok probably really old questions not interesting i will google or deja search or something
<ithkuil> are french people really smarter
<ithkuil> j/k
<ithkuil> My conversations are always seem much more successful for me when I have them with myself.
KrispyKringle has joined #ocaml
<buggs> ithkuil, ocaml has global variables
<ithkuil> buggs: thats why you dont need monads with ocaml?
<ithkuil> i know this is boring also but i always thought global variables were evil
<ithkuil> sorry
<buggs> well and not having them complicates stuff
<buggs> you need whole worlds to work around (monads)
<ithkuil> certainly
<ithkuil> global variables are not evil then?
<buggs> it depends on how you use them
<ithkuil> brb
<mattam> monads are not needed because you can have mutable data structures
<mattam> french people are really smart, and yes, ocaml has tail-call optimisation
<monotonom> Monads are still a nice wrapper around lists, options, sets, parsers, substitution, ...
<mattam> yeah, sure
<mattam> substitution ?
<mattam> for composing them ?
<monotonom> Take an expression with free variables, instantiate the free variables by other expressions.
<monotonom> Yes, composing substitutions.
bzzbzz has joined #ocaml
<mattam> interesting perspective
<mattam> is there some idiomatic use of the substitution monad ?
<monotonom> If you write a theorem prover, substitution is essential. Otherwise I don't suppose it is of much use.
<mattam> when i have substitutions i usually apply them one by one, i don't see where monadic style would help
<ithkuil> is there anything monadic in the ocaml libs?
<monotonom> It becomes a monad when you want to pass substitutions around without applying them.
<ithkuil> if not i bet someone will put them in there
<mattam> i see
<monotonom> If the only operation you ever want to perform over substitutions is to apply them, of course there is not much point.
<mattam> ithkuil: nope, and don't expect anything ressembling monads to get into the standard lib :)
<ithkuil> ok
<mattam> i think there is a monadic parser implementation somewhere though
<ithkuil> i just started learning about functional programming because i wanted to learn how to write compilers
<monotonom> That is a good start.
<ithkuil> is ocaml a good language for creating compilers?
* monotonom thinks writing a compiler in a popular imperative language is intractible.
<monotonom> Yes.
<monotonom> The entire ML family is good.
* ithkuil looks up the word 'intracitble'
<monotonom> Oh haha I mean the English word, not the CS complexity theory word.
<ithkuil> what about compared to java or c#? (ocaml for writing compilers)
<monotonom> The CS software engineering words are "unmaintainable" and "doesn't scale".
<ithkuil> i see
<ithkuil> what do you think of the idea of writing compilers with java
<ithkuil> or with c++ i mean
<monotonom> {java, c#} \subset "popular imperative language"
<KrispyKringle> heh
<KrispyKringle> is there an equivalent to CUP, jlex, or yylex for OCaml?
<KrispyKringle> ocamllex. cool.
<KrispyKringle> and ocamlyacc. even cooler. i answered my own question. :)
<monotonom> I think you will write longer code for data structures and algorithms in Java, C++, C#.
<ithkuil> definitely
<ithkuil> i used to think c# was the answer to all of my problems
<KrispyKringle> never used it. might have to try.
<monotonom> For example you will need some kind of representation of the parse tree. In Ocaml you just go like type expr = Var of string | Op of operator*expr*expr | ...
<KrispyKringle> parse trees aren't that hard to write in Java or some other OO imperative language.
<monotonom> In OOP languages you will write a lot of subclasses. A lot of typing.
<KrispyKringle> it might turn otu to be a bit longer in terms of code, but it's not--well, intellectually--that challenging.
<monotonom> Well that is precisely the problem. If it is not intellectually challenging, it shouldn't take up a lot of lines of code.
<ithkuil> i think that many aspects of writing compilers are intellectually challenging
<KrispyKringle> ithkuil: no, i totally agree. but writing the data type for a parse tree is relatively trivial :P
<ithkuil> krispykringle would it be intellectually challenging for you to write a distributed system for persistent object storage
<monotonom> The Dijkstra metric for software cost is line-of-code wasted, not line-of-code produced.
<ithkuil> oh ok :)
<KrispyKringle> writing semantic analysers and code generators is a bitch, and writing lexers is just tedious and then some, even with something like jlex.
<KrispyKringle> ithkuil: i wasn't saying compilers are trivial by any extent :P
<Riastradh> So don't write lexers! Just use S-expressions for everything!
<ithkuil> personally i think that people have wasted waay too much time parsing text. i dont like text
<KrispyKringle> but the parse tree itself is reasonably simple, if tedious (which is I suppose monotonom's point; no reason it should be bloated if it's simple intellectually).
<ithkuil> i think we should try to get passed the thing with serializing everything
<ithkuil> and unserializing
<ithkuil> and serializing
<KrispyKringle> what's the alternative?
<ithkuil> information isnt naturally organized in streams
<ithkuil> we just do that because we can only speak one word at a time
<ithkuil> interactive incremental compilation
<KrispyKringle> i dont know what that means :P
<KrispyKringle> are you talking about a different means of input? because so long as the input is some sort of textual representation, i dont see another eway of parsing it.
<ithkuil> well maybe someday i will develop the idea and come up with a good explanation and convincing argument. i dont really have that though
<ithkuil> at this point
<ithkuil> thank you this is interesting mono
<KrispyKringle> i understand :)
<KrispyKringle> monotonom: yeah. interesting reading. i think i may have heard something like this once before.
<ithkuil> the idea of storing programs as xml is interesting right
<ithkuil> what about storing programs as OWL or some other DL or logic
<monotonom> Um actually the most recent url I pasted is not the one I intend.
<KrispyKringle> but this talk of extensibility leaves me a little confused; so far the examples seem to be little different than what you can do in languages that support higher order functions (ocaml, python, etc)
CosmicRay has quit [Read error: 60 (Operation timed out)]
<Riastradh> That guy talking about storing all code in XML is silly.
<KrispyKringle> what am i missing?
<Riastradh> Or rather, specifying that it must be XML is silly.
<KrispyKringle> agreed, Riastradh.
<KrispyKringle> XML is a great buzzword :P
<Riastradh> Indeed, the programmer really shouldn't _care_ how it's formatted; it should be formatted in whatever way the IDE developers deemed suitable.
<ithkuil> componentization
<Riastradh> For instance, they might format it as a serialized & compressed flow graph.
<Riastradh> Componentization?
<monotonom> But for now the IDE developers deem xml suitable. :)
<ithkuil> Compilers and linkers are still monolithic command-line applications: files go in, files come out, and the only way to control what happens in between is through command-line flags or embedded, vendor-specific directives. Programmers cannot invoke parsers, analyzers, or code generators selectively, or insert custom modules to change how programs are processed1.
<ithkuil> But why would anyone want to? One answer is given by SUIF [SUIF], a C++ compiler that allows users to plug in their own optimization modules.
<KrispyKringle> monotonom: i heard C# doesn't store in plaintext (?). The problem regarding things like CVS and diff usage are solveable, but the difference between something like that and a plaintext-syntax language with a good IDE (there are some already that do the tree view discussed in that post) are minimal.
<KrispyKringle> Why change the structure of the language (as this author points out) when you can just have an IDE that interprets the syntax properly and displays it to your liking?
<monotonom> I think we can easily do both and have both in the same IDE.
<KrispyKringle> either is certainly achievable. but why would you want to move away from plaintext?
<KrispyKringle> it's hardly necessary to do what C# (apparently--I haven't used it) did just to achieve a better display ;)
<monotonom> I mean hey, even a spreadsheet today can import and export multiple formats.
<KrispyKringle> true.
<Riastradh> KrispyKringle, because a serialized AST is much simpler. Why waste time with complicated parsing?
<KrispyKringle> Riastradh: good point.
<monotonom> And then, one spreadsheet program (gnumeric specifically) defaults to an xml format. :D
<KrispyKringle> Riastradh: my only point there is that the input takes place in some manner that requires some sort of input parsing. if we had graphical IDEs that showed the AST itself...
<KrispyKringle> i dont know. the user interface would be weird :P
GSF has joined #ocaml
<monotonom> The IDE should also be able to display the stuff in various formats at the programmer's choice.
<ithkuil> shouldnt need to be stored in any kind of textual format
<Riastradh> KrispyKringle, the IDE would be able to display it as whatever the user wants.
<KrispyKringle> monotonom: yeah, but there's no *standard* way of representing spreadsheets. by nature, there is a standard with a given language. so it doesn't really matter if it's XML or some other format, since the language itself creates a format.
<monotonom> "How would you like your code done?" "Medium rare."
<KrispyKringle> Riastradh: wouldn't that then mean the user might input in a way that requires parsing? :P
<ithkuil> files and filesystems ought to be going out by now
<KrispyKringle> as long as you let the user do it how he wants, you'll have to parse his input, no?
<Riastradh> No. It's just _displayed_ to the user as source code.
<KrispyKringle> Riastradh: but not input as such?
<Riastradh> The user inputs key sequences that the IDE inteprets not as text but as syntactic elements.
<KrispyKringle> what's the difference?
<KrispyKringle> im afraid im lost at this point.
<ithkuil> i was thinking of writing a compiler without any parsing capabilities, just select identifiers and control structs with a mouse
<KrispyKringle> if the user inputs ``if'', you still have to parse it to determine that it's an IF token and not a string.
<monotonom> Oh and just to mud the pool further, the IDE should also allow the programmer to enter stuff in various modes, including sequential mode, tree mode, ...
<Riastradh> There's a demonstration of Interlisp's S-expression -- not text -- editor.
<KrispyKringle> ok. :)
<monotonom> You see a math expression as a line, but you enter or edit it like a tree.
Demitar has quit [Remote closed the connection]
<ithkuil> cool
<KrispyKringle> mathspad looks neat, but a lot like something like kdevelop with collapsible code segments.
<buggs> vim has folding too
<KrispyKringle> there ya go.
<monotonom> mathspad doesn't collapse things.
<KrispyKringle> monotonom: right. it represents them internally with a tree, no?
<KrispyKringle> im just saying that from a user viewpoint, it doesn't really matter how it's represented if the interface is the same. it doesn't seem necessary (or a lot easier) to get rid of parsing just to provide a better IDE interface.
<monotonom> I understand.
<KrispyKringle> but i may be wrong. i dont know enough about what you're proposing ;)
<Riastradh> KrispyKringle, watching the movie?
<KrispyKringle> Riastradh: just unzipped it.
<KrispyKringle> just a sesc.
<KrispyKringle> sec
<KrispyKringle> slow ssystem 'cause installing mono.
<monotonom> I am not slow!
<KrispyKringle> heh
* Riastradh hiccups.
bzzbzz has quit ["[BX] Get your free warez from ftp://127.0.0.1!"]
<KrispyKringle> this better not turn out to be porn.
<KrispyKringle> ug. postfix. reminds me why i dont use lisp :P
<Riastradh> Postfix?
<KrispyKringle> postfix expressions.
<KrispyKringle> 2 3
<KrispyKringle> / 2 3
<KrispyKringle> + 1 1
<KrispyKringle> etc
<Riastradh> That's prefix, KrispyKringle.
<mellum> That's prefix
<Riastradh> What's wrong wiith it?
<KrispyKringle> prefix. duh.
<KrispyKringle> brainfart.
<Riastradh> With, even.
<KrispyKringle> meh. ugly :P
<KrispyKringle> i think im about to get a beatdown, so ill shut up about it ;)
<Riastradh> Meh. OCaml ugly.
<Riastradh> Observe the futility.
<monotonom> My brain's internal representation is the most elegant!
<KrispyKringle> hehe
<Riastradh> My brain's internal representation is S-expressions!
<ithkuil> thats because information is generally structured in a complex networked way like your brain (rather than as a simple taxonomy or a stream)
<ithkuil> i guess i have to look up s expr
<KrispyKringle> hmm. interesting video.
<KrispyKringle> i didnt really understand what was going on, though. kinda distracted.
<KrispyKringle> looks interesting, but to me it looks like so much effort with the cursor...
<monotonom> S-expression simply means (is this (an s-expression))
<Riastradh> So much effort with the cursor? No, _less_ effort; the IDE deals with moving the cursor to the correct spot in S-expressions.
CosmicRay has joined #ocaml
<KrispyKringle> Riastradh: i see what you mean. i just meant a lot of clicking and new windows for each new expression (or so it looked?).
<Riastradh> With text, you have to manually position it to the exact _character_ you want; Interlisp's S-expression editor would let you move the cursor to the _S-expression_object_ you want, with no textual details involved except when displaying it to the user.
<KrispyKringle> as in, i still think plaintext gives the most options. it doesn't seem to restrict the IDE from doing what you want.
<KrispyKringle> but i see your point. that does seem nice.
<Riastradh> KrispyKringle, perhaps you ought to watch it again, with a little less distraction. Brian had only one window for editing the TAK definition S-expression. The other windows were for invoking the editor and calling the TAK function.
<KrispyKringle> ah
<KrispyKringle> heh, sorry.
<KrispyKringle> so it tokenises input immediately?
<Riastradh> There's no tokenization involved.
<KrispyKringle> how's it know where each expression is?
<Riastradh> The ( keystroke tells the editor 'insert a new list here.'
<KrispyKringle> ah
<KrispyKringle> ill rewatch :P
<Riastradh> The editor is operating on _S-expression_objects_ -- lists, symbols, strings, numbers --, not any sort of text or simple tokens.
<KrispyKringle> hmm.
<KrispyKringle> anyway, thanks for the interesting discussion :)
<Riastradh> Now implement an OCaml AST editor!
<GSF> Does labltk work with tcl/tk 8.4.x?
<KrispyKringle> Riastradh i barely know OCaml. Haven't used it in a long time.
<KrispyKringle> im starting to doubt if i ever knew it, because when i look at ocaml, it looks like greek to me.
<KrispyKringle> actually, i've been doing some catchup, because im annoyed at my lost skills ;)
OliverTwist has joined #ocaml
<buggs> some might remember my LZW implementation
<buggs> i'm down to:
<buggs> 39.6 122.09 122.09 1363423 0.09 0.09 alloc_shr [7]
<buggs> 39.6 244.17 122.09 611 199.81 199.81 _read [8]
<buggs> 19.8 305.20 61.02 506 120.60 120.60 write [16]
<buggs> now i would like to improve my input / output
<buggs> what are the tradeoffs of the various ocaml ways todo IO
gl has quit ["changing servers"]
gl has joined #ocaml
smimou has quit [Remote closed the connection]
CosmicRay_ has joined #ocaml
CosmicRay has quit [Read error: 110 (Connection timed out)]
GreyLensman has joined #ocaml