__DL__ changed the topic of #ocaml to: OCaml 3.09.0 available! Archive of Caml Weekly News: http://sardes.inrialpes.fr/~aschmitt/cwn/ | A free book: http://cristal.inria.fr/~remy/cours/appsem/ | Mailing List: http://caml.inria.fr/bin/wilma/caml-list/ | Cookbook: http://pleac.sourceforge.net/
shirogane has joined #ocaml
<ski_> exceptions is an effect
<ski_> type 'a option = None | Some of 'a
<ski_> if you have a function return it's result wrapped in that, then caller must handle failure
<schlick> pango: I can see how you can check that there's a exception handler installed for every kind of exception, the thing is I don't want flow going outside normal flow in any circumstance. Handling them (only) locally still amounts to a local goto. If you had <attempt here> then in the next line <handler here> that'd work. It'd look pretty unclean.
<ski_> (of course it could sometimes delegate, too)
<schlick> Basically the way C handles it /looks/ ok. You try to do something, it fails, it returns a wacko value, you test for it, you handle it. The only problem is C can't /MAKE/ you handle it, because it doesn't know what a error is.
<schlick> There's no standard for "wacko value".
<ski_> match foo x y with
<schlick> I'd like to have something that looks sort of like C's way, but lets the compiler know "external routine foo can return a error, this code must check it". It can't make you handle it sanely, since it doesn't know what "sanely" would be for all contexts, but one major source of bugs in C is not catching errors.
<ski_> None -> ...
<ski_> | Some z -> ...
<ski_> schlick : how about that ?
<schlick> ski_: I'm trying to learn about 16 languages at once. :P ML is too new for me to follow most of it. That doesn't mean I'm not interested. I have to admit I can't tell what that says.
<ski_> 'foo x y' possibly returns 'z', wrapped in 'Some' .. or maybe it just returns 'None'
<ski_> it's a bit like unions, except they are automatically tagged, and you can't acccess parts without looking at the tag with a "switch" (match) construct
<schlick> As for why my thought process is so scattered nobody's telling me what I need to know because I've never seen it in one place (the concept is simple; try to kill as many bugs at once as compile time, no holds barred, all methods are ok). I'm trying reeeeeally hard to not insert causes of errors in the language, or make it hard to optimize. Goto is bad. I started on it. I don't want it, at all.
<schlick> Hmm.
<schlick> Yes, that's more or less what I came up with at first.
<schlick> Returning a struct with a failed/succeeded boolean, and the value if it succeded, or error details if it failed.
<ski_> except, here, if the bool is false, then the other value doesn't exist
<ski_> (as opposed to is just uninitialized or something)
<ski_> so you *must* check to get the value inside
<ski_> in the above case, there's no error details in the error case .. that's easy to add if needed, though
<pango> sum types is also how ocaml get rid of "null pointers" (and the risk of trying to dereference them)
rg has quit [Read error: 104 (Connection reset by peer)]
<ski_> the reason exceptions is bad (and good) is similar to the reason state or continuations or any other 'effects' are bad (and good)
<ski_> (good in the sense of powerful, but dangerous)
<schlick> This is true. Uninitialized values are the devil. Part of the issues is how it effects flow control and syntax (I've heard people claim syntax doesn't matter, to them, I'd like to point out the famous "=" vs "==" fiasco (one of many)). I thought maybe if (is_type(success) = connect(some_computer)) then send stuff else pray for salvation end if would be the most sane.
<schlick> I'm trying to explicitly avoid goto/exceptions/continuations/conditions in this language.
<pango> it's not about uninitialized values, but about magic values
<ski_> anyway, in the sum/variant/algebraic type case, there are no "uninitialized" parts, each variant only contains it's own parts, the other possible parts doesn't exist
<ski_> the mistake Pascal and C (and Ada ?) did was to allow one to extract parts from unions with record/struct field select syntax
<schlick> Yes, untagged unions.
<schlick> Untagged unions are, as far as I can tell, not worth using.
<ski_> with sum types, you can only extract by doing an explicit 'match' and give code to handle all cases
<pango> well, ocaml fixes it using pattern matching, that neither Pascal nor C have
<ski_> Pascal has tagged unions, only they are broken .. it's not checked
<schlick> Ok, so what I'd be looking at doing is having a sum type, that was standard for the return value of all functions? i.e. all functions return this sum type. Then you'd have to extract it? Syntax would be similar to ML? And it'd avoid any non-structured flow control? (just branching)
<ski_> why should all functions return it ?
<ski_> not all functions have same ways of failure, if any
<schlick> I want the compiler to keep track of whether any function can fail. If it can fail, I want the compiler to determine a check for failure is made (i.e. the value is read somewhere). To do this there has to be a standard mechanism for differentiating failure from success.
<ski_> it'd be tedious to wrap every function in this, even if it can't fail
<ski_> s/function/function call/
<ski_> i'm not sure why you want to differentiate between failure and success, in the language
<schlick> I'm aware. See, if you were the inventor of C, you could have said "all functions will return a struct, the struct contains a field "success" which is either true or false (this assumes you had real booleans), and a field "value" which will contain the result if success occured, and function-dependent failure information if failure occured".
<schlick> But they didn't do that.
<ski_> no
<schlick> If you differentiate between failure and success in the language you get two things.
<ski_> and in C, one can avoid checking 'success', and get 'value' even if it's uninitialized
<ski_> sure one should differentiate between them
<ski_> but, i meant more, why should the language treat them differently
<schlick> One, you get better static checking. You can make sure errors are handled (without resorting to goto-esque methods). Not checking error codes is one of the most common sources of error.
<ski_> i.e., why should language know which is success and which is failure ?
<schlick> Two, you can use things along the lines of generators in Unicon (how good a idea this is I'm not sure, I'm just thinking about it) which depend on the notion of "failure" as some special occurence.
* schlick points you at what he just said.
<ski_> isn't it sufficiant for language to know they are different ?
<schlick> That's why the language should know.
<schlick> ski: No.
<schlick> pango: for some reason I can't get to rafb.net never have been.
<ski_> schlick : do these generators succeed many times, until a final failure ?
<pango> oh my
<schlick> ski: Basically a generator lets you spew out a (potentially) infinite number of results. You can use them to make complex statements really simple. You can also avoid reading more values than you're interested in. It strikes me similar to lazily evaluated languages and their infinite data structures. Unicon is one of the few languages that does it.
<schlick> It /has/ to know when failure occurs. It uses a special "fail" keyword, to know that it should stop generating results.
<schlick> The problem is I've never seen a type safe language do it (Unicon is extremely un-type-safe).
<schlick> So I have no idea what it'd look like.
<pango> it's not really required to restrict to two cases sum types however
<schlick> pango: Sum type notation? (at the top)?
<ski_> schlick : ok, this is a good reason, yes (was wondering if you had any reason for assymmetry in mind)
<ski_> schlick : yes, sum type notation
<pango> schlick: yes, parametrized at that ('a and 'b are type variables)
<ski_> schlick : but, isn't this 'failure' a very specialized failure condition ?
<ski_> schlick : btw, do you have any link to Unicon ?
<schlick> ski: I'm a psychopath that has the idea of trying to create "One language to rule them all." (not really, more like one language suite)... I tend to be obcessed with two things in particular. Different ways of doing things (I like to know as many as possible, even if it's just to know "don't do that, it sucks, here's why (e.g. for goto)"). I also really really hate bugs.
* ski_ seems to recall hearing about something similar in CLU or something ..
<schlick> So I'm looking at every interesting language I can find, and every interesting static checker I can find, and try to figure out what I can rob for the first uberlanguage. :P
<ski_> nothing bad about that :)
<schlick> The first one will have to be a C-level language to implement the higher level ones. Generators is one thing you'd need a special handler for failure for. Another is hardcore static checking of error handling.
<schlick> ski: What bugs me is, for instance, Smalltalk fixed math, and assignment vs equality. However, there's lots I hate about it. Unfortunatly, no other language seems to have those two features (block notation is interesting but I have a feeling it's not that great a idea). All these little improvements... all scattered.
<ski_> 'fixed math' ?
bd__ is now known as bd_
<ski_> 'assignment vs equality'
<ski_> could you elaborate ?
<pango> ski_: for the later, he means confusion around = and ==
<schlick> ski: So it'd be nice to have all the ones that can sanely be put together in one language. Obviously you don't want to try to mix purely functional and object oriented (i.e. functional with local side effects) notions of how things should work. You could do it. I've seen conglomeration languages where you can switch programming styles midways, but they tend to be incomprehensable.
<pango> schlick: they're functional objects
<ski_> there are multi-paradigm languages .. like Oz, e.g.
<schlick> ski: assignment vs inequality is a simple but really bad mistake C and most C spawn make. Assignment is /not/ the same as making something equal, it's "making something contain something else". Smalltalk's notation is container <- value It doesn't let you get away with equality for tests either.
<schlick> Sorry, with /assignment/ for tests. See, my brain was injured by C! :P I'll never think again!
<ski_> Pascal's/Ada's ':=' isn't too bad, either
<schlick> if (foo = bar) { do stuff } should never have been a valid construct
<schlick> [with C's notion of "="]
<ski_> indeed
<pango> ocaml uses <- for mutables (mutable record fields, arrays)
<schlick> The math is a bit more complicated. Basically it's popular (indeed, you get screamed at for criticizing it) to intentionally corrupt data on every operation using floating point.
<ski_> actually, assignment makes something equal .. the problem is only that its implicit *what* is changed to make them equal
<pango> and := for references because it's syntactic sugar around a record of one mutable field
<ski_> (and of course, also the point that things are *changed* at all)
<pango> even if it can be explained, it's not very pretty
<schlick> Smalltalk uses bignum integer math unless you /force/ it into floating point (e.g. for displaying it to the user). Some of the notation looks a little weird but it's a lot better than losing data on each operation (hint: algebra /really/ doesn't like losing data for tests involving revering operations).
<schlick> (1/3)*3 != 1
<ski_> right, floating-point rounding can bite
<pango> how are transcendental functions handled ?
* ski_ assumes the answer is "no"
<schlick> As for why I don't think Smalltalk is the beginning and end of all... well, let's see. You try to use a GUI application and the buttons fall off (all the GUI can be edited, all the time, you can tack some of it down but not all of it), the language thinks it's a OS, and GUI subsystem, if you make a mistake EVERYTHING is persistent, so there's no "restarting" (persistence has arisen again as a popular academic fad, I've noticed).
<ski_> schlick : i guess one problem, featurewise, is that it's easier to add a new feature to a simple language, than ortogonally merge it with a language with many other features
<schlick> so there's no "restarting" (persistence has arisen again as a popular academic fad, I've noticed, apparently the EROS-OS people eventually figured out why it was a bad idea). Those are the main ones, though obviously having it in a VM has performance impacts too.
Schmurtz has joined #ocaml
* ski_ has heard persistence is hard
<ski_> m
<schlick> ski: I suppose, it's a lot more useful to have one good language with most of the useful aspects than having 1000 languages that are mostly so so, with some really sucky aspects, and one or two really good aspects.
<schlick> As for functions that result in long computations they're bounded in Smalltalk. You can, of course, generate up to the point you want.
<schlick> Though you may have to do it by writing it out.
<ski_> re floats ?
<schlick> ski: To Pango's question about how math is handled.
<ski_> what do you think about the basic idea of accounting exceptions, as java tries ?
<schlick> I think any variation on gotos is evil. Goto belongs in assembly, where it should stay, to serve the purposes of compilers. :P
<schlick> Basically if you dig through stuff on good style (e.g. Code Complete and kin) you find two things.
<schlick> First, doing /anything/ flow control wise, except pure procedures, is associated with bugs.
<ski_> "effects are dangerous"
<schlick> Second, separating error handling from error detection is associated with bugs (it's a variation on the same theme that related things should not be widely separated in a text). Imagine me telling you "a = 1854" and then 150 pages later I test the value of "a". Will you know what it was?
<quamaretto> If you name a variable 'a' you get what you deserve.
<quamaretto> If you have a variable in scope for more than a page, you *also* have gotten what you deserve.
<schlick> So, yes, while exceptions are the hip and cool thing right now (note that Java is seeing a lot of exception abuse, for non-errors now, surprise surprise), it's still goto, and still deserves to be buried with other evil 1960s era technology. :P
<schlick> I could name it "dollars_in_account" and it'd still be true. Generally speaking related things should appear close together in the text. It holds for english prose. It holds for programming. Constructs design to separate them are sort of like debates on the "right way" to write a infinite loop in C. Is it while (true) or for (;;) People will have long bloody battles over the right way to do wrong things.
<schlick> will have long bloody battles over the right way to do wrong things.
<pango> but not everything can be close to an instruction
<schlick> Along those lines I hear INTERCAL's "COME FROM" statement has become quite popular in academia, and they're trying to bring the joys of INTERCAL programming, and programming with the preprocessor, to the masses. ;)
<pango> the idea to move special cases out of the way is to keep usual instruction path together
<schlick> I'm still holding out for Brainfuck to become the new language of choice. It'll have to be implemented on a VM, running a interpreter, with its own GUI toolkit (not sure how to represent brainfuck output in a GUI either) to take off right now though.
<schlick> Pango: I've heard that said. But generally speaking if your normal path is that long, with the error handling locally, you're doing something wrong. Lots of branches are assocated with bad code.
<schlick> I tend to like complicated stuff to look complicated. At least you know something might be wrong then.
<schlick> It's better than someone telling you "Brainsurgery is easy, here, use this Brainsurgery for Dummies book. Here's your chainsaw. The patient is already prepped in surgery room A-13." :P
<pango> you're getting carried away
<schlick> Possibly. ;)
<pango> and it's getting late here
* pango is looking at BitC
<ski_> 'COME FROM' in academia ?
<schlick> I'm not kidding about the "right way to write a infinite loop" thing causing religious wars, or come from and cpp style preprocessing ("aspect oriented programming" also going by more exotic names, like "hyperspaces").
<ski_> string macros are evil
<schlick> Yes, the idea is to automate cut and paste programming. Instead of trying to have things broken down into objects, you can cut and paste code with a preprocessor into whatever objects your 'cross cutting concern' uses. COME FROM had roughly the same notation. The original concept was how to make GOTO more destructive.
<ski_> AOP is another thing, from what i understand
<ski_> (or at least, *should* be)
<ski_> hehe
<schlick> That's what they claim.
<schlick> I basically described it accuratly though. If you search for "aspect oriented programming" and "come from" you'll get several hits.
<ski_> it's possible it's no better than cut'n'paste in common AOP environs
* ski_ haven't looked
<schlick> The idea that source code needs to have some routine inserted in multiple objects means you screwed up your design. There are no 'cross cutting concerns'. If something needs handling, don't spray it all over your source code, stick it in one place. AOP avoids usual problems with rape and paste by keeping the pasted code in one place so fixing bugs isn't as hard.
<schlick> But it still blows up your design.
<schlick> But hey, it's "The Next Big Thing" ;)
<schlick> Some day maybe I'll start the Side Effect Oriented programming movement, since nobody's harped on that for a while.
<ski_> that's called 'imperative'
<schlick> ski: Well, true, but my language would enhance imperative programming. Side effects are /powerful/! Powerful language constructs save time!
<ski_> yes ! reflected monads for all !!
<pango> schlick: since you mentionned EROS-OS, I suppose you looked at BitC ?
<schlick> We would of course include /both/ goto and come from, to allow you to use more powerful constructs. Probably self modifying code both by eval and buffer overflows too. After all, it saves memory!
<ski_> "invent your own kind of side-effect, and use it implicitely in your program in 10 minutes !"
<schlick> pango: I heard of it, but haven't looked at it in detail. I think it's interesting they called it C since it looks like Scheme.
<pango> but is designed for system programming
<ski_> no "goto", continuations are more powerful
<schlick> Hmm... Maybe come from with continuations...
<schlick> Make it /really/ powerful. ;) Returning is optional of course.
<ski_> come from is not hygienic
<pango> call/cc ?
<schlick> call/cc backwards.
<schlick> We can use them to implement "deceptions". All we need to do is convince everyone that's the new best way to handle all errors (and anything else they'd just assume not be in the current control flow path).
<schlick> pango: I'd heard it was for systems programming. I'm not sure how much checking it does at compile time. For instance Vault is much more interesting to me than Cyclone, since Vault catches more at compile time.
<ski_> reify (fun () -> reflect [1;2;3] + reflect [40;50]) ==> [41;51;42;52;43;53]
<schlick> ski: Looks too much like english. I can see three words in there. Fun is a good idea though. Side effects are FUN!
<ski_> that is translated from SML (actually SML/NJ)
<schlick> Might have a look at APL for pointers. ;)
<ski_> (just to show that 'invent your own kind of side-effect' was not made up)
<schlick> I like the implicitly idea.
<ski_> note that that is not built-in to the lang .. it's coded in the lang
<schlick> Side Effect Oriented programming should allow all type conversions to occur at run time. After all, only stupid programmers make mistakes, and none of us programmers are stupid, right? ;)
<ski_> we can have parsing-side-effects, too
<schlick> ski: C's preprocessor would be hard to beat there.
<ski_> type conversion have little to do with side-effects
<schlick> ski: However, I like their priorities. Clearly it is more important to have imaginary numbers support than safe array handling or standard modern language features (e.g. gasp, networking). Why, only last week I was saying to myself, golly, my taxes would be easier to figure out if I could just whip up a program to work with imaginary numbers, but none of these languages have support for them!
<schlick> work with imaginary numbers, but none of these languages have support for them!
<ski_> whose priorities ?
<schlick> ski: Why sure it does! You can't tell me unsafe type conversion has no side effects. ;)
<ski_> *whose* priorities ?
<schlick> ski: C standard committee's.
<ski_> mhm
* ski_ means 'side-effects' in a special meaning here
<schlick> You can still fall off the end of a array, but doing fancy math is now easier.
<ski_> continuations (goto), state, i/o, exceptions, nondeterminism (both "don't know" and "don't care" variant), parsing are all examples of effects
<ski_> (the above example used ("don't know") nondeterminism side-effects)
<schlick> Yeah, I/O is sorta sad. It's not so bad if you look at the computer from the point of view of being one gigantic filter that all input devices (or the input coming from devices that can do both input and output) feed into, that is one gigantic function, and returns the value to all I/O addresses... Of course the looping and stuff kinda throws the analogy off.
<schlick> At least the terminates-in-indefinite time variety.
<ski_> that's how it's done in Clean
<ski_> the whole program is a pure function from World to World
<schlick> I think that's the way Mercury does it.
<ski_> yes, that too
<schlick> I/O doesn't seem to be that big a source of problems. It's mostly flow control and data processing inbetween that gets you. :( Mishandling volatile and nonvolatile storage can be bad too (especially the latter...).
<ski_> concurrency is hard .. especially if language wasn't designed to allow it cleanly
<schlick> I'm hoping to have the higher level version of the uberlanguage be functions with local side effects. Most of the "easy to read" OO languages are that way.
* schlick nods. "Several old languages were designed to do it. A few people are dredging them up now."
<ski_> for what do you (think) you need to local side effects ?
<ski_> s/to //
<schlick> Setting the value "inside" a object (i.e. not in the procedure that was called), without having to resort to the more evil alternative of self modifying code.
<ski_> oh, you mean 'local' as in 'locally scoped' ?
<schlick> Sort of locally scoped. You can change stuff inside the function you're in, or the object, or by calling routines on other objects, no other way.
<ski_> right
<schlick> Doing so means getting rid of global data, functions that aren't tied to objects, etc.
<ski_> so, it's still global side-effects
<ski_> only, they can't be accessed globally
<ski_> but still, can be felt globally
<schlick> I suppose. It solves most of the problems with data mishandling, by putting it behind a function to do sanity checks.
<ski_> the OO idea of handling state is by localizing access
<ski_> the FP idea of handling state is by disallowing it (which works quite well, in most cases)
<schlick> Yes.
<ski_> of course, it's no FP sin to use state locally in implementation, if it's impossible to discern from outside
<schlick> Granted I'm almost entirely self trained, so I don't claim to know everything, or even everything most college CS majors would. But as far as I can tell (from living through most of it) first there was spagette code. Then they encapsulated code into subroutines. You still had people reaching into data structures and dicking it around and fowling it up for other subroutines.
<ski_> (the 'as if' rule)
<ski_> yeah
<schlick> So then two alternatives emerged. Get rid of the state, and contain the state. OO seems to work well where the structure of what's being processed is fairly static, but the operations change a lot. Functional seems to work well where the structure of what's being processed can vary a lot, but the operations are fairly fixed.
<ski_> yes, that's actually a quite good characterization of an important difference
<ski_> (though, i'm not sure how much that relates to contained vs removed state)
<pango> http://c2.com/cgi/wiki?CategoryException (c2.com is a great resource)
<schlick> Figuring out OO was living hell. The terminology really sounds like something a bunch of kids that were high in the 60s might have come up with "Super hyper poly morphite ism! Heh, yeah, Algol-2050 DEFINATLY needs that feature!"
<schlick> The idea was pretty simple. Just had to weed it out myself.
<ski_> terminology isn't a strong side in OO
<ski_> what idea did you end up with ?
<schlick> Explained right the idea is really simple. I have yet to see a book explain it well, however. I think leading people through the spagette code->structured->functional/OO thing helps, and avoiding all the wacky terminology and unimportant ideas. I mean, sure, inheritance is nice, but, really, it has nothing to do with the basic idea in OO which is just adding data encapsulation to structured programming.
<ski_> (ppl often come up with different 'essentials' of OO :)
<schlick> Basically it's just encapsulation. A object is data encapsulated with the functions that manipulate it.
<ski_> it's encapsulation in a specific way
<schlick> All the rest is just pleasantries, mostly to reduce what you have to write to get something done.
<ski_> modules provide another kind of encapsulation
<schlick> I haven't heard a clear explanation of that. Mostly because there seems to be no agreed on explanation. The only way you can further encapsulate anything that I'm aware of is by putting multiple objects in their own namespaces, and controlling who can use what method (e.g. Eiffel's selective export).
<ski_> modules provide a way to abstract over several datatypes (and some ops over them) at once, in a nice way .. you can't do that easily with objects as only encapsulation mechanism
<schlick> pango: I've read c2's stuff fairly often looking up terms or languages.
<schlick> ski: I'm still having trouble with this type thing.
<ski_> heh
<ski_> what trouble ?
<schlick> If you grew up with basic with line numbers and goto only (no gosub), and assembly, and C, and Pascal, if you pay attention through the structured and functional/OO growth, it's at least somewhat comprehensable what's going on. It's mostly direct transslation (some OO still gives me headaches, how variables on objects on the heap are handled are still a mystery, I assume it's by mallocing
<ski_> in relation to OO ?
<schlick> objects on the heap are handled are still a mystery, I assume it's by mallocing enough to hold the struct of the variables and then writing within the malloced block.
<ski_> yes, something like that
<schlick> As for types, no, I'm sort of having a problem figuring out exactly what is ment by a type. From the 'oldfashioned popular' worldview, a type is just 'how big do I have to make this pidgeon hole to fit this thing in it'. C's data types don't do much other than that. You occasionally notice that it's doesn't let you do something, but it's all so random you don't pay much attention.
* ski_ grew up with basic with line numbers and goto,gosub and (some) assembly and C
<schlick> Apparently while most of the world got rid of types (e.g. I know a little Lisp, which is mostly untyped, unless you want to use the very lenient dynamically typed notion), a few languages went in the other direction, and now there's these grouped user definiable types and all sorts of weird stuff. I'm completely mystified by how it gets checked.
<ski_> 'types' are a classification of values into useful classes
Maledict has quit ["a si biri mellu"]
<ski_> the "type system" in C,C++ and Java are weak .. this is one reason people go to 'dynamically typed' langs like Lisp
<schlick> Yeah, but a class, to me, is a sort of blueprint to make objects from. It doesn't seem to be the same idea, though I here there are 'types' for classes.
<ski_> a class is a type together with a constructor function for that type
<ski_> s/type/particular kind of type/
<ski_> objects are just the values of class types
<schlick> Holy crap, look at the flamewar on the C2 page on "avoid exceptions page. ;)
<schlick> ski: I suppose that's so.
<schlick> ski: Most of what's interesting from the 'this modern type' thing is they seem to actually be worth something in terms of catching errors, instead of a nuisance you have to cope with because the compiler can't figure out how big to make something.
<schlick> ski: How this occurs is rather mysterious.
<ski_> anyway, if you're interested in real type systems, play around with at least one of OCaml,SML,Haskell,Clean,Mercury for a while
<ski_> yes
<schlick> ski: If you say this can only be one of x y or z values, how does the compiler figure out that nothing in your compilation unit can cause it to be anything but that? That's very mysterious.
<ski_> the reason the old type systems are bad (nuisance) is that they are too weak
<schlick> ski: First one on my list is Epigram (the most hardcore apparently). I'm ordering some books to help me beat my head against this type thing. Smerdyakov recommended some.
<ski_> they require you to state much detail, but still doesn't manage to catch the most common errors one would excpect a type system to handle, also they're in your way so you have to cast, which mostly defeats the purpose of the type system
<ski_> hehe
<ski_> TaPL ?
<schlick> ski: Apparently so. I never really thought they were good for anything other than helping C get your program turned into something that would run. I can't recall it ever catching a error. After all, C considers assignment to return a numeric value that's equivalent to true because it has no boolean type... Any language like that isn't going to catch type errors.
<schlick> ski: Yeah, that, and I'm getting the advanced one. I'm interested enough to care.
<ski_> Epigram is prolly a bit esoteric, as of now, at least
<ski_> TaPL is good
<schlick> ski: But apparently it's the only 'regular' programming language with dependant types. There's also DML, but it's not maintained, and apparently can't do everything Epigram can with types (if you read the paper they talk about holes, and the fact Epigram fixed them).
<schlick> I'm going to have to keep the klingon language dictionary (a list of what various math symbols mean) to wade through a lot of these papers though.
<schlick> First time in my life I ever saw a giant hollow N as a math symbol. :P
<ski_> i'd suggest learning Haskell or an ML before trying Epigram
<ski_> there's lots of useful stuff even there
<ski_> <schlick> ski: If you say this can only be one of x y or z values, how does the compiler figure out that nothing in your compilation unit can cause it to be anything but that? That's very mysterious.
<ski_> this is type checking and type inference
<ski_> you probably want to learn how a simplistic such system can work
<schlick> ski: I could, I suppose, and may end up learning ML enough to use it (it's tied to some other tools I need to look over thoroughly, namely MetaPRL and Coq), but I've got so many languages to learn anyway I tend to prefer keeping the numbers down. I really do have somewhere around 16 by now. I don't know any CS majors that know that many, even in passing (and no, these are NOT C variants).
<schlick> majors that know that many, even in passing (and no, these are NOT C variants, they're generally pretty 'weird').
<ski_> yeah, too many interesting langs out there :)
<schlick> I'm trying to keep it down to one for each concept.
<schlick> The only place I've had to break with that is concurrency.
<ski_> anyway, Haskell and the MLs are more or less the standard statically typed functional languages
<ski_> so, imo, it's good to know at least one of them a bit more
<ski_> to e.g. learn about sum types
<ski_> and pattern matching
<schlick> Apparently concurrency is hard to get right. All the people that 'got it right' did it via avoiding shared memory, but there are specifics that vary. They tend to be based on the actors model (pure or impure), dataflow (pure functional), communicating sequential processes (pure or impure), pi calculus, or join calculus.
* ski_ hasn't looked at all of those, yet :)
<schlick> What's this pattern matching thing? I know about regexps, and the much more esoteric SNOBOL/Icon/Unicon scanners, which are, frankly, the most kickass thing ever compared to how you USED to cope with strings. But you clearly mean something to do with types.
<ski_> pattern matching has little to do with regexps
<ski_> pattern matching is a bit like switch on stereoids
<quamaretto> Pattern matching is like switch on steroids with variable binding on polymorphic datatypes.
<ski_> s/polymorphic/parametric/
<quamaretto> schlick: Have you looked at the first chaper of the manual?
<schlick> Actors pure "SALSA", actors impure "E", dataflow "SISAL", communicating sequential processes pure "Occam 2.1" (not Occam-Pi), CSP impure Erlang, pi calculus "pi calculus" (programming language), join calculus "join calculus" (programming language). The last two are sort of educational languages, not intended for real use.
<schlick> E is insanely interesting.
<schlick> I mean REEEALLY interesting.
<ski_> and actually, that bit (parametric datatypes) is orthogonal to pattern matching
<schlick> Great to show those people that claim viruses and hackers can't be stopped.
<schlick> quamaretto: Not sure which manual you're referring to.
<schlick> the OCaml one?
<quamaretto> The OCaml Documentaiton.
<quamaretto> If you poke through it, you'll get introduced to all the core language features.
<schlick> I havent gone through it yet, no. Been trying to organize notes on what I have and work out some specifics about how to fix C's design with what I know now (useful for a language to build a language runtime on).
<ski_> thats join calculus ext. of ocaml
<schlick> ski: I knew about it. I picked join calculus because I figured it'd get the idea across to me more by not being mixed with any other ideas.
<schlick> I actually didn't know type checking was good for anything until I hit CQual.
<schlick> Which was fascinating and made my head hurt a lot. I ended up here indirectly because of that.
<ski_> heh
<schlick> It seems like something slightly lower level than SML or OCaml should have killed C and C++ long ago. You'd think it would have killed C++ for applications. I've actually run a few things written in OCaml. I thought they were C they were so fast.
<schlick> I didn't know they were in OCaml at the time. I think Unison and MLDonkey are both in it.
<ski_> m
<schlick> In case anybody cares most of what I've done to C is decided that the pointer type is too general, and figured out some (to me, understandable, nothing fancy types wise) limits on various types of pointers that could be statically checked, with some inspiration from Vault. The error handling thing I'm not too clear on how to fix, but sum types looks good.
<ski_> limitations on dynamic extent ?
<ski_> or, things like : can't be NULL, etc ?
<schlick> Basically pointers are only lagitimatly used for a few things.
<ski_> dynamically allocated structures
<schlick> If you make each thing into a type, you can avoid almost all the problems. Most of the checking is really simple. For instance, some of them should only work with the assignment operator. I mean, even I can follow that.
<ski_> pointer to "current" value
<ski_> output arguments
<schlick> Most of them are used for what references are in pointer-free languages. You can look at a lot of them from that point of view. The only one you should be doing raw math on is array indexes, which involve complex checking I'm not sure how to implement, but I am pretty sure they need their own type.
<ski_> yes
<ski_> ragged arrays ?
<ski_> or rectangular ?
<schlick> The only really nasty checking I've noticed with a sane subset of C would be the array indexes and malloc'ed memory. Enforcing "will it be handled right (not just avoid overflows) for all inputs" would be high magic, but it is apparently doable in things like Epigram.
<ski_> actually, when i say 'pointers' i usually mean 'references' .. the pointer math stuff is very seldom good
<schlick> As for ragged or rectangular, I'll claim stupidity here. To me, as far as I know, there's just a block of ram on the stack. It's got a start and a end. You can have one or more indexes into it.
<ski_> C has two different concepts of array
<ski_> the first, which has weak support, includes size in the type
<ski_> the second, is used through pointers (malloced arrays)
<ski_> trouble is one can't have a dynamically allocated array, of first kind
<schlick> I think the first kind is my concept of a array.
<schlick> You can do almost anything with a malloced block of ram.
<schlick> Including blow both legs off and a arm. ;)
Snark has joined #ocaml
<ski_> right
<ski_> but there's a statically typed concept of array screaming to come out of malloc
<schlick> And that's called a ragged array?
<ski_> no
<ski_> ragged arrays can only be fully statically typed, using dependent types
<ski_> ragged arrays is like a two dimensional array of the days of the year
<ski_> 12 rows, one for each month
<ski_> and we want no extraneous elements for "unused" days
<ski_> that can be partly done as an array of 12 elements, being arrays of dynamically known size
<ski_> or, dependently, as an array of 12 elements, being arrays of size f(i) where i is the index, and f is a user-function giving length of month
<schlick> See, this is why I need to get this dependent types thing.
<ski_> hehe
<ski_> i suggest getting ordinary FP, first
<schlick> I have a bad feeling it won't integrate well with Side Effect Oriented programming though. :P [kidding]
<ski_> there are issues, yes .. this advanced type-stuff has mostly been tried (yet) with (fully or mostly) pure FP langs .. but i think some things at least can arry over
<ski_> s/arry/carry/
<schlick> Well, I know functional programming, at least to the extent of using Lisp and some things like it. That doesn't help much with the types thing though.
<ski_> oh sorry
<ski_> i should have said, statically typed FP
<ski_> :)
<ski_> anyway, i have to leave in a few minutes
<ski_> maybe we could continue discussing later, if you like ..
<schlick> One thing that sorta confuses me about ML and what little Haskell I've looked at is the missing parenthesis. And no, I'm not kidding.
<ski_> that's "just" a syntax issue
<schlick> I have trouble figuring out what's going on. It will make it easier to sell to C programmers though, who frequently bitch about "Lots of Irritating Silly Parenthesis"
<schlick> I think my brain sort of sorts and collapses the parenthesis. Makes it easier for me to tell what happens first, and what pieces go with what.
<schlick> I'll probably be around till I get chased off. This is the only channel that seems to have people interested in mass bug killing. :P I like it here for that reason.
<schlick> I've got more pointers to interesting stuff here and on #osdev than anywhere else.
<schlick> #osdev is grumpy though.
<ski_> heh, ok
<ski_> prolly cya later, then
<schlick> Take care. Thanks for talking with me.
Snark has quit ["Leaving"]
pango_ has joined #ocaml
* schlick waves at pango.
<schlick> Hey pango, if you're there, thanks for the BitC thing, it is relevent and interesting.
pango has quit [Read error: 110 (Connection timed out)]
shirogane has quit [Read error: 104 (Connection reset by peer)]
Skal has quit [Connection timed out]
Skal has joined #ocaml
bluestorm has quit ["Leaving"]
Snark has joined #ocaml
Smerdyakov has quit ["Leaving"]
vodka-goo has joined #ocaml
schlick has quit [Remote closed the connection]
Snark has quit [Read error: 110 (Connection timed out)]
schlick has joined #ocaml
schlick has left #ocaml []
schlick has joined #ocaml
Snark has joined #ocaml
Submarine has joined #ocaml
vodka-goo has quit ["Connection reset by by pear"]
pango_ has quit [Remote closed the connection]
pango has joined #ocaml
ramkrsna has joined #ocaml
gim has quit []
ski has joined #ocaml
_fab has joined #ocaml
ppsmimou has joined #ocaml
revision17_ has joined #ocaml
Submarine has quit [Nick collision from services.]
Submarine_ has joined #ocaml
Submarine_ has quit [Remote closed the connection]
pingoo has joined #ocaml
Revision17 has quit [Read error: 110 (Connection timed out)]
__mattam__ is now known as mattam
ski has quit ["NMI"]
ski has joined #ocaml
Schmurtz has quit [Remote closed the connection]
Maledict has joined #ocaml
Schmurtz has joined #ocaml
joshcryer has joined #ocaml
<ulfdoz_> Is there some generalised SQL-database-interface, e.g. like ODBC, for ocaml? I found a library special on postgresql, but I want it for different databases.
<ppsmimou> there's something called dbi I think
<pingoo> anyone tried dbi by the way ?
<pingoo> is it a wrapper on perl stuff ? how difficult is it to get running ? does it support multithreaded caml apps ? (mysql doesn't, that's why I'm looking for something else)
bzzbzz has quit ["leaving"]
<ppsmimou> pingoo: it's a frontend on various backends if I remember well
<ppsmimou> so it uses ocaml-mysl and won't be multithreaded if ocaml-mysql isn't
pingoo is now known as vodka-goo
Mozillion has joined #ocaml
__DL__ has joined #ocaml
Maledict has quit ["a si biri mellu"]
mattam has quit [Connection reset by peer]
__mattam__ has joined #ocaml
weel has joined #ocaml
__DL__ has quit [Remote closed the connection]
__DL__ has joined #ocaml
__DL__ has quit [Remote closed the connection]
ramkrsna has quit [Remote closed the connection]
inkedmn has quit [Remote closed the connection]
inkedmn_ has joined #ocaml
ppsmimou has quit ["Leaving"]
ppsmimou has joined #ocaml
batdog|gone is now known as batdog
__DL__ has joined #ocaml
malc_ has joined #ocaml
Raziel has quit ["Yo soy goma. Tú eres cola."]
weel_ has joined #ocaml
weel has quit [Read error: 110 (Connection timed out)]
batdog has quit [Read error: 104 (Connection reset by peer)]
batdog has joined #ocaml
vodka-goo has quit ["Leaving"]
joshcryer has quit [Connection timed out]
Smerdyakov has joined #ocaml
ppsmimou has quit ["Leaving"]
gim has joined #ocaml
Submarine has joined #ocaml
malc__ has joined #ocaml
malc_ has quit [Read error: 110 (Connection timed out)]
inkedmn_ has quit [Remote closed the connection]
inkedmn has joined #ocaml
weel_ has quit [Read error: 110 (Connection timed out)]
weel has joined #ocaml
vodka-goo has joined #ocaml
smimou has joined #ocaml
Maledict has joined #ocaml
Mozillion has quit ["Client exiting"]
gim has quit []
pango has quit ["Leaving"]
pango has joined #ocaml
rgrig has joined #ocaml
quamaretto has quit [Connection timed out]
weel has quit ["Leaving"]
rgrig has left #ocaml []
<schlick> Looking at the OCaml manual. Am I understanding right the only place you have to specify types is for functions external code will call?
<ski> in module interfaces, too
<ski> and in class definitions
<schlick> Hmm. Module interfaces are intended for separate compilation too, right?
<ski> (i.e. method and instance variable types, in latter)
<ski> not only
<schlick> Namespace restriction for separatly developed bits too...
<ski> also functors
<ski> (i.e. module functions)
<schlick> Hmm.
<ski> see e.g. Set.Make
<schlick> Well, the part I'm mystified by is exactly how it knows what the type of something is without making a mistake. I haven't seen any mistakes made by the type inference implementation shown. It seems reasonably obvious to me that you'd /have/ to specify the type on externally available functions, since you can't see the other code to see how it will be used.
<schlick> I'm guessing so long as you did that it should be able to figure it out, if it doesn't allow unsafe autotragic conversions like between numbers and strings.
<ski> it takes a module containing a type and an comparision over that type, and returns a module of sets specialized to elements of that type
<schlick> What does? Set.Make?
<ski> it create Set modules
<schlick> Oh.
<ski> specilized
<ski> specialized
<schlick> Still trying to figure the type inference magic out, more generally, than specific examples.
<vodka-goo> only first-order unification
<schlick> There's obviously some general trick it uses. As far as I can tell it looks through the code to see what you're doing with a piece of data, and assumes the most general type that can do all that.
malc__ has left #ocaml []
__DL__ has quit [Remote closed the connection]
<schlick> But if you can't see all the code, I'd think you'd have to specify it. Which means you'd have to do it on externally available functions.
<schlick> Am I understanding wrong?
__DL__ has joined #ocaml
<ski> more or less what you say, yes
<ski> for other modules, you assume their interface
<ski> the interface is checked when that module is checked
<schlick> There is some notion of binary-only linking, like a library, I assume?
<ski> the only time something is taken on faith, and not checked, is foreign language calls (C)
<schlick> i.e. one you may not have the source code to
<ski> yes, sure, you have interface even if not source
* schlick nods. External code in other languages would always be a problem.
<ski> *-mli
<ski> *.mli
<schlick> Is there any way it can avoid catching a error, provided you specify the externally available interfaces? It seems like it should be safe given that.
<schlick> A type error that is.
Raziel has joined #ocaml
<schlick> I've dredged up some examples where it can't figure out the type but apparently it just gives a error there, and supposedly you never need to write that sort of thing (e.g. the "absorb" function in the Standard ML 97 Tutorial).
<ski> well, maybe if you lie in the interface
<schlick> Hmm... How would that work? You change the interface after compiling the library?
<ski> (hm, actually, interfaces are also compiled)
<schlick> To make the two not match you'd have to swap one out after compiling, though, right?
<ski> so, i think it's hard to change the compiled interface, without it detecting some possible crc error, or something
<ski> (possibly it's md5 digested, or something, not sure)
<ski> swap one what out ?
<schlick> If you have a library file and a interface file, that are expected to match, the type checker would make sure they matched at compile time, but after that you could swap one out. Doing so would be very silly (on the order of opening the library and scrambling its contents in a hex editor), not something accidental.
<ski> linker checks compiled interfaces, i think
* schlick nods. "In any case it's not a problem with type inference messing up."
<schlick> Mostly trying to figure out how to understand what's going on when it infers a type, and figure out if it's always safe to do so.
<ski> also, it's possible it uses some crc so you can't mess up with contents without it noticing it, in any easy way
bluestorm has joined #ocaml
<schlick> If this seems silly, please understand I've never used a language with type inference.
<ski> hm
<schlick> So it's one of those things that seems 'magical' at this point.
<ski> there's another source of type problems
<ski> persistance and also passing stuff over pipes/network/something
<ski> don't recall how that's handled
<ski> s/source/potential source/
<schlick> I'd think the functions that read from files or the network would have to make sure they were reading in things that would fit in the type (i.e. the type checker would catch errors there when compiling those functions). Right?
<ski> iirc one could currently only pass stuff from one program instance to another instance of same program (whether on same machine or not), but i could recall wrong
<ski> hm
<Submarine> currently, marshalling is essentially untyped
<Submarine> you need something external to the type system to make marshalling safe
<schlick> Marshalling is IPC?
<ski> actually, wasn't it marshalling of functions which had this extra restriction ?
<ski> Marshalling is also known as (de/)pickling and (de/)serializing
<schlick> Oh. Dumping the state of a object to a file or restoring it? As in Python?
<schlick> Without manually describing how to save/restore that state, that is.
<ski> yes
<ski> only you can marshall to another process, not necessarily to a file, iirc
<schlick> I see.
<schlick> The problem still being that the other end has no clue what format the data should be in, since the entire code involved can't be seen from either end.
<ski> m
<schlick> Or am I still not getting it?
<ski> you are correct, i think
<schlick> Hmm, interesting.
<schlick> I take it Haskell does type inference too?
<ski> yes
<ski> most mainstream (as far as that goes :) statically typed FP langs do
<ski> the MLs have more powerful module systems, though
<schlick> I don't know of any other ("fancy") statically typed languages besides Epigram, the MLs, and Haskell.
<schlick> There's a lot of MLs for some reason (guess because it's the oldest).
Submarine has quit ["in Soviet Russia, Céline Dion owns you"]
<schlick> Are there others?
<ski> Clean (quite similar to haskell, but with an interesting "uniqueness" type system, which is used for another approach to IO)
<ski> Mercury is a logic programming language, which also has support for FP
<schlick> I knew of it (seems to be Uberprolog), but didn't know Mercury did thorough type checking.
<ski> Miranda is like an old and proprietary version of Haskell (don't know if anyone uses it anymore)
<ski> it does
<ski> it's type-system is quite similar to haskells
<schlick> Is it's way of handling I/O the same as Clean? I think it does the world to world thing we talked about yesterday.
<schlick> Hmm, good. Was planning on taking on Mercury at some point in the future. Least that keeps the number of languages to look at down.
<ski> yes, it's i/o is similar to clean
<ski> s/'//
<schlick> Cool. Looks like I've homed in on all the languages I need to learn about then. I missed a few because I didn't realize type checking was of much practical value. None of the popular languages seemed to do anything useful with it. Now it seems like it wouldn't be too useful if you didn't have it.
<ski> type checking can be used for lotsa stuff
<schlick> Still a little stumped at why some of these aren't more popular. Given how bad things are with C and C++ security and stability wise it seems like if there was a known better alternative people would have fled to it by now. Then again, I guess ACLs vs capabilities are in the same boat... Kinda makes you wonder why if somthing was figured out over 30 years ago people aren't using it.
<schlick> somthing was figured out over 30 years ago people aren't using it.
<ski> iirc, there are type-based analyses that can guarrantee the absense of deadlock in concurrent code, and such things :)
<ski> sadly, most ppl in industry aren't choosing langs much on technical merits
<schlick> Yes, apparently dependent types can check for everything a theorem prover or model checker can, without the difficulty or the overhead. Apparently generating counter examples for real world situations still takes a model checker, but if you could avoid model checking anything but, say, a modularly defined piece of code, it'd probably make the model checking doable.
<schlick> What other merits are there? Well, I guess readability is a human factor, but, honestly, other than VB and COBOL most languages aren't too readable (and COBOL seems to have issues with not being able to do much without writing LOTS of code).
<schlick> Most popular ones anyway...
<schlick> Personally I find Eiffel pretty readable.
<dylan> schlick: I dunno.. APL, J, K... are pretty unreadable.
<schlick> Yeah, but nobody uses those in industry. :P
<dylan> True. :)
mercury^ has joined #ocaml
<dylan> I'm in odd frame of mind today, writing a dataflow language similar to Homespring (a joke language).
<ski> dataflow ? like Lucid ?
<dylan> The primary means of... execution is sending squirells between trees.
<schlick> I've about come to the possibly crazy conclusion that programming is ahead of math. "Normal" mathematics still thinks excessive terseness is a good quality, especially when naming variables and functions meaningless stuff like "a". Flow control is limited to sequence and ranged loops, no branches. It looks like on the most basic level a programming language is just a math notation.
<schlick> most basic level a programming language is just a math notation.
<schlick> Though if you'd told me that in highschool you might have scared me off of programming because I thought I didn't like math. :P
<ski> schlick : size of available pool of programmers to choos from, what rest of programming team know, what managers think is the current hype, what majority or authority or collegues say, how big libs there are, how well it interoperates with other langs and legacy code and database, ...
<schlick> APL is what math turned into a fully functional programming language would look like. The end result is widely considered to be bad. :P
<mercury^> hi, when I try to compile a file that's first none quoted non empty line begins with "let" ocamlopt (ocamlc does so too) tells me:
<mercury^> File "Recursion.mli", line 3, characters 0-3:
<mercury^> Syntax error
<flux__> schlick, what do you mean no branches? f(x) = 4, if x = 0, otherwise 5? you've seen them too I guess.
<ski> schlick : i agree that many practicioners of math seems to use bad style and syntax .. thought generally the concepts are often more powerful than usual prog concepts, i think, though not as complex/large/formal
<flux__> schlick, programs usually have this feature that they need to be interpreted in certain order, while mathematics doesn't have this limitation
<schlick> ski: I guess some of those are valid. If a company wants programmers for a better language, they could advertise, and people would learn it if enough people wanted them, I'm sure. Hype/colleges don't seem to override "what works best". The standard library thing is a genuine issue. I think it's probably the only valid reason for using Java.
<schlick> Most things seem to interoperate with C and C++, so you should be able to use that as base glue.
<flux__> I agree, Java's best feature is its comprehensive standard library
<flux__> mercury^, can you put the file to some paste site?
<flux__> (or web otherwise)
<schlick> flux__: The way I figure it, math's job is to represent concepts. Sometimes the order of what happens is absolutely /vital/ (math notation recognizes this to some extent with parenthesis). I'm not aware of any math notation for "if".
Smerdyakov has quit [Read error: 110 (Connection timed out)]
<flux__> schlick, math notation is what you say it is.
<flux__> schlick, mathematics definitely has a concept of 'if'
<ski> programs have the restriction to be computable
Smerdyakov has joined #ocaml
<schlick> Naa, math notation is what happens when you open a binary file, or write programs while under the influence of mind altering substances. ;)
<flux__> ski, and preferably in practice too, not just in theory ;)
<ski> (mercury^ : 'none quoted' ?)
<schlick> [open a binary file in a text editor]
<mercury^> ski, yeah
<ski> there are separate concepts 'if'
<ski> one is 'if-then-else'-expression
<ski> another is 'if-then'-logic-formula
<ski> those are not same
<schlick> flux__: I /have/ heard that mathematics used to be done entirely in prose, in the western middle ages. I think that's probably going too far the other direction, but it makes you wonder if it wouldn't be the better of the two directions to err in.
<flux__> ski, what is 'if then' really?
<ski> (mercury^ : what does it mean ?)
<ski> flux__ : implication
<flux__> ski, ah yes, if we're dealing with truth values
<mercury^> ski, the first line is:
<mercury^> let read_whole_chan chan =
<flux__> ski, but I think even -> has 'else'
<flux__> 'else true'
<ski> flux__ : or definitions, and theorems, etc
<flux__> ok, now that's a better example
<schlick> flux__: The "if" I was referring to was branches on conditions. There is no math notation I know of that says "if <math expression here> then <do some more math> else <do this math here>"
<schlick> There is notation for loops over ranges however.
<schlick> And seqence.
<flux__> a theorem may say 'if number is divideble by two, then..' but nothing about the other case, although we could consider "else this theorem says nothing about it" :)
<mercury^> schlick: you can easily express that with common math notation
<schlick> mercury^: What's it look like?
<mercury^> depends on the specific thing you want to express
Skal has quit [Remote closed the connection]
<schlick> So there's no if/then/else symbols?
<mercury^> no
<schlick> That's the thing I was referring to.
<mercury^> but there's ∀, ∃, etc. and |
<mercury^> those are more powerful concepts
<ski> (if f(x) = 0 then sin else cos)(x)
* ski is bothered that math ppl don't use much anonymous functions (at least from what i know)
<mercury^> they do
<mercury^> depends on what branch of math you're currently talking about
<ski> D(y |-> y^3)(x) = 3*x^2
<ski> D(y |-> y^3) = x |-> 3*x^2
<schlick> Hmm, never have seen the upside down A or reversed E or pipe in math. I'm sure they're there. I need to memorize that math chart I suppose.
<ski> something like that
<ski> should be common in analysis, one'd think
<mercury^> linear algebra is "sufficient" for you to encounter anonymous functions
<mercury^> any idea on my compilation problem?
<ski> hm
<ski> err
<schlick> No formal training here. Just me, the internet, a few books, and me trying to translate the math-ish gobbltygook into "plain English" so I can understand it where I run into it. Basically the problem I had with math originally was nobody showed us how to use it to do anything until highschool. Math was just playing calculator.
<ski> why are you putting a let in an interface
<mercury^> ski: I'm currently learning ocaml, the line is from a tutorial
<ski> mercury^ : maybe you wanted Recursion.ml ?
<schlick> Programming I came at from the point of view of "it's bastardized English to tell the machine to do what you want". That's a lot less scary. I can read quite well. As of a year or two ago I came to the conclusion that human language (without the inpreciseness) = math = programming.
<mercury^> is that a library I have to open before using let?
<ski> no
<ski> just maybe you wanted to name your file Recursion.ml instead of Recursion.mli
<mercury^> ah, seems to help with the let at least
<mercury^> ok, worked now :)
<mercury^> mli is stuff for the interpreter to be loaded?
<ski> mli is for interfaces for compilation units
<mercury^> ok, thanks
<ski> you state type signatures of exported stuff, in it
<mercury^> oh, and btw: is there a reason for ocaml not to have typeclasses?
Snark has quit [Read error: 104 (Connection reset by peer)]
<schlick> Thanks for clarifying ski, and telling me about the existance of some math symbols for if/then/else mercury^. Sorry if I scared you all with my mathematical ineptness. At least I'm trying. :P
<mercury^> schlick: the symbols are showed you aren't equivalent to if/then/else
Submarine has joined #ocaml
<schlick> mercury^ you said they could be used to express the same concepts.
<mercury^> right
<schlick> That's all I'm really concerned with.
<ski> in other way
<ski> just like one can declare local functions, instead of using anonymous function expressions
<schlick> So long as I have my magic decoder ring to read some of the equations I should be able to survive. The rest is just the concepts (which I have to wrestle with for a while but haven't run into anything I simply can't grasp, at least when given a example), and playing calculator.
<schlick> ski: I think if they can express the same concepts it should be roughly equivalent. Two things can look terribly different, but, for instance, coming at it from the programming = english = math point of view, most well formed flow control can be transformed around a lot like algebra. And of course straight line code /is/ algebra (as far as I can tell anyway).
Snark has joined #ocaml
<ski> schlick : yes, though some froms can be better for particular purposes, than others
<schlick> True. So long as it can be safely/correctly converted between forms it should be doable though.
<ski> referentially opaque expressions are harder to convert, though
<schlick> I suppose. I'm not sure what that term means. If it means 'you don't know what's going on inside the expression' then yes, you couldn't do any transformations that involved breaking it into pieces.
Bigb[a]ng is now known as Bigbang
<ski> referentially opaque expressions don't follow the law of substituting equals for equals
<schlick> Meaning you couldn't replace the expression with the value it resolved to (assuming it was fully computable)?
<ski> e.g. nat. lang. "Paul doesn't know the morning star is the same as the evening star"
<ski> right
<ski> generally, the expression has some kind of 'side-effect'
<ski> 'linguistic side-effects' in the case of natural language (see Chung-Chieh Shan)
<schlick> That could happen if dealing with external code. Generally speaking that's not a problem I can forsee having to deal with, since obviously if it's external it's already compiled, so you can't transform it anyway.
<ski> '(computational) side-effects' in case of programming language
* schlick nods. "You'd be read/writing hardware or external code."
<ski> this is a language issue
<schlick> You don't want to avoid the former, or change it, you can't change the latter by definition.
<ski> well
<ski> even if one can't transform external stuff themselves ..
<schlick> Guess I should say reading/writing I/O hardware.
<ski> .. one might want to reorder stuff which calls external things
<ski> and do that reordering safely
<schlick> This is true.
<schlick> To do it safely you'd have to know what was going on in those proceedures though.
<ski> also, sometimes one can factor, so only performing something once instead of many times (or zero times instead of once)
<schlick> Which would break down to keeping the source around.
<ski> not necessarily
Mozillion has joined #ocaml
<schlick> You'd have to preserve enough meaning to relate input and output at the very least, even if you didn't retain /everything/ that went on.
<ski> if you knew what kind of effects they could you, you could e.g. wrap them in a similar monad (or effect system), in the language
<schlick> Probably external calls too, which you'd have to crawl along.
<ski> in worst case, a "sin-bin" monad for "the rest of the effects" like IO monad in haskell
<ski> though, generally, IO can't be reordered at all, of course
<ski> still, some other parts of your program could possibly be reordered, and to do that, it'd be good to know which parts can't be reordered, so one only changes in safe wways
* schlick nods. "I'm not sure making such a transformer is practical though. It would assume you had said information for everything you called directly or indirectly, which isn't realistic, what with other languages, remote systems, and whatnot."
<schlick> You'd probably have to just treat external code as atomic. I don't know of any compiler that does otherwise. I'm not really sure how a real compiler would work if it didn't handle it that way.
<schlick> I do know of a certain developer on #osdev who hasn't figured out this problem yet.
<ski> you can appoximate
<ski> it's food for thought, anyway :)
<schlick> True.
<schlick> I think partly due to my lack of "academic" background, and partly due to constant criticism of anybody that attempts to statically check anything as being "impractical", I tend to focus on "how do I do X on a real world system" and "how does that trick work?"
quamaretto has joined #ocaml
<ski> (critisim by whom ? :)
<ski> s//s/
<schlick> ski: Try this some time...
<schlick> ski: Go into a arbitrary programming channel people are active in. Tell them you're interested in trying to check for bugs statically. I predict one of two responces will occur.
<schlick> ski: "Guess you've never heard of Godel's incompleteness theorem!" or "Guess you've never heard of the halting problem!"
<ski> hehe
<ski> type systems step around that, so to speak
<ski> by appoximation
<schlick> ski: Analogy: While driving carefully, someone could swerve into my lane, hitting me and killing me instantly. THEREFORE, I may as well drive while intoxicated, since I could die either way.
<schlick> ski: Most people apparently have difficulty spotting the problem in this line of logic.
<ski> right
<ski> the trouble is that the well-known statically typed langs all have bad and weak type-systems
<schlick> ski: I'm /perfectly/ happy with having to hold the compiler's hand and lead it along, so long as the checks are sound, even if they aren't complete.
<ski> requiring casting and stuff
<ski> right
<schlick> ski: It would be very nice if it would show me input that would violate my assumptions, but even if not, I'd take something that was sound over something that wasn't. Besides, it looks like doing both is possible.
<ski> # let head (h::t) = h;;
<ski> Warning: this pattern-matching is not exhaustive.
<ski> Here is an example of a value that is not matched:
<ski> []
<ski> val head : 'a list -> 'a = <fun>
<schlick> Sounds good to me.
<ski> there's a concept named 'type error slicing'
<schlick> Now all I'm trying to do is figure out exactly how hardcore you can go on it that way, and still live in the real world. It's one reason Epigram looks really neat to me.
<flux__> ski, however, the same output is given when you write let (a::b) = [1]
<schlick> Though I'm going to have to take baby steps to make my gray matter handle from getting from point A to point B. I just hope there aren't too many steps, and I don't veer off course too much.
<ski> that is about finding (and presenting to user) all the exact relevant places contributing to a type error, instead of just the first place the type checker notices the error
<flux__> because that problem is out of the domain of typing problems (non-dependant types anyway)
<ski> yes
<flux__> I wouldn't mind if I could case-by-case remove that warning
<flux__> it still could have the runtime check in place though ;)
<flux__> because what happens here is that I will need to use a clumsier syntax to do the same thing the program would otherwise do: throw an exception
<ski> also, there's a style sometimes called 'typeful programming' where one programs in a way as to increase chances of type system noticing possible trouble (i.e. turning errors into type errors)
<schlick> ski: Recommended reading on that?
<flux__> like wrapping integers for different things into their own types?
<flux__> btw, is there a camlp4-extension that would create de-wrapping functions for such types?-)
<Mozillion> speaking of camlp4, I've been struggling with a Grammar for the entire day and still got troubles with it
<Mozillion> the trouble is probably the grammar not being nice and me, not knowing Grammar well enough
<Mozillion> the problem*
<Mozillion> anyone an idea how to parse something like: exp -> exp.ident in such a way that it doesn't loop? :)
<ski> isn't that left-recursion ?
<Mozillion> yeah
<ski> bottom-up parsing ?
<Mozillion> only that rule.. the rest is left linear
<ski> ocamlyacc ?
<Mozillion> you think it's better suited for that?
<ski> i'm wondering which you use ?
<ski> bottom-up or top-down ?
<Mozillion> thing is, my colleague already has implemented something using ocamlp4/Grammar
<Mozillion> I've put the grammar on http://rafb.net/paste/results/GSbiS538.html
<Mozillion> well the rest is top down
<schlick> ski: I was referring to the typeful programming.
<Mozillion> I'm 5 days new to OCaml, so quite a deep dive for me, heh
<ski> can i assume the system your colleague has implemented is top-down ?
<ski> schlick : see the citeseer link
<Mozillion> ski: yes
<ski> ok, so you can prolly not use left-recursion, then
exa has joined #ocaml
<Mozillion> no, I have to transform the rule somehow
<ski> is EXP -> CIDENT -> EXP the only left-(mutually-)recursive loop ?
<Mozillion> this is in the form that it's intuitively clear
<ski> right
<Mozillion> AFAIK, yes
<schlick> Magic. It's all magic. :P
<ski> are the parens syntactical ?
<Mozillion> yes
<schlick> ski: Thanks. Off to go beat my head against stuff a while more.
<Mozillion> well they are sometimes optional when the thing that is contained within it isn't there, but that's a detail
<ski> CIDENT ::= IDENT | EXP.CIDENT
<ski> so
_DL_ has joined #ocaml
<ski> CIDENT ::= EXPDOT*IDENT | EXP.CIDENT
<ski> EXPDOT ::= EXP.
<ski> or something
<ski> um
<ski> CIDENT ::= EXPDOT*IDENT
<Mozillion> ah yes
<ski> sequence of EXPs and dots, followed by final IDENT
<ski> hm
<Mozillion> so that would become cident : [ [ OPT [ LIST0 exp SEP "."; "." ]; ident ] ]
<ski> EXP ::= CIDENT(EXP*)
<ski> need something here, too, i think
<ski> hm
mercury^ has quit []
<ski> 'OPT' ?
<Mozillion> yes it's unguarded now.. parsing of exp can go straight to exp, and so on
<Mozillion> ski: can it be done without OPT ?
<ski> i'm just guessing what OPT is
<ski> but, doesn't LIST0 handle zero elements ?
<Mozillion> yes, but then you're left with the dot
<ski> hm
<ski> right
SnarkBoojum has joined #ocaml
<ski> i guess i was thinking of kleene star for a sequence of exp and dot
Snark has quit [Nick collision from services.]
<ski> hm
SnarkBoojum is now known as Snark
<ski> won't that OPT and stuff above allow parsing something of form ".IDENT" ?
<Mozillion> well you eiter have { exp. } or you don't
<ski> [LIST0 [exp; "."]; ident]
<ski> ?
<Mozillion> hmm.. that's possible too I think!
<ski> that's the obvious corresponding ..
<Mozillion> yeah
<ski> so is your colleague's code translated into this camlp4 grammar thing ?
<ski> EXP ::= EXPDOT*IDENT(EXP*)
<ski> so
<Mozillion> will that work?
<ski> if still left-recursion :)
<Mozillion> I mean.. EXPDOT goes to EXP directly
<Mozillion> yes
<ski> s/if //
<ski> but
<ski> now we see directly that EXP is either many other alternatives, or it is
<ski> EXP ::= EXP.EXPDOT*IDENT(EXP*)
<ski> right ?
<ski> (just expanded first part of the EXPDOT*)
<Mozillion> | IDENT(EXP*)
<Mozillion> yes
shawn_ has joined #ocaml
<ski> so
<ski> we make two nonterminals EXP, one for full EXP, and one for "atomic" expr
<ski> what to call them ?
<ski> EXP0,EXP ?
<ski> EXP,AEXP ?
<Mozillion> both fine
__DL__ has quit [Read error: 110 (Connection timed out)]
<ski> hm, think second requires least renaming
<ski> EXP ::= AEXP
<ski> erm
<ski> EXP ::= AEXP EXPCONT*
<Mozillion> right
<ski> hm, slightly more complicated, possibly
* ski ponders how to recreate CIDENT, to some degree
<Mozillion> CIDENT is only used on 2 places.. it can be removed
<ski> hm, maybe we don't need to left-factor
<ski> EXP ::= AEXP
<ski> | AEXP EXPCONT
<ski> EXPCONT ::= .EXP.IDENT(EXP*)
<ski> | .EXP EXPCONT
<ski> something like that
<ski> then all the old EXP branches now belong to AEXP, instead, but still call EXP
<ski> (since no more left-recursion)
<ski> erm
<ski> actually
<ski> | EXP EXP
<ski> is left-recursion
<ski> so you need to transform that out, too
<Mozillion> do you need that .EXP at the start of both EXPCONT rules?
<ski> it could be factored, yes
rillig has joined #ocaml
<Mozillion> no, I think not
<ski> what ?
<Mozillion> that would of course create EXPCONT ::= EXPCONT
<ski> rather
<ski> EXPCONT ::= .EXP EXPCONTB
Skal has joined #ocaml
<ski> EXPCONTB ::= .IDENT(EXP*)
<Mozillion> hmm?
<ski> | EXPCONT
<ski> no ?
<Mozillion> yes
<ski> how should something of form "EXP EXP . EXP . IDENT(EXP*)" be parsed ?
<ski> or "EXP EXP . EXP EXP. IDENT(EXP*)" ?
<ski> etc
<ski> if you decide on a precedence, then i think you need one more EXP nonterminal
<Mozillion> note that there can be no spaces around the dot
<Mozillion> so.. heh, what do you mean?
<Mozillion> EXP chaining is ala lambda-calc left-assoc
<ski> so ((EXP EXP).(EXP EXP).IDENT(EXP*)) ?
<ski> in nesting, i mean
<Mozillion> yes
<ski> hm, what to name the new nonterm ?
<Mozillion> it has something to do with refinement
<ski> EXP2 ?
<Mozillion> heh.. why not ;)
<ski> EXP2 ::= AEXP EXP2CONT
<ski> EXP2CONT ::=
<ski> | EXP2 EXP2CONT
<ski> hm
<Mozillion> huh?
<ski> will that do ?
<Mozillion> nothing behind the ::= ?
<ski> epsilon, however you write it ?
<ski> empty
<ski> EXP2 is a sequence of at least one AEXP
<ski> hm
<ski> EXP2 in second branch should be AEXP, i think
* ski tries to recall details of how this was done
<Mozillion> me too
<ski> uhrm
<ski> why don't we use AEXP* ?
<ski> isn't that simpler ?
<ski> EXP2 ::= AEXP AEXP*
<Mozillion> yes
<ski> or
<ski> EXP2 ::= AEXP+
<ski> if you have that
<Mozillion> LIST1
<ski> in underlying grammar
<Mozillion> this comes from EXP ::= EXP EXP2
<Mozillion> ... right?
<ski> yes
<ski> so, EXP should call EXP2 and not AEXP
<Mozillion> I've lost my AEXP somewhere
<ski> EXP ::= EXP2
<ski> | EXP2 DOTEXP* IDENT(EXP*)
<ski> DOTEXP ::= .EXP2
<Mozillion> DOTEXP was dead
<ski> hm, s/DOTEXP/DOTEXP2/
<Mozillion> not that an IDENT is also an EXP
<ski> revived it :)
<Mozillion> I was adapting my grammar file, but now I'm confused
<ski> hm
<Mozillion> ha! we never defined AEXP.. hehe, I wasn't mistaken
<ski> rename old EXP to AEXP
<ski> and remove the left-rec rules
<ski> (but don't change the recursive calls to AEXP)
<ski> hm, yes
<ski> i'm forgetting IDENT as EXP
<ski> or rather
<ski> IDENT(EXP*) as EXP
<Mozillion> yeah
<ski> or am i ?
<ski> EXP ::= EXP2
<ski> | EXP2 DOTEXP*.IDENT(EXP*)
<Mozillion> heh, wanna see the local mess?
<ski> does that work ?
<ski> of course, the parse trees are going to look weird, so you maybe might want to recify them back to fit the original grammar, to get better recursion patterns over them
<ski> local mess ?
<Mozillion> http://rafb.net/paste/results/LHoKiD65.html (kinda lost track)
<schlick> ski: Something just occured to me. What happens if you tried to do type inference and a operator is overloaded?
<pango> schlick: ocaml doesn't support overloading
<ski> Mozillion : something like that, i think
<Mozillion> ah.. that is what you meant, ok.. lemme merge it
<schlick> pango: Is this the reason why?
<ski> type inference is harder with overloaded .. Mercury has overloading though .. though combining it with common use of currying is problematic (in pragmatic sense, less helpful errors)
<pango> schlick: have a look at gcaml http://www.yl.is.s.u-tokyo.ac.jp/~furuse/gcaml/... It's only experimental however
<ski> Mozillion : i'm not sure if your system there supports having more than one thing under '*', if so, you could remove DOTEXP2
Maledict has quit ["a si biri mellu"]
Bigbang is now known as Bigb[a]ng
<Mozillion> ski: LIST0 [".", exp]
cp has quit [Connection timed out]
<schlick> Here's the example I dreamed up when I realized there might be a problem:
<schlick> string_to_display = "Result: " & a_number
<schlick> Assuming & ment "logically and" for numbers, and "concatinate" for strings, it seems like what would occur is you'd get a error the first time you tried to use it in a 'invalid' way. In this case, probably at the string use, since you most likely did math first.
<schlick> Assume = is the evil assignment operator. :P
<Mozillion> ski: it's your suggestion, it would work fine
<schlick> So is my guess right? It's doable, but the place where the type error is reported may not be where you'd think it should be?
<ski> possibly
<ski> type error slicing though aims to report all possible (and relevant) places which contribute to the error
<ski> i don't know if there's any work on combining such with overloading, though
<schlick> I don't really mind the idea of losing overloading but I wonder what a intuitive notation for non-math things would be. I guess "><" could be a decent concatination operator.
<pango> # let plus = generic (+) | (+.);;
<pango> val plus : [| int -> int -> int
<pango> | float -> float -> float |] = <generic>
<ski> # (^);;
<ski> - : string -> string -> string = <fun>
<ski> # (@);;
<ski> - : 'a list -> 'a list -> 'a list = <fun>
<ski> Prelude> :t (++)
_DL_ has quit [Remote closed the connection]
<ski> (++) :: [a] -> [a] -> [a]
<ski> (last was haskell)
<schlick> Hmm. ^ wouldn't have been my pick, but ++ looks ok. Any thoughts on the matter? I guess overloading might be confusing in general. I remember learning some Cherokee one summer (we were on vacation and stopped by a reservation where they had some books on it). It's sort of like English made sane. There's a one to one relationship between sound and symbol.
<Mozillion> ski: thanks a lot anyway! I'll implement it tomorrow.. have been busy with it for 9 hours now, it's enough
<schlick> From that perspective maybe it's easier to understand source code without overloading, since a certain symbol always means one thing?
<Mozillion> ski: damn... there is a CIDENT in PHRASE
<ski> hm
<Mozillion> almost the same but IDENTS in a list instead of EXPs
<ski> could you factor out from
<ski> | EXP2 DOTEXP2*.IDENT(EXP*)
<ski> ?
<schlick> pango: Any thoughts?
<Mozillion> no.. don't think so
<ski> | CIDENT(EXP*)
<ski> CIDENT ::= EXP2 DOTEXP2*.IDENT
<ski> ?
<ski> how about that ?
<pango> schlick: I don't really miss operators overloading
<Mozillion> | IDENT
<Mozillion> should be added I think.. it's missing now for EXP too
<pango> schlick: ocaml allows to redefine an operator
<pango> # let (+) = Int64.add in 2L + 5L ;;
<pango> - : int64 = 7L
<ski> Mozillion : no
<ski> Mozillion : it wasn't part of EXP, before
<pango> that's not exactly the same thing: you can't have both signatures at the same time
<ski> you can have them in different scopes and namespaces
<Mozillion> ski: it was.. EXP ::= CIDENT(EXP*) and CIDENT ::= IDENT
<ski> also, you can always invent new operator identifiers
<schlick> pango: Yeah, it seems like the redefining would be even more confusing.
<ski> note the (EXP*)
<ski> IDENT(EXP*) is a valid EXP
<schlick> pango: Guess it's probably best to not have the operator overloading.
<ski> IDENT is not a valid EXP
<ski> schlick : redefining is only local
<pango> schlick: guess why ocaml has + for ints and +. for floats, etc...
<Mozillion> true.. but if EXP occurs zero times, the ( ) can be left out
<Mozillion> but that's doable with an OPT [ ]..so doesn't matter IMO
<schlick> ski: That's not as bad as the alternative but I still think it'd result in headscratching a lot of the time.
<ski> # let (++) = (@) in [1;2;3] ++ [4;5];;
<ski> - : int list = [1; 2; 3; 4; 5]
<schlick> pango: I already knew it did but I wasn't really sure why. The syntax looks quite alien to me. It's not a knock against OCaml. The main problem, I think, is I expect that if it's supposed to be a functional language it's supposed to look like Lisp, and if it looks like C it should look a /lot/ like C, and be imperative. ML doesn't really fit those assumptions.
<ski> Mozillion : the old grammar didn't specify that the parens could be left out, then
<ski> Mozillion : in any case, if they can there, then they also can in the new grammar
<Mozillion> ski: I know.. I mentioned it here though... but it doesn't matter IMO
<ski> ML looks like ML :)
<Mozillion> ski: anyway, with the grammar you posted I can't make IDENT(EXP*) either?
<schlick> pango: So, basically, when I saw a lot of odd looking operators it didn't strike me as something to think much about.
<pango> schlick: ocaml is both functional and imperative
<ski> Mozillion : hm
<Mozillion> ski: heh, we DID have that rule somewhere back though :)
<ski> Mozillion : you're right .. need one branch for IDENT(EXP*) in AEXP
<pango> schlick: almost on the same level of efficiency, with specific cases (number crunching code works better if written imperative way, symbolic mangling works better if written functional), because of compiler optimizations
<schlick> pango: True I guess. It looks more C-ish than Lisp-ish, and Lisp isn't 'pure' (at least no flavor I've used). Still it seems like it's more functional than imperative. It doesn't look like anything I'm used to so I can't say, "oh, there's that symbol/grouping, just like in language-X".
<pango> schlick: also, I've read that the Gc adds a slight overhead to mutations (to check for new references from old generation to new), so it's somewhat optimized for functional code
<pango> schlick: I've used (some implementation of) Logo, which is also functional, but doesn't look "lispish", too
<schlick> pango: OCaml's GC is apparently quite good. "Real" stuff I've used in it feels just like C. Can't say the same for Java. Squeak is pretty snappy, but not as fast, and I haven't seen much 'real' in it (the 3-D "Alice" thing probably comes close though). Of course OCaml is "actually compiled" not interpreted bytecode.
<ski> isn't Logo sometimes considered a lisp dialect ?
<schlick> pango: Apparently Logo has been resurrected. It was going out of style as a beginner language back in the mid 80s when I started fiddling with computers. I never learned it. I was a bit shocked to hear some places are teaching it to math students now.
<schlick> ski: It is. It just lopped the parenthesis off, which I find horribly confusing. Apparently most people don't like the 'look' of the parenthesis, but for some reason I find they help me understand things better.
<schlick> ski: Everything is always in the /exact/ same form, and you always know what parts go with what.
<ski> you know how many args each function takes ?
<schlick> backwards think you don't have to and like forth Which would be roughly equivalent otherwise.
<pango> schlick: I learned a version of Logo that was implemented for french micro computers (found in few schools, a while back), and only recently looked at the syntax of the official Logo. official syntax looks much less clean :/
* ski only fiddled for a short while with logo in beginning school, before those 'puters got stolen
<Mozillion> hehe, will have to spend some time showing equivalence tomorrow
<schlick> ski: It's not just defined functions, all operations in Lisp look exactly the same. There's none of the prefix/infix/postfix differentiation, and a distinct lack of 'funny little symbols'. It's sort of the anti-Unix-shell (which borders on considering @#$% a valid command).
<ski> Mozillion : hm, maybe instead
<ski> EXP2DOTCIDENT ::= EXP2 DOTEXP2*.IDENT
<ski> and used that in EXP
<ski> and then
<ski> CIDENT ::= IDENT
<schlick> pango: Have you looked at Pilot? It's been resurrected too. ;)
<ski> | EXP2DOTCIDENT
<schlick> pango: I have a feeling you won't like how it looks.
<ski> and then use CIDENT in PHRASE (so you don't have to have duplicate instances there, at least)
<pango> schlick: correct ;)
<ski> in lisp one don't know how many args each function takes
<ski> i.e. syntax doesn't know
<Mozillion> ski: and also removes the dupliccate of Instance in AEXP, right?
<ski> no
<ski> hm
<schlick> pango: I can't believe people have decided to teach with that. :P I feel sorry for the students. If it had some special feature like making security or error checking or optimization really easy I could see it, but it doesn't seem to have anything going for it, it just looks... arbitrary.
<Mozillion> no you're right.. wouldn't be able to do muliple IDENT(EXP*) then
Snark has quit ["Leaving"]
<ski> it'd think IDENT.IDENT(EXP*) was valid
<schlick> ski: I suppose. Basically Lisp is fairly easy to read. Each statement has it's name, that's what's happening to everything up to the end parenthesis. Stuff inside it gets evaluated as needed, line evaluation starts top to bottom, and within that left to right. Probably has the simplest evaluation order ever.
<ski> so, sadlly, no
<pango> schlick: Logo is a functional language, with easy to learn syntax... Had fun with continuations in Logo... around '86 or '87
<ski> logo has continuations ?
<pango> ski: sure
<ski> cool
<Mozillion> ski: it is
<ski> Mozillion : but you can still avoid the duplication in PHRASE
<Mozillion> yes
<ski> schlick : are you talking Common Lisp ?
<schlick> pango: Hee, I started out plinking at a old Apple II and Commadore 64 (got them at roughly the same time, the Commadore first), with the built in BASIC, some scraps of documentation, and a book on Apple assembly that I sort of lucked into finding at a used book store.
* ski has 5 commodore 64s
<schlick> ski: Actually, when I was playing much with Lisp, I can't remember what it was called. I think it might have been xlisp. It was a itty bitty interpreter. I don't think it tried to comply to any standard (I don't think there was one at the time).
* ski though started at ca 7 years age with a small programmable calcuator (BASIC) with 510 bytes of RAM for programs :)
<ski> schlick : ok
<schlick> ski: Were you about to tell me about the horrors of common lisp evaluation? :P I don't know much about how it differs other than I've seen the slab that is the standard.
<ski> no .. just that not all lisps have left-to-right evaluation of arguments
<schlick> Really?
<schlick> That seems evil.
<ski> just don't rely on argument evaluation order
<ski> if order is needed, use let or let* or begin (/progn)
<schlick> I suppose, but then you're stuck with 'purely functional' programming, which is ok, I guess, till you need to do I/O.
<ski> no, you're not
<ski> (let* ((a (...)) (b (..a..))) ..a..b..)
<schlick> You could work around it, true, by making it separate, like trying to cope with C's foo(bar(),baz()); style reordering (bar and baz may execute in any order, worse, the order may vary depending on the optimization level you use in your compiler).
<schlick> Still, I distinctly dislike flow control reordering where it isn't known to be safe. "Random" bugs are the worst kind.
<Mozillion> ski: btw, a diff is easier to see what's changed -> http://rafb.net/paste/results/YpoZ4742.html (I see no errors, you?)
<ski> in haskell, effectful code *must* be sequenced (type error otherwise) .. though of course there's no such thing as argument evaluation order, there
<schlick> Sounds like a good policy.
<ski> Mozillion : looks ok, from what i see
<schlick> I'm not used to the term "effect" being used the way you use it. I have heard 'side effect' but that's a little more specific. Plus I've attempted to understand the 'type and effect' thing lately.
<ski> iirc SPJ called Haskell "The world's finest imperative language" :)
<Mozillion> ski: yeah, it's great!
<ski> by effect, i here more or less mean : that which can be described by a monad :)
<Mozillion> ski: now I hope that this is directly translatable to camlp's Grammar (which seems to be nearly LL(1))
<ski> example effects are : I/O (aka external state), (internal) state, exceptions, continuations (goto on stereoids), "don't know"/angelic nondeterminism (related to generators and iterators), "don't care"/demonic nondeterminism (this is when you get one of many possible answers, and can't control which .. concurrency can give rise to this), parsing )
<ski> also, there's environment/reader (dynamic scopic), writer/output (logging etc)
<ski> it can possibly be a bit hard to grasp what is meant by 'effects' by this diverse list
<ski> schlick : what do you think ?
<schlick> ski: I think Djikstra is wrong, everything should be sequential. Maybe if we hook input to output we can get rid of those side effects too. :P
<ski> effects != side-effects
<ski> effects can be manifested as side-effects
<schlick> I'm mostly joking with you.
<ski> they usually are, in most proglangs
<ski> the 'side' means that it's something that happens on the side, it's not included in the main result, the return value
<schlick> Personally I don't like having to cope with concurrency but new processors will force it on us, even if you're only interested in the desktop. Some sort of unpredictableness is unavoidable so long as your computer isn't a closed loop, and if it's a closed loop it's not good for much.
<ski> in haskell though, effects *are* included in the main result
<ski> well
<ski> there's stuff like declarative concurrency, too
<ski> that's not effectful
<schlick> Depends on what you mean by harmful.
<schlick> Creating/killing massive numbers of threads isn't exactly friendly to performance.
<ski> who said 'harmful' ?
<ski> true
<schlick> I misread effectful to harmful.
<ski> you still need some reasonably smart way of handling spawning and joining, etc
<ski> either explicit or implicit
<schlick> Yes. I've noticed most of the languages that seem to cope with concurrency well are impure versions of pure theories that avoid spawning threads for short calculations and group longer lived ones into true threads.
<ski> have you looked at Oz or Alice ?
<schlick> Implicit would be great, if it could be done intelligently. It obviously can't from the source because it doesn't necessarily know how long a operation will take. By running a instrumented version you might be able to get away with it. The reason for bothering would be to avoid having to alter the source every time a processor comes out with more cores.
<ski> right
<ski> or, if you are borrowing computing power over a network
<schlick> I know of Oz. I'm probably not smart enough to judge, but my take on mixed-concept languages is they tend to look like a mess. Looked like Oz was doing some interesting optimization work, but I'm not that heavily into that. Natively compiled languages that at least make some attempt at optimization tend to whip VM's all to heck, yet, apparently people are willing to tolerate even the Java VM.
<schlick> VM's all to heck, yet, apparently people are willing to tolerate even the Java VM.
<schlick> I don't know about Alice.
<ski> Alice is basically same model as Oz, except it's an SML variant, and thus statically typed (and some more differences)
<schlick> I'd rather have lots of relatively conceptually clean languages that could be linked, than have styles changing every few pages of source.
<ski> i think declarative concurrency is one of the most interesting ideas in Oz
<ski> would be nice to see how far one could take that concept
<schlick> Declarative concurrency is a very old concept. One of the oldest still surviving languages is SISAL.
<schlick> The problem of avoiding rapid mass spawning of threads and mass killing of them isn't easy to fix though.
<ski> with dataflow variables, which can be instantiated ?
<ski> (and threads block on read-only-views until other end instantiates it)
<schlick> Basically works like a compiler back end. The order of almost anything isn't guaranted, but it doesn't matter because you're forced to program in pure functional style. Tends to heavily rearrange the code.
<schlick> It was intended for a hardware architecture that never caught on. Most of the research supposedly got used in compilers for imperative languages.
<ski> SISAL ?
<schlick> Yep.
<schlick> SISAL and P... something. Post? Were two early ones.
<ski> haven't looked at that yet .. does it have dataflow-vars ?
<ski> (guesses not)
<schlick> Not really sure. It's very old. Post has no surviving compilers. SISAL does have a open source one. There's lots of spawn of SISAL. SAC (SISAL made to look like C, it's proprietary), L... something, Lucent or Lucid or something like that (also proprietary). It sounds like Oz is using some of that. I wasn't aware.
<ski> Lustre ?
<schlick> Could be.
<ski> Lucid is also a proglang
<ski> those are signal langs
<schlick> I remember trying to find examples to look up and something that started with L that ment "shiny" came up, but you couldn't get a compiler for it for free. :P
<ski> Synchrone
<ski> from what i understand, the Lucid and friends is about 'dataflow' in a different sense
<schlick> The "data flow languages" are the family I'm referring to. They're all pure FP, with some peculiar ideas about tags that were supposed to exist in that hardware. I haven't looked into them much. It's something I plan to make myself learn when I'm a old man and have a working static checking compiler that needs a optimizer.
<ski> yeah, sounds like Lucid and family
<schlick> SISAL = compiler back end's scheduler, basically
<ski> from what i understand, that family uses a different kind of effects (than i mentioned above)
<schlick> Put another way it's what you'd get if you tool Labview, and forced it into a typical text representation of programming rather than icons with wires.
<ski> you have stuff which have a current value, and values for next tick of time, etc
<schlick> Though personally I find it easier to think of as a compiler's scheduler.
<ski> yes, (from what little i've looked at) Labview seems related, somehow
<schlick> Sounds right. Stuff moves through a four stage cycle, which sounds like the ticks you're talking about.
<ski> nat = 0 fby (nat + 1)
<ski> this first has value 0, then value 1, then value 2, etc
<schlick> And yes, all the "graphical languages" (Labview, Scicos, P... something? Pliney?) are "data flow". they just represent it with pretty pictures instead of text, which means they're well suited to simulations of things that are naturally represented as "things with connections" like electronics, and not much else. Of course that's exactly where they're used.
<ski> m
* ski should look into those more, some time
<ski> when i have time :)
<schlick> I think SISAL would probably have been easier to use. Graphical languages are "pretty" and probably don't spook non-programmers as much (e.g. electronics engineers using Labview), but writing in them is slow, and they eat up huge amounts of space (somewhat mitigated by allowing you to group chunks into icons, but sometimes you can't do that in a meaningful way).
<ski> sum x = 0 fby (x + sum (next x))
<schlick> icons, but sometimes you can't do that in a meaningful way).
<ski> sum nat first have value 0, then 1+0=1, then 2+1=3, then 3+3=6, then 4+6=10, etc
<ski> from what i understand, they don't have much facilities for abstraction
<Submarine> SCADE, SAO...
<schlick> If you want to look at one, the most advanced graphical language that's freely available that I know of is Scicos, which is part of the Scilab project. SISAL seems to be the only surviving open source data flow language. It's more a curiosity than anything practical due to it not working well on real, popular, hardware. Some people use it to teach compiler scheduling they say.
<schlick> Some people use it to teach compiler scheduling they say.
<Submarine> schlick, If it helps, the fly-by-wire controllers of Airbus airplanes are coded graphically, see Handbook of Avionics.
<schlick> I don't know about not much facilities for abstraction. If it's functional, stick it in a function. If it's graphical, stick it in its own icon. The problem is sometimes a complex operation doesn't cleanly break down into a icon, and you end up with a big wad you have to scroll around.
<schlick> Submarine: Probably works well for that. The graphical languages would be well suited for electronics (the only thing I know of them being widely used for, Labview seems to be the most popular by far), heating and cooling systems, plumbing systems, /possibly/ factory simulations, and about anything else that is most easily modeled with boxes with wires.
<schlick> You could do anything in it, I suspect, it'd just hurt a lot to use it for anything it doesn't easily model.
* ski should go to sleep, before he goes to sleep
<schlick> Take care ski.
<ski> night
smimou has quit ["bli"]
rillig has quit ["exit(EXIT_SUCCESS)"]
Skal has quit ["Client exiting"]