Haskell 1.3 Draft Report
A draft of the Haskell 1.3 report is available by FTP from ftp.dcs.glasgow.ac.uk [130.209.240.50] in pub/haskell/report/draft-report-1.3.dvi.gz [Report] pub/haskell/report/draft-libraries-1.3.dvi.gz [Libraries] Highlights include: Monadic I/O A split into prelude and libraries, with qualified names Strict data types Some minor syntactic revisions We are planning to revise this and release it in time for FPCA '95. There will definitely be additional prelude and library changes; including several new libraries. Feedback is welcome and will be taken into account when revising the report, but please remember that we will be very busy over the next few weeks (I am also away for the next two weeks!). Please mail typos., minor notes on syntax etc. to me; substantive comments should be sent to [EMAIL PROTECTED] Regards, Kevin
Sincere Apologies
For sending out a large and very drafty Haskell 1.3 report by mistake. I was caught out by a very helpful mailer and forgetting an option on a command line (it treated what I thought was a subject as a list of addresses). Our current plans are to release the final Haskell 1.3 report at FPCA '95. If there's time, I hope to preview the report here before then! Kevin
Re: Haskell 1.3
Ian Holyer writes: To go back to the debate on instances, here is a concrete proposal for handling instances in Haskell 1.3: I can see what you're doing, but I dislike the idea of no longer being able to define instances local to a module. This limits my choice of class and type names, and may cause problems when importing libraries defined by other users. For global (exported) instances your rules make sense (a variant of these was considered at one point) with the caveats marked below. 1) A C-T instance can be defined in any module in which C and T are in scope. Fine, in conjunction with 5 and 2 or similar constraints. 2) A C-T instance defined in module M is in scope in every module which imports from M, directly or indirectly. (If C or T are not in scope, a module just passes the instance on in its interface). You need to ignore local C-T instances (i.e. those where a class C or type T is defined locally and not exported), otherwise mayhem could result. Local instances will now also cause problems if there is a global C-T instance defined in any importing module. The interface is problematic if a new class with local name C or type with local type T is defined (or both!), especially if there is a (local) C-T instance. Getting round this would involve being much more explicit about global names in interface files (e.g. an M1.C-M2.T instance). There is also potential name capture of type, class, or operator names by the importing module, which would require additional checking of interfaces import (something we would like to avoid for efficiency reasons). 3) A C-T instance may be imported more than once via different routes, provided that the module of origin is the same. This implies annotating instances with their module of origin, as you note below. 4) If an application of an overloaded function is resolved locally, the relevant instance must be in scope. ...a relevant instance must be in scope... ^ 5) There must be at most one C-T instance defined in the collection of modules which make up any one program (global resolution occurs in Main). There should be at most one global C-T instance defined (otherwise you lose the ability to create local types with instances)... You also shouldn't specify where resolution takes place. Link resolution is much faster... I would like to see the origin of instances in interface files. My preference from an implementers point of view would be something like: interface M1 whereinterface M3 where import M2 (C(..))or import M2 (C(..)) import M3 (T(..),fT) type T = ... instance C T where f = fT instance C T where f = fT The name fT is invented while compiling M3 and passed around in interface files, but not exported from them into implementation modules. As well as specifying the origin of the instance, it gives the code generator something to link to. This really isn't a problem for an implementation. We can always link to a hidden name derived from the unique C-T combination. Introducing magic names in an interface sounds like a *very bad* idea -- you might well accidentally capture a user- or Prelude-defined name. For example, class From where from :: Int - [a] - a instance From Int where from = ... introduces fromInt in the interface, which will clash with the Prelude name. interface M1 where import M2(C(...)) import M3(T(...)) import M4(instance M2.C M3.T) is probably closer to what's required. Regards, Kevin
Re: Recursive type synonyms
[I hear cries of Haskell 2] Phil Wadler writes: The suggestion is: Remove the restriction that type synonym declarations must not be recursive. [...] The obvious way to go is for someone to implement it first, to make sure it's not difficult. Mark Jones, have you tried this in Gofer yet? It's not a big deal if you use a graph algorithm for unification -- you just don't bother checking whether the result of unification is recursive! I implemented recursive types this way in 1987, and I'm sure this wasn't new then. A graph algorithm is arguably the "right way" to implement type inference, anyway (Patrick Sansom has achieved significant speedup for type inference in GHC by adopting a graph-based algorithm). I have a paper in the 1991 Glasgow FP Workshop which describes this algorithm in a functional style K. Hammond, "Efficient Type Inference Using Monads", Proc 1991 Glasgow Workshop on Functional Programming, Portree, Skye, 1991, Springer-Verlag Series of Workshops in Computing Science. and adds the occurs check to obtain normal types. The same thing is also sketched out in my thesis (as a programming example for DACTL). It is slightly harder to do with substitutions, but to compensate you can remove the horrible occurs check. I don't know the state of theoretical work on substitutions for recursive types. Anyone? The really big issue is how you represent recursive types for printing or to define new types. Coming from a graph rewriting world, I prefer explicit labelling (with type variables as labels) to implicit recursion via synonyms. For example e :: a:(Int - a) defines "e" to have the recursive type (Int - Int - ). If you think in terms of mu types, this is just syntactic sugar for: e :: mu a . Int - a There's a nice relationship between types represented this way and graph-based unification. The other nice things about using explicit labels rather than implicit synonyms are that 1) They can be used in arbitrary signatures without needing to predeclare type synonyms. 2) They have a uniform printable representation (not true for synonyms, since you might be able to unify a type with more than one synonym). 3) With the right algorithm, it's easy to generate recursive types -- which makes type inference straightforward (essentially you *remove* the "occurs check" but make sure you "tie a knot" at this point -- trivial with a graph, slightly harder with substitutions). 4) It's easy to introduce multiple recursions in the same type (you need multiple mutually recursive synonyms to achieve the same effect): e :: a: ((b:Int - Char - b) - a) The big disadvantage of recursive types seems to be that you may not be able to detect when a function is applied to the wrong number of arguments, since a type variable will now unify with a recursive function type: f :: a - a unifies with f :: a - a: (b - b) Either John Launchbury or Simon Marlow had a convincing example of how this could cause problems. Kevin
Dec_1991_docs
Begin forwarded message: Date: Wed, 8 Sep 1993 12:04:10 -0400 Errors-To: haskell-request Reply-To: haskell Originator: [EMAIL PROTECTED] Sender: haskell Precedence: bulk From: "Vincent Maiorana" [EMAIL PROTECTED] To: haskers Subject: Dec_1991_docs X-Listserver-Version: 6.0 -- UNIX ListServer by Anastasios Kotsikonas Sirs: I have three short questions prompted by my reading of HASKELL, Version 1.2beta, December 1991. - Question 1 Could you describe (or point to a page that describes) what is meant by the notation on page 83: -- constant function const :: a - b - a const x _ = x With a copy of Winston/Horn's discussion of Lambda calculus in hand, (and I've almost located a paper by Church), I do not understand the :: a - b - a expression. Help ! -- Question 2 Could you provide a simple glossary of mathematical notations in the next versions of the docs? It took a while for me to realize that the = symbol meant if p then q (p only if q) a.k.a the 'context operator' Question 2a: Could you provide an English definition of "expression type signature" versus "type signature". Are they one-in-the-same? I could not find an adequate English definition that distinguished the two. F Y I C O M M E N T S: o The industry language MHDL (based on HASKELL) never defined the = operator! C++ literature does a somewhat better job of defining type defintion and class definitions of types. o Perhaps the HASKELL docs could follow the formats of introductory (and later in HASKELL) advanced C++ docs. See Lippman's C++ or other "primers" for an idea. -- Question 3 Could you explain (or point to an explanation) of the Lambda production (page 10) exp 10 - \apat .. apatn - exp and how it relates to Winston/Horn's discussion of Lambda in their LISP book, chapter 6, "Definition of Lambda"? It seems as if the backslant is a LITERAL part of the syntax. If that is the case, BNF formatting rules usually require a '\' as the designation of a literal. Thanks ! Vincent Maiorana Raytheon Company Missile System Division Computer Aided Engineering -- - End Included Message -
Looking for examples of functional imperative programming
- Begin Included Message - Date: Tue, 7 Sep 93 11:14:57 -0400 From: Donald "A." Smith [EMAIL PROTECTED] To: [EMAIL PROTECTED] Subject: Looking for examples of functional imperative programming Could people please post listings of Haskell or Gopher programs for array updates, mutable abstract datatypes, and other "imperative" functional programming features? I'm trying to determine whether the techniques are really viable or are just awkward tricks. Thanks, Don Smith ([EMAIL PROTECTED]) - End Included Message -
Looking for examples of functional imperative programming
- Begin Included Message - Date: Tue, 7 Sep 93 12:08:23 -0400 From: [EMAIL PROTECTED] To: [EMAIL PROTECTED] Subject: Looking for examples of functional imperative programming In response to Don Smith's request, here follows my version of a Gensym monad and real code that uses it. This is syntactic manipulation code that needs to invent new variable names for the output terms. Constructed terms are returned by calling the monad's `unit' function; constructed subterms are passed on into the rest of the program by the monad's `' operator. The main burden is having to invent a name for each intermediate result, rather than substituting the imperative function in its place in the output as one can do in Lisp or Standard ML. I don't have handy any examples of hardcore reference-cell hacking a la impure Standard ML, but I think such code would exhibit the same limitation: one loses the anonymous value-passing implicit in the functional-expression notation. In my opinion, this drawback can be fixed with syntactic sugar of a sort that has heretofore been excluded by the functional programming community's dogma that higher-order functions suffice for all such purposes. A further problem is combining more than one imperative construct in a single program. I know that David King and Phil Wadler have worked on this problem, but I don't know the current state of their work. Here again I think cautious optimism is in order. The Glasgow Haskell compiler is written in Haskell, and uses various imperative programming techniques throughout. It's available for anonymous ftp from nebula.systemsz.cs.yale.edu, as well as from glasgow. They have a C interface. Sheng Liang here at Yale has written an X interface that's available in the Yale Haskell release (at the same ftp site). -- Dan Rabin ([EMAIL PROTECTED]) module Gensym(NameUser, newNameSupply, gensym, regensym, (), unit) where data NameUser a = NameUser (Integer - (a, Integer)) newNameSupply :: NameUser a - a newNameSupply (NameUser f) = let (x, n) = f 0 in x gensym :: String - NameUser String gensym baseName = NameUser (\ n - (baseName ++ "-" ++ show n, n + 1)) regensym :: String - NameUser String regensym oldName = let baseName = takeWhile (/= '-') oldName in gensym baseName () :: NameUser a - (a - NameUser b) - NameUser b (NameUser f) g = NameUser (\ n - let (x, n') = f n NameUser f' = g x in f' n') unit :: a - NameUser a unit x = NameUser (\ n - (x, n)) -- {- CPS transform from Sabry-Felleisen `Reasoning...' tech report. Dan Rabin Tue Aug 17 12:53:48 1993 -} {-**-} module SFCPS' where import Terms import Gensym convertTerm :: Name - Term a - NameUser (Term a) convertTerm cname (Val val) = convertValue val (\ term - unit (App (Val (Var cname)) term)) convertTerm cname (App term1 term2) = convertApp term1 term2 [] where convertApp (Val (Var name)) (Val val) ectxt = convertContext cname ectxt (\ t1 - convertValue val(\ t2 - unit (App (App (Val (Var name)) t1) t2))) convertApp (Val (Const x)) (Val val) ectxt = convertContext cname ectxt (\ t1 - convertValue val(\ t2 - unit (App (App (Val (Const x)) t1) t2))) convertApp (Val (Abs name body)) (Val val) ectxt = convertTerm cname (intoEContext body ectxt) (\ t1 - convertValue val (\ t2 - unit (App (Val (Abs name t1)) t2))) convertApp (Val val) (App term1 term2) ectxt = convertApp term1 term2 (ArgECtxt val : ectxt) convertApp (App term1 term2) term3 ectxt = convertApp term1 term2 (FunECtxt term3 : ectxt) convertValue :: Value a - NameUser (Term a) convertValue (Var name) = unit (Val (Var name)) convertValue (Const x) = unit (Val (Const x)) convertValue (Abs name body) = gensym "k" (\ cname - convertTerm cname body (\ t1 - unit (Val (Abs cname (Val (Abs name t1)) convertContext :: Name - EContext a - NameUser (Term a) convertContext cname [] = unit (Val (Var cname)) convertContext cname (ArgECtxt (Var name) : ectxt) = convertContext cname ectxt (\ t1 - unit (App (Val (Var name)) t1)) convertContext cname (ArgECtxt (Const x) : ectxt) = convertContext cname ectxt (\ t1 - unit (App (Val (Const x)) t1)) convertContext cname (ArgECtxt (Abs name body) : ectxt) = convertTerm cname (intoEContext body ectxt) (\ t1 - unit (Val (Abs name t1))) convertContext cname (FunECtxt term : ectxt) = gensym "v" (\ vname - convertTerm
Haskell List Problems
Folks, We've switched to manual moderation of the Glasgow end of the Haskell list until we've dealt with the US-generated mail failures. There may be a few failure messages still in the pipeline, so please be patient with us. Kevin
Mail Problems on Haskell List
My apologies for the number of error messages which have been echoed to the list today. These seem to have been erroneously generated by a target site in Hong Kong and fed into the list at Yale. I'm working with the people at Yale to try to solve the problem. Kevin
Re: Records in Haskell
Most Lisp dialects don't have any sort of destructuring for abstract data types, but I question whether destructuring is really all that useful anyway. If you have a type with 20 or 30 components -- which is not all that unusual, in my experience -- it's much easier to grab the ones you want by name than by trying to remember the positions of all n components. Why doesn't Haskell allow you to name components? No real reason other than not wanting to add complexity. At a Glasgow workshop two years back the Glasgow Haskellers worked out a couple of schemes for adding records to Haskell. The implementation seemed straightforward, if reasonable design decisions were made. For example, if you disallow identical field names (or require discriminating type information in this case, as with SML) then the field names can easily be used to generate position-dependent code. It is not hard to infer record types in this scheme. data Day = ...; Month = ...; Year = ... record Date = year @ Year, month @ Month, day @ Day pensioner birthday @ month@August, year = year = 1928 == data Day = ... data Date = Date Day Month Year pensioner (Date _ month@August year) = year = 1928 pensioner :: Date - Bool [I've used alphabetical ordering of field names to get a canonical component ordering, though an implementation might get away with just using the ordering in the original definition, or might optimise the ordering to minimise the deconstruction required.] This doesn't allow you to write functions which e.g. select the first component of an arbitrary-sized tuple, but should you be allowed to do that? Also, should you be able to specify defaults for field values, so allowing record Date = year :: Year = 1993, month :: Month, day :: Day taxdate = day@17, month@June Should you be able to specify that a record must contain *exactly* the fields named as in SML, or is it always more useful and flexible to leave this unspecified. Syntax seemed to be the other "big" issue. For instance, should I be able to omit a pattern as with "year" in the first example, should "@" be overloaded like this, what characters delimit records... I can't remember the other suggestion, though I do remember that it involved a dual to case-expressions. Phil Wadler was keen on this. Kevin PS Allowing abstract record types as mentioned above would add a certain amount of complication, but might be worthwhile? module Accounts ( Employee age, birthday ) record Employee = age@Age, salary@Integer, birthday@Date, health@HealthRecord ... The main complication is if field positions or types change -- that information has to be communicated to a using module.
Re: constructor overloading
[This discussion was taking place on comp.lang.functional. I've copied it to the Haskell mailing list. Basically, the original question was whether constructors could be overloaded. My answer was that they could be, if they were nullary, in a similar way to numbers, but I haven't thought this out in great detail.] Hi, "True" is predined in the standard prelude as a boolean constant. But I'd like to use "True" as well as a nullary constructor in abstract type of Prolog goals: data Goal = True | And Goal Goal | Or Goal Goal | Atom Pred Term Could this overloading be allowed as long as the programmer specifies the type explicitly using "::"? Thanks, Don In practice, yes, but I wouldn't want to put such a constraint into a type inference algorithm (SML has this for numbers, and its rather ugly). In a more general sense, I think you can approximate what you asked for as follows: class Bool a where True, False :: a data Bool = BTrue | BFalse instance Bool Bool where True = BTrue False = BFalse data Goal = GTrue | And Goal Goal | Or Goal Goal | Atom Pred Term instance Bool Goal where True :: GTrue and True = True and (And g1 g2) = g1 g2 Now the translation of "and" would be: data CBool = True | False ... fromBool.Goal True = GTrue and x | x == fromBool True = fromBool True and (And g1 g2) = g1 g2 or with dictionaries and static simplification: and x | ==.Goal x GTrue = BTrue and (And g1 g2) = g1 g2 since the types of both argument and result can be inferred in this case. In my opinion, the real problems with this approach would be deciding at definition time which constructors should be overloaded, and perhaps user confusion when a "constructor" doesn't define a single type: and :: (Bool a, Bool b, Bool c) = a - b - c and True True = True and _ _ = False I suppose we do already have this with numbers! Kevin
EJFLP CFP
I've been asked to forward this on behalf of the EJFLP Editorial Board. Kevin - Begin Included Message - First Electronic Journal of Functional and Logic Programming Announcement and Call for Papers At the end of this year a new journal, called Electronic Journal of Functional and Logic Programming (EJFLP), will be started. EJFLP is distributed via email! Thus EJFLP will be available more easily than "hard copy journals" and you will get it FOR FREE. Since papers submitted to EJFLP pass through a refereeing process, EJFLP differs from ftp-distributed papers. The aim of EJFLP is to create a new medium for researches investigating the integration of the functional, logic and constraint programming paradigms. Papers are being solicited in the following areas: - functional and logic languages - integration of functional languages, logic languages and constraint systems - parallelism in functional and logic programming languages - interpretation, compilation and transformation techniques - static analysis for functional and logic programs - foundations and semantics (narrowing, residuation, etc) - calculi for functional, logic and constraint programming - applications - declarative programming concepts and methodolgy There is no page limit for submitted papers. Submit your contribution as a file in postscript or dvi format to the email address below. Deadline for the first volume of EJFLP is: August 31, 1993. Late papers and papers that require a major revision will be considered for the second volume. Submissions: To get some advice for submitting papers to EJFLP send an empty mail with Subject: Help to: [EMAIL PROTECTED] You will get an acknowledgement of your submission within some hours. Subscription: To subscribe the journal send an empty message to: [EMAIL PROTECTED] You will receive an acknowledgement of your registration within some days. Anyone who has ordered EJFLP will get the contents of any volume along with the abstracts of the articles by email. Problems: If there are any problems in handling this to robots please contact [EMAIL PROTECTED] Editorial Board: --- Rita Loogen (RWTH Aachen) Herbert Kuchen (RWTH Aachen) Michael Hanus (MPI-Saarbruecken) Manuel MT Chakravarty (TU Berlin) Martin Koehler (Imperial College London) Yike Guo (Imperial College London) Mario Rodriguez-Artalejo (Univ. Madrid) Andy Krall (TU Wien) Andy Mueck (LMU Muenchen) Tetsuo Ida (Univ. Tsukuba, Japan) Hendrik C.R. Lock (IBM Heidelberg) Andreas Hallmann (Univ. Dortmund) Peter Padawitz (Univ. Dortmund) Christoph Brzoska (Univ. Karlsruhe) Frank Pfennig (Carnegie Mellon Univ.) - End Included Message -
Re: Successor patterns in bindings and n+k patterns
And now for a little quiz. What's the value of the following (legal) Haskell expression? (Don't try it with hbc, it fails.) let (+) + 1 + 1 = (+) in 1 + 1 Given infixl 6 + (since you can't change this without renaming!): (+) + 1 + 1 == lpat6 + pat7 var + int + pat so I'd expect the answer to be 0. glhc and gofer both agree with me. Kevin
Re: More questions
More questions along the same lines as for n+k: Does == in the pattern match translation refer to == in PreludeCore? Does negate in the translation of -e refer to negate in PreludeCore? All identifiers used in explicit translations refer to those from the Prelude. Kevin
Re: Stupid Haskell question
I also think its neat that you seem to have found a use for cyclic unification. This is definitely an impetus to extend the language to include cyclic types. (I don't expect we'll do this for a while though. You might consider modifying the Glasgow Haskell compiler to include this yourself -- it may not be too difficult.) I'm not sure with it's possible to do this with the substitution algorithm used in our compiler, I thought the occurs check helped preserve the idempotency of substitions? It's certainly possible in the graph-based algorithm I describe in my 1991 Glasgow FP workshop paper (in fact, you get this "for free" and end up adding an occurs check just to match the normal algorithm!). The paper describes [informally] how to transform a substitution algorithm written using monads (such as the one in our compiler) into the graph version. You can also use a parallel algorithm if you use the right monad. Apart from the changes to the underlying monad, the differences are quite minor. The paper is (still) a draft version, so may be buggy, but please ask if you'd like a copy. Oh if you did this, you'd also need to change the type output routines, and you might like to allow explicitly cyclic types in type signatures [may as well as existential types while you're there, too :-) -- it's a pain when not all expressions can be given a type signature]. Apart from the implementation (which doesn't seem to be a problem if the right alg. is used[*]) does anyone know of more subtle problems with cyclic types [such as not being able to define the type system using the traditional sequent style]? Is this a well-studied area? Kevin [*] Though if substitions couldn't be used, I wouldn't like to have to reimplement the type checkers in all existing Haskell compilers.
Re: Layout expansion
I want to build the layout expansion ('{', '}' and ';') into the scanner. In general you could only do this by building some parsing capability into the scanner (though in musing about it I haven't found any cases which couldn't be solved by adding simple "bracket-counting" for interesting constructs). It is quite straightforward to integrate the scanner with the parser so that the parser gives enough information for the scanner to work correctly. Unless you *need* a standalone scanner this is probably the easiest thing to do... Since I try to include this expander in the scanner, I tried to figure out which the cases might be, in which such "syntactical categories" end, independently from the layout. The only constructs I found are "(...)", "[...]", "{...}" and "let ... in". You should think in terms of symbols (and then relate these back to constructs!). The following are some that you've missed: ",", "then", "else", "..", "|", ";", "-" Semicolons and close-braces could be ones which were inserted automatically (perhaps by "error" processing), of course, so you need to allow for this possibility! The question I'm raising is, if anybody knows a general rule for finding out this categories (I did it intuitively), Computing the follow-set of the "}" token should give the symbols which could cause problems (any standard parsing text should have an alg., but it's usually simple to do intuitively). Subtract infix operators and "::" since they will be handled by the "longest parse" rule. The main problems arise with case expressions, such as: [case of x - case f of p | g - e1 + e2, 2] Two close braces must be inserted before the ",". Since the "|" is a guard rather than a list comprehension, don't insert braces here! On the other hand, you should insert the close braces before the "]" in the following example, [case of x - case f of p | g - (e1 + e2, 2)] Regards, Kevin
Re: Another import question
On Thu, 03 Dec 92 08:13:17 +, Simon L Peyton Jones [EMAIL PROTECTED] said: Simon Why do you need to drop the (..) when it turns into a "data" decl? Simon You only need do so if you want it to be abstract! Simon But "type" decls can't be abstract; the (..) reminds you of this. I don't want reminding. I know it isn't abstract, but for the sake of the importing module I like to pretend it is. In that case, perhaps you should always use data declarations (with a dummy constructor) rather than type synonyms. Some compilers will give you better error messages this way, and a good compiler might eliminate the extra constructor anyway (depending on how good a strictness analyser it has!). Abstract type synonyms would be an interesting addition to the language, and I can't see any particular problem (we already have the mechanism we'd need, in order to import abstract data types). Is the idea worth resurrecting? For example, module F(S,T) where type S a = (a,a) data T a = C a a could have the interface: interface F where type S a data T a Perhaps the fact that a type is a synonym/datatype should also be hidden in the interface? Obviously a deriving clause would give the game away, but otherwise it probably shouldn't be important whether an abstract type is implemented by a synonym or a datatype. For example, interface F where type S a type T a Are there any problems with this? Kevin
Re: importing derived functions
Is it possible to import a type and the derived "show" function for it without having to import all the type's constuctors? Yes. However, HBC claims that Lexeme is not an instance of Text when I compile the Token module. Sounds like a bug. Lennart probably already has a fix :-) Kevin
Re: Kernel
I have just realised that nowhere in the report does it say specifically what the kernel language is. It says how to translate to it but not what it is!! The short answer is that the report defines an informal semantics with a notional "easily understood", but imprecise kernel. If you want to understand the semantics at a formal level, read the static and dynamic semantics. Together, these define the complete language rather than relying on implicit translation to a kernel (there is some explicit translation in the dynamic semantics). Having worked with SML semantics, I prefer this more direct approach to a translation: the meaning (and type) of a source expression is rather clearer this way. Both semantics are available from ftp.dcs.glasgow.ac.uk (and probably animal.cs.chalmers.se and nebula.cs.yale.edu) in: pub/glasgow-fp/papers/static-semantics.dvi dynamic-semantics.dvi These are binary, DVI files, of course. Kevin
MacGofer 0.12
Mac Gofer Beta Release == MacGofer version 0.12 is now available for beta-testing. Use anonymous ftp to ftp.dcs.glasgow.ac.uk and fetch pub/haskell/gofer/macgofer/MacGofer_0.12.sit.hqx pub/haskell/gofer/macgofer/MacGofer_Manuals.sit.hqx These are BinHexed, Stuffit encoded files (ASCII format). MacGofer_0.12.sit.hqx contains the application, Preludes, Gofer Demos and Mac Documentation. MacGofer_Manuals.sit.hqx is a copy of the Unix docs directory. The documentation is a self-running PostCard file. PLEASE READ THIS BEFORE YOU START, and please take the usual precautions to protect your system from beta-test software... A bug report form is included. I'll do what I can to make sure serious bugs are fixed. If anyone is interested in helping to develop this further, please contact me. I will make sources available soon. MacGofer is free for personal, teaching or research use. You may redistribute it, providing you include the documentation and README files. Kevin About MacGofer -- MacGofer is a standalone Mac implementation of the popular Gofer interpreter, based on version 2.21 of Mark Jones' Unix/PC interpreter. The Mac version has full support for floating-point numbers including trignometrical functions and truncate/round (as also provided in gofer 2.23+). It uses 32-bit integers. The minimal MacGofer configuration needs about 300K of disk space and 1M of RAM (but see below). Summary of Mac Features: A fully integrated Macintosh editor (limited to 32K files), with the usual Mac features. Windows may be selected from the windows menu, which also records when files have changed. Files can be reverted, or deleted from within MacGofer. Find/Replace is provided. Select All is available. Expressions and results are entered in an editable worksheet. Previously entered text may be edited in-place and (re-)evaluated on demand. The worksheet can be saved. Changed files are automatically reloaded when an expression is evaluated. They may also be loaded on demand. The Prelude is treated as a normal file, which will be reloaded if changed. The file containing the last error can be opened at the line where the error occurred. Definitions and types of values can be located through a module-oriented dialog. Direct access to the modules forming a project is provided from the Project Menu. The files being edited are entirely separate from those which form a project (so you can edit data files, or look at other programs etc.). Files can be added to or removed from a project individually. Projects can be saved from within MacGofer. A "Multitasking" option allows you to continue editing whilst evaluating expressions. Input can be taken from the worksheet, using normal Gofer requests. It is possible to turn echoing off. The Gofer heap automatically adjusts to suit the size of the MultiFinder partition. Memory parameters can be saved in a Preferences file. Undo is provided for text entry, cut/paste etc. All symbols in the standard Mac character set can be included in function names. This should appeal to non-English Europeans. You *will* have to manually convert any such characters if you export the file to Unix, but this can be done trivially by a Unix script. Documents can be printed. All printers should be provided. Interrupt is provided(!). Cursors inform you when garbage collection takes place. Errors which exit the Unix/PC Gofer return you to the command-prompt in MacGofer. This helps prevent lost work. Full stack overflow and low-memory checking is provided. The About Gofer dialog gives an indication of the free memory available for editing etc. Some standard command-line commands are supported, e.g. :?. System 7 and MultiFinder friendly. MacGofer will happily evaluate in the background. System Requirements: Requires System 4.1 or later, may run under System 3.2. I recommend System 6.0.7.1/6.0.8 or System 7.x The full version needs at least 1M MultiFinder partition, I am working on a cut-down version for UniFinder MacPluses. MacGofer should run on any Macintosh, including Quadras. It has been tested on LCs, SEs, SE/30s, Classics, Powerbooks, and Quadras, but there *may* still be lurking incompatibilities. A minimal MacGofer with the full Prelude needs 300K of disk. The complete release (including manuals) is 855K. I *recommend* running under System 7 if at all possible. Larger memory partitions will mean more files can be edited, as well as larger programs run.