[Haskell] Lexically scoped type variables: new proposal

2006-10-26 Thread Ben Rudiak-Gould
Hi, everyone. Long time no see. I have a specific proposal for scoped type variables, which is totally different from plans A and B, and which I'd like people to pick to pieces for me. (Especially you, Simon.) Type variable scoping in System F is simple: the type bindings are explicit and follow

[Haskell] Re: Visual Haskell: Could not find module `Control.Monad.Writer'

2006-03-01 Thread Ben Rudiak-Gould
Replying to an old thread... Bernd Holzmüller wrote: Could not find module `Control.Monad.Writer': use -v to see a list of the files searched for I just installed Visual Haskell and ran into the same problem, and the solution I found was to right click on "References" in the project and

[Haskell] Re: "strange" behavior of Implicit Parameters

2006-02-27 Thread Ben Rudiak-Gould
I'd advise against using implicit parameters, because (as you've seen) it's hard to reason about when they'll get passed to functions. Another example: http://www.haskell.org/pipermail/haskell-cafe/2005-January/008571.html -- Ben ___ Haskell mailin

[Haskell] Re: Compilation of big, static tables

2006-02-24 Thread Ben Rudiak-Gould
John Meacham wrote: On Thu, Feb 23, 2006 at 10:40:31AM +, Malcolm Wallace wrote: What I would really like is a syntax to statically construct an array, without having to compute it from a list. This is exactly what my ForeignData proposal on the haskell-prime wiki is meant to address [...

[Haskell] Re: IO == ST RealWorld

2006-02-20 Thread Ben Rudiak-Gould
John Meacham wrote: ST doesn't have exceptions which IO does. It would be no good to make ST pay for the cost of exception handling. GHC handles them behind the scenes (I think?) but in jhc they are explicit and IO is defined as follows: data World__ data IOResult a = FailIO World__ IOError |

[Haskell] Re: Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-16 Thread Ben Rudiak-Gould
Data.Array.ST has runSTArray :: Ix i => (forall s . ST s (STArray s i e)) -> Array i e I think if you can implement that, then all your problems will be solved. -- Ben ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/list

[Haskell] compares :: Ord a => a -> a -> Ordering -> Ordering

2006-02-14 Thread Ben Rudiak-Gould
I just realized that the class Ord should have an additional method: class Eq a => Ord a where compares :: a -> a -> Ordering -> Ordering compares x y d = case compare x y of { EQ -> d ; o -> o } ... This would make writing Ord instances much easier: instance (Ord a, Ord b, Ord

Re: [Haskell] IO == ST RealWorld

2006-01-24 Thread Ben Rudiak-Gould
Ross Paterson wrote: But IO isn't a state monad: others are concurrently changing the world without waiting for my Haskell program to terminate. I think that closed-world behavior should be treated as a property of runST, not of the ST monad operations. Otherwise your IORef = STRef IORegion p

Re: [Haskell] Monads vs. continuations

2005-10-31 Thread Ben Rudiak-Gould
I don't know if this helps, but there's a straightforward way to understand the IO monad in terms of continuation passing. You can think of a value of type IO a as being a CPS expression with a hole in it; the hole is to be filled with a continuation which expects a value of type a. The only w

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-17 Thread Ben Rudiak-Gould
Frederik Eaton wrote: I think this is a good idea. I like the inline "<-", or maybe something like "@". The operator-section notation (<- expr) has the big advantage of being unlikely to collide with any other syntax proposals. I'm not sure what you intend to do about nested "do" statements

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-17 Thread Ben Rudiak-Gould
Bjorn Lisper wrote: However, there is a way to resolve the ambiguity that can be claimed to be the most natural one, and that is to always choose the "least possible" lifting. In the example above, this would mean to interpret [[1]]++[[2]] precisely as [[1]]++[[2]] (lift 0 levels) rather than [[1

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-14 Thread Ben Rudiak-Gould
Frederik Eaton wrote: I want the type system to be able to do "automatic lifting" of monads, i.e., since [] is a monad, I should be able to write the following: [1,2]+[3,4] and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}". The main problem is ambiguity: [[1]]++[[2]] could be

Re: [Haskell] Proposal: Allow "\=" for field update in record update syntax

2005-03-02 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: >On Thursday 24 February 2005 23:27, Keean Schupke wrote: > >>Well, not quite true, because the type of the label is used to index the >>value, the selection happens at compile time. So at run time there is no >>instance selection left... it is simply the value. At least in

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread Ben Rudiak-Gould
Pedro Vasconcelos wrote: >Jim Apple <[EMAIL PROTECTED]> wrote: >>Is there a type we can give to >> >>y f = f . f >> >>y id >>y head >>y fst >> >>are all typeable? > >Using ghci: > >Prelude> let y f = f.f >Prelude> :t y >y :: forall c. (c -> c) -> c -> c > >So it admits principal type (a->a) -> a->a

Re: [Haskell] Typing in haskell and mathematics

2005-02-01 Thread Ben Rudiak-Gould
Jeremy Gibbons wrote: If you want "a < b < c" to mean "(a < b) && (b < c)" but "a + b + c" to mean "(a + b) + c", you're going to have to treat "<" differently from "+", which goes against the spirit of considering them both simply functions. I've wanted to chime in here for a while now. I stron

Re: [Haskell] space behaviour of lazy recursive lists

2005-01-30 Thread Ben Rudiak-Gould
Axel Jantsch wrote: >Consider: > >>gibs = 1 : 1 : (zipWith f gibs (tail gibs)) >> where f x y = min (x + y) 10 > >[...] how can I force the garbage collector to reclaim the >memory of the head of the list after I have processed it, since I will >never ever reference it again? There's no entir

Re: [Haskell] Re: Why is getArgs in the IO monad?

2005-01-18 Thread Ben Rudiak-Gould
Conal Elliott wrote: >The meaning of >"length getArgs" would then have to be a value whose type is the meaning >of Haskell's "Int", i.e. either bottom or a 32-bit integer. I'm >guessing that none of those 2^32+1 values is what you'd mean by "length >getArgs". On the other hand, the IO monad is a

Re: [Haskell] Re: Rebindable syntax for monads and arrows

2005-01-10 Thread Ben Rudiak-Gould
Ashley Yakeley wrote: >Amr A Sabry <[EMAIL PROTECTED]> wrote: >>Because of the additional type constraint (FinSet a =>) we cannot make the >>type Vec an instance of the class Monad, and hence we cannot use the >>do-notation to express our computations. > >You can to do this with GADTs: > >data MyV

Re: DeepSeq.lhs [was: Re: [Haskell] Force evaluation]

2004-12-08 Thread Ben Rudiak-Gould
Dean Herington wrote: >> deepSeq :: DeepSeq a => a -> b -> b I should point out that deepSeq with this type is the composition of two simpler operations: deepSeq = seq . eval where eval :: DeepSeq a => a -> a eval ties a demand for a value to a demand for all its subvalues, while seq ties a d

Re: [Haskell] Force evaluation

2004-12-07 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: >The version with () does less redundant forcing, although the compiler >could perhaps optimize them statically. I did some tests with both versions in GHC on a large binary tree and they appear to have the same performance (even without -O), so I guess GHC does d

Re: [Haskell] Force evaluation

2004-12-06 Thread Ben Rudiak-Gould
Tomasz Zielonka wrote: > I guess you could also do something like deepSeq with Data.Generics. Ralf Hinze posted just such an implementation to one of the mailing lists a couple of years back: http://www.mail-archive.com/glasgow-haskell-users@haskell.org/msg03810.html The end of the message see

Re: [Haskell] pattern matching accross instance declarations

2004-12-01 Thread Ben Rudiak-Gould
S. Alexander Jacobson wrote: > data MyExistantialType=forall v.(Show v)=>EType v > > class MyExistentialTypeable a where >toMyType::String->MyExistantialType > > instance MyExistentialTypeable String where >toMyType "String" = EType "foo" > > instance MyExistentialTypeable Int where

Re: [Haskell] Real life examples

2004-11-25 Thread Ben Rudiak-Gould
John Meacham wrote: >I should say that efficiency is the only thing I have been concerned >about in this conversation. As I said in the mdo proposal, there is no >efficient and safe way to do global variables in haskell. I think George Russell's library (with a simple extension) can be used to cre

Re: [Haskell] Real life examples

2004-11-24 Thread Ben Rudiak-Gould
John Meacham wrote: >On Wed, Nov 24, 2004 at 10:40:41PM +0000, Ben Rudiak-Gould wrote: > >>If the unsafePerformIO hack doesn't work in your new Haskell >>compiler, you can replace it with some other magic that does work. It's >>fine for the Haskell environment

Re: [Haskell] Real life examples

2004-11-24 Thread Ben Rudiak-Gould
John Meacham wrote: >With my mdo proposal, and I think all proposals brought forth, the >module system behaves identically to how it normally does for >namespace control. [...] modules do not change code at all, they >are pure syntantic sugar for deciding what names you can see. I'm not sure I unde

Re: [Haskell] Real life examples

2004-11-24 Thread Ben Rudiak-Gould
Lennart Augustsson wrote: > What do you mean when you say the interface is pure? > > If your module is really pure then there should be an implemenation > of it (which could have really bad complexity) with the same observable > behaviour that uses only pure Haskell. Is this possible? Really? I ag

Re: [Haskell] Real life examples

2004-11-24 Thread Ben Rudiak-Gould
John Meacham wrote: >On Wed, Nov 24, 2004 at 02:40:52PM +0000, Ben Rudiak-Gould wrote: > >>But they can all be implemented with George Russell's library plus safe >>(pure) uses of unsafePerformIO. > >George Russell's library is precicly an invalid use of unsa

Re: [Haskell] Real life examples

2004-11-24 Thread Ben Rudiak-Gould
John Meacham wrote: > randomIO [...] Data.Unique [...] Atom.hs [...] caching These are all great examples of cases where having per-process state makes sense. But they can all be implemented with George Russell's library plus safe (pure) uses of unsafePerformIO. I hope his library or something l

Re: [Haskell] Better Exception Handling

2004-11-23 Thread Ben Rudiak-Gould
Marcin 'Qrczak' Kowalczyk wrote: >What is > exceptionToMaybe (f 0 + error "x") >where > f x = f x >? I guess that answers my question. :-) -- Ben ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: Exceptions

2004-11-23 Thread Ben Rudiak-Gould
John Goerzen wrote: >main = do > xs <- return [ 1, 2, error "throw" ] > `catch` \ any -> do > putStrLn "caught" > return [ 4, 5, 6 ] > print xs > >When run, I get: Fail: throw > >In any case, in the more general case, I don't see a problem with that. >I get a

Re: [Haskell] Better Exception Handling

2004-11-23 Thread Ben Rudiak-Gould
John Goerzen wrote: >On Tue, Nov 23, 2004 at 05:20:19PM +0000, Ben Rudiak-Gould wrote: > >>In any case, mapException is pure, and it's good enough for most of the cases where one might want to catch exceptions outside the IO monad. > >Well, I'm maving trouble wrappin

Re: [Haskell] Better Exception Handling

2004-11-23 Thread Ben Rudiak-Gould
John Goerzen wrote: >myfunc :: String -> Int > >This does some sort of string parsing and returns an Int. Or it may >raise an exception if it couldn't parse the string. But it would do >that every time. > >Now, let's say we have a non-IO catchJust. Of course, if we never need >the value, we neve

Re: [Haskell] Global Variables and IO initializers

2004-11-23 Thread Ben Rudiak-Gould
Lennart Augustsson wrote: George Russell wrote: (3) It needs no extensions to the Haskell language, and only fairly standard hierarchical libraries like Data.IORef. It uses unsafePerformIO which is very much an extension to Haskell. :) I think by Haskell he means the common language currently imple

Re: [Haskell] Unnamed fields

2004-11-16 Thread Ben Rudiak-Gould
Martin Sjögren wrote: >On Tue, 16 Nov 2004 15:04:02 +, Ian Lynagh <[EMAIL PROTECTED]> wrote: > >>Hi all, >> >>Is there a good reason why I can't say >> >>data Bar = Bar { _ :: Int, _ :: Char, x :: Bool } >> >>? > >I agree that it would be useful, but wouldn't > data Bar = Bar Int Char { x

Re: [Haskell] Re: Parameterized Show

2004-11-16 Thread Ben Rudiak-Gould
George Russell wrote: > Sorry, but I like implicit parameters, I use them, and I'm not going > to stop using them because beta conversion no longer preserves semantics. You'll find that many people here don't agree with this view in general (though there's been surprisingly little backlash against

Re: [Haskell] Re: Parameterized Show

2004-11-15 Thread Ben Rudiak-Gould
George Russell wrote: I like the idea too, not just for Show but for any instances. It seems to me that in general you should be able to combine the convenience of the Haskell type system with the power of Standard ML's structures and functors. It looks like it would be easy, but it's very hard.

Re: [Haskell] Re: Using implicit parameter constraints in data decl

2004-11-08 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: >Functions with implicit parameters *are* first class values but only if you >use -fglasgow-exts and not only -fimplicit-params. Careful, they're still not entirely first class. For example, you can't pass types with implicit parameters as arguments to type constructors,

Re: [Haskell] Re: Using implicit parameter constraints in data decl

2004-11-08 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: >On Sunday 07 November 2004 23:19, Ben Rudiak-Gould wrote: > >>Does this do what you want?: >> >>data Test = Test { name :: (?val::Bool) => String } > >Thanks for the hint, but no: > >TestBug.hs:4: >Illegal constraint ?va

Re: [Haskell] Re: Using implicit parameter constraints in data decl

2004-11-07 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: >data (?val::Bool) => Test = Test { name :: String } > >is rejected by the compiler: > >TestBug.hs:3: >Illegal constraint ?val :: Bool >In the context: (?val :: Bool) >While checking the context of the data type declaration for `Test' >In the data type decla

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: >On Thursday 04 November 2004 17:20, Ben Rudiak-Gould wrote: > >>This is one of the several ways in which the current implementation of >>implicit parameters is broken. Clearly they *should* belong to the >>module namespace, and if we modify the imp

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Ben Rudiak-Gould
Koen Claessen wrote: >Ben Rudiak-Gould wrote: > > | I'm not convinced this is a problem either. All you have > | to do is use a single parameter (?MyModule.globals :: > | MyModule.Globals), where MyModule.Globals is an abstract > | type, and you've hidden your impleme

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Ben Rudiak-Gould
Koen Claessen wrote: >Benjamin Franksen wrote: > > | 1) I strongly disagree with ideas to execute IO actions > | implicitly in whatever defined or undefined sequence > | before or during main for whatever reasons. > >I agree with the objections you make. Having full IO actions >as initialization ac

Re: [Haskell] Litle problem with a haskell Function...

2004-11-03 Thread Ben Rudiak-Gould
Manuel Costa wrote: I need to do add "c" and the "c" most be append to list1 to make list1=["a","c"] Then if i input list1 the output must be ["a","c"] But i can't do it... It can't be done. Your source code defines list1 to be equal to "a", and so equal to "a" it is. It can't also be equal to som

Re: [Haskell] Haskell implementation of infixr and infixl/priorities

2004-10-22 Thread Ben Rudiak-Gould
Peter Theissen wrote: I´m progarmming a parser for functional programs. Now I want to implement the infixL and infixR feature to increase the readability of the code. I would be very glad if anyone can send me some information about the implementation of this feature of the Haskell parser or w

Re: [Haskell] Syntax Q: How do you share RHS's in case expressions!?

2004-10-22 Thread Ben Rudiak-Gould
Ryan Newton wrote: For example, in OCaml: match 3 with 3 -> 99 | 4 -> 99 Can be abbreviated match 3 with 3 | 4 -> 99 But I have had no luck figuring out how to do the same thing with: case 3 of 3 -> 99; 4 -> 99 You can do this: let rhs = (some complicated expression) in case 3 of 3 ->

Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Ben Rudiak-Gould
Remi Turk wrote: On Sun, Oct 17, 2004 at 05:11:02PM +0100, Ben Rudiak-Gould wrote: > I don't think there's any problem with > > type MVar = STMVar RealWorld > > newMVar :: a -> ST s (STMVar s a) >> withMVar :: STMVar s a -> (a -> ST s b) -> ST s

Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Ben Rudiak-Gould
Remi Turk wrote: It definitely sounds nice, but is it actually possible to generalize e.g. MVar from "RealWorld" to "forall s" or are we always going to have to say: v <- unsafeIOToST (newMVar / newChan ... ) I hadn't thought of that, but I don't think there's any problem with type MVar = ST

Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Ben Rudiak-Gould
Wolfgang Thaller wrote: Adrian Hey wrote: > I'm puzzled about this idea of "module init action" in a > declarative language. Perhaps, if it's desirable to have some > module initialisation applied to a module if anything from it is > used, the way to do this would be to have a reserved identifier

Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Ben Rudiak-Gould
On Tue, 23 Mar 2004, Sean E. Russell wrote: > The standard explaination about why monads are so troublesome always sounds > like an excuse to me. We have monads, because they allow side-effects. Ok. > If programs that used side effects were uncommon, I'd be fine with them being > troublesome

[Haskell] Re: Impredicative Types?

2004-02-23 Thread Ben Rudiak-Gould
On Wed, 18 Feb 2004, Daan Leijen wrote: > choose :: a -> a -> a > choose x y = x > > What is the type of "choose id" if your system is impredicative? > Either "forall a. (a -> a) -> (a -> a)" or > "(forall a. a->a) -> (forall a. a->a)" Note that neither of these > types subsumes the other. This

[Haskell] Re: "exists" keyword and "existential" types

2004-02-16 Thread Ben Rudiak-Gould
On Mon, 16 Feb 2004, Ashley Yakeley wrote: > A value of "type" (exists t. Interface t => t) consists of two values, > one of type t, and one "dictionary" value. For that reason a data type > is used to represent this (and a newtype type cannot be). This is an implementation detail, though. It's

[Haskell] "exists" keyword and "existential" types

2004-02-15 Thread Ben Rudiak-Gould
I find myself confused by the lack of an "exists" quantifier to complement "forall". It imposes seemingly arbitrary restrictions on the ways in which types can be expressed, and makes some seemingly harmless (and useful) types entirely inexpressible. For example, it seems as though runST could j

Re: [Haskell] GHC 64bit?

2004-02-13 Thread Ben Rudiak-Gould
On 13 Feb 2004, Ketil Malde wrote: > Axel Simon <[EMAIL PROTECTED]> writes: > > > I wonder if such an effort is worthwhile. If all pointers are suddenly > > twice the size then the footprint of a program roughly doubles. > > [...] > > It would be interesting if Haskell programs could run in the

Re: [Haskell] Re: Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
On Thu, 29 Jan 2004, Ashley Yakeley wrote: > Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > > > Another extension I proposed is that the "name" of an implicit return > > value can include type parameters: thus %foo Int and %foo Char would be > > tr

Re: [Haskell] Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
Here's an example of implicit return values from a project I worked on recently, followed by an example of the thread idea. Suppose I've written a decompiler -- it takes binary object code and produces an abstract syntax tree representing source code. A very simplified version of the output type m

[Haskell] Implicit parameters redux

2004-01-27 Thread Ben Rudiak-Gould
This article attempts to describe in more detail the implicit-parameter- based sequencing model that I was trying to develop in a recent thread. I am getting more and more excited about this idea, and after reading this I hope you'll understand why. Any comments are greatly appreciated. (Especially

Re: [Haskell] Re: Implicit return values

2004-01-25 Thread Ben Rudiak-Gould
Continuing my one-sided discussion: > newRef :: a -> (exists s . (Ref s, ^st s a :: State)) > readRef :: (?st s a :: State) => Ref s -> a > writeRef :: Ref s -> a -> ((), ^st s a :: State) ?io and ?st should have been %io and %st, of course. It's essential that these be linear (and that

RE: [Haskell] Re: Implicit return values

2004-01-25 Thread Ben Rudiak-Gould
On Sun, 25 Jan 2004, David Bergman wrote: > Ben, it seems that you are having a quite fruitful discussion with yourself > ;-) Anyone who wants to join in is welcome. :-) > I will just wait here for a more conclusive form of your > backward-propagating linear parameter. I'm not changing the idea

[Haskell] Re: Implicit return values

2004-01-25 Thread Ben Rudiak-Gould
I wrote: > newRef :: a -> (exists s . Ref s a, ^st s :: State) > readRef :: (?st s :: State) => Ref s a -> (a, ^st s :: State) > writeRef :: (?st s :: State) => Ref s a -> a -> ((), ^st s :: State) > > (It's not clear that readRef actually needs to return the state.) It shouldn't, and n

[Haskell] Re: Implicit return values

2004-01-25 Thread Ben Rudiak-Gould
On Mon, 26 Jan 2004, Vincenzo aka Nick Name wrote: > Alle 00:57, lunedì 26 gennaio 2004, Ben Rudiak-Gould ha scritto: > > > > (123, ^x="foo") - (45, ^x="bar", ^y="baz") > > > > would be converted by the compiler to > > > >

[Haskell] Re: Implicit return values

2004-01-25 Thread Ben Rudiak-Gould
I wrote: > It should be possible to implicitly return values which are not instances > of Monoid: the compiler errors out if it ever needs to merge such a type. > Wouldn't this provide a form of uniqueness typing a la Clean? In fact, > couldn't we implement safe state threads on top of this, inste

[Haskell] Implicit return values

2004-01-25 Thread Ben Rudiak-Gould
I'm sure we've all used the Writer monad from time to time when we want to yield a value which will propagate up several levels of a recursive call tree "behind the scenes". And we've all been annoyed at having to rewrite the whole function in monadic style. WriterT is less intrusive, but not much

[Haskell] Re: Use of tab characters in indentation-sensitive code

2004-01-25 Thread Ben Rudiak-Gould
On Sun, 25 Jan 2004, Sean L. Palmer wrote: > Joking aside, surely you intelligent people realize that the internals of a > file format have nothing whatsoever to do with the user interface of the > editing tool. Something like this would be completely transparent *if* you > used the right tools.

Re: Hugs/GHC incompatibility

2004-01-22 Thread Ben Rudiak-Gould
On Wed, 21 Jan 2004, Wolfgang Jeltsch wrote: > In addition, I would like as little undefinedness as possible, i.e., > different implementations behaving as similar as possible. So I'd be > happy if the handling of duplicate indices was defined by the library > specification. I agree (in this cas

RE: no continuations

2003-12-30 Thread Ben Rudiak-Gould
On Tue, 30 Dec 2003, Kevin S. Millikin wrote: > On Tuesday, December 30, 2003 12:39 PM, Ben Rudiak-Gould wrote: > > With letrec and unrestricted call/cc you can implement ML-style refs: > > With an *implementation of letrec that uses mutation* and unrestricted > call/cc, yo

Re: no continuations

2003-12-30 Thread Ben Rudiak-Gould
On Tue, 30 Dec 2003, Scott wrote: > Why does Haskell have no continuations? > (http://www.haskell.org/hawiki/CoMonad) > If continuations are incompatible with non-strict semantics, I'd > appreciate an explanation. With letrec and unrestricted call/cc you can implement ML-style refs: (define (m

RE: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
I wrote: > My solution *is* the Right Thing. :-) What I meant is: it always preserves the validity of inlining, it always preserves sharing, and it rejects otherwise-correct programs only in situations which are (I expect) uncommon in practice. -- Ben ___

Implicit parameters, second draft

2003-08-14 Thread Ben Rudiak-Gould
0. Introduction This is a complete rewrite of my implicit-parameter proposal, with a lot more motivating text and examples, as well as discussions of the tradeoffs involved in making various changes to the existing system. It incorporates various changes which came up in the discussion which follo

Re: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
I wrote: > Exactly the same rule should apply to implicit parameters. In the case of > implicit parameters, safety is ensured if in every use of the bound > variable, its implicit parameter refers to the same explicit binding of > that parameter. For example, the expression > > let g = ?x i

RE: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
On Tue, 5 Aug 2003, Simon Peyton-Jones wrote: > I'm afraid that I have not read all of the recent exciting flood of > messages carefully, Hi, I'm glad to see that you're around, and I'm very much looking forward to any comments you may have about my proposal. > You say that "All implementations

Re: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
Complications: * In my examples it's easy to tell whether all uses of the implicit parameter refer to the same explicit binding, but it may be difficult when recursion is involved. This problem has already arisen in the case of type class constraints, and has been solved, so I'm conf

Re: Implicit parameters, second draft

2003-08-10 Thread Ben Rudiak-Gould
On Sat, 9 Aug 2003, Ashley Yakeley wrote: > I'm a bit worried about the use of curly braces. Currently they're used > to mark blocks when "layout" isn't used. Might this clash? > > IIRC braces are used after "do", "where", "let", "in" and "of" (probably > OK), and also for data structures with

Re: The madness of implicit parameters: cured?

2003-08-07 Thread Ben Rudiak-Gould
On Mon, 4 Aug 2003, Ashley Yakeley wrote: > ((\a -> ((a,[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 2})) ([EMAIL PROTECTED] -> > @x),[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 1} ^^^ > (([EMAIL PROTECTED] -> @x,[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 2

Re: The madness of implicit parameters: cured?

2003-08-06 Thread Ben Rudiak-Gould
On Mon, 4 Aug 2003, Ashley Yakeley wrote: > At 2003-08-04 18:19, Ben Rudiak-Gould wrote: > > >> ((\a -> ((a,[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 2})) ([EMAIL PROTECTED] > >> -> @x),[EMAIL PROTECTED] -> @x) [EMAIL PROTECTED] = 1} > >

Re: The madness of implicit parameters: cured?

2003-08-05 Thread Ben Rudiak-Gould
On Mon, 4 Aug 2003, Ashley Yakeley wrote: > At 2003-08-04 22:33, Ben Rudiak-Gould wrote: > > >This illustrates what you pointed out earlier, that the > >program's semantics can be changed by adding explicit type signatures > >which include implicitly-parameterize

Solution to the monomorphism restriction/implicit parameter problem

2003-08-05 Thread Ben Rudiak-Gould
I just figured out why the monomorphism restriction interacts so weirdly with implicit parameters, and how to fix it. We all know that when the monomorphism restriction is turned on, the following doesn't work: let f = (<) in (f 1 2, f 'a' 'b') On the other hand, the following does work:

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ben Rudiak-Gould
On Mon, 4 Aug 2003, Ashley Yakeley wrote: > At 2003-08-04 20:00, Ben Rudiak-Gould wrote: > > >This is a different lambda calculus, with a different beta rule. You can > >see the same effect in the type inference rules for implicit parameters: > >If f has type Int ->

Re: The madness of implicit parameters: cured?

2003-08-04 Thread Ben Rudiak-Gould
Trouble for implicit parameter defaults: consider ?foo = 0 let x = ?foo in (x + ?foo) { ?foo = 1 } This evaluates to 1 when the monomorphism restriction is turned on, and 2 when it's off. This is no worse than the current behavior of implicit parameters even without def

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
On Sun, 3 Aug 2003, Derek Elkins wrote: > I kinda think someone mentioned this, perhaps even you. Or maybe I'm > thinking of something else. As I'm feeling too lazy to check the > archives, at the risk of saying something stupid or repeating something > said, you may want to look at named instan

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
On Sun, 3 Aug 2003, Ashley Yakeley wrote: > At 2003-08-03 14:09, Ben Rudiak-Gould wrote: > > g ([EMAIL PROTECTED] -> @x) => ([EMAIL PROTECTED] -> g { @x = @x } @x) > > Hmm... I assume you mean specifically this: > > g ([EMAIL PROTECTED] -> @x) > [E

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
I just noticed something interesting. Consider f #name = g where g #name = "hello" This apparently has type (#name :: a) -> (#name :: b) -> String. Should the two #names be merged? Clearly not, because ordinary positional parameters never get merged, and named parameters are supposed to be th

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
First of all, thanks for reading my proposal, and I apologize for the ill-considered rant which preceded it. I hope you won't hold it against me -- we should all be on the same side here. On Sun, 3 Aug 2003, Ashley Yakeley wrote: > ((let g = \_ _ -> [EMAIL PROTECTED] -> @x in ((g ([EMAIL PROTEC

Re: The madness of implicit parameters: cured?

2003-08-03 Thread Ben Rudiak-Gould
On Sat, 2 Aug 2003, Derek Elkins wrote: > Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote: > > > More recently, I've realized that I really don't understand implicit > > parameters at all. They seemed simple enough at first, but when I look > > at an expressio

The madness of implicit parameters: cured?

2003-08-02 Thread Ben Rudiak-Gould
When I first learned about implicit parameters I thought they were a great idea. The honeymoon ended about the time I wrote some code of the form "let ?foo = 123 in expr2", where expr2 used ?foo implicitly, and debugging eventually unearthed the fact that ?foo's implicit value was not being set to

Text I/O library proposal, first draft

2003-07-31 Thread Ben Rudiak-Gould
[Crossposted to Haskell and Libraries. Replies to Libraries.] {- Good things about this text library design: * Efficient implementation should be straightforward * Character coder interface is public, so users can supply their own encodings, or write coder transformers (there are some in

Raw I/O library proposal, second (more pragmatic) draft

2003-07-31 Thread Ben Rudiak-Gould
[Crossposted to Haskell and Libraries. Replies to Libraries.] -- More comments, please. Bad names? Important missing functionality? -- Still unimplementable? module System.RawIOSecondDraft (...) where data File -- now essentially a file handle data InputChannel -- renamed f

Re: System.Directory (was RE: Proposal for a new I/O library design)

2003-07-28 Thread Ben Rudiak-Gould
On Mon, 28 Jul 2003, Wolfgang Thaller wrote: > It's not that easy. Case sensitivity is a property of a file system, > not of the operating system. Actually, it's not even that easy. The NT native API allows you to specify case sensitivity as a flag when creating or opening a file in any director

Proposal for a new I/O library design

2003-07-27 Thread Ben Rudiak-Gould
The other day I was reading the Haskell i18n debate in the list archives, and started thinking about possible replacements for the existing Haskell file I/O model. It occurred to me that the Haskell community has really dropped the ball on this one. Haskell's design has always emphasized doing the