Imperative Object Destruction

2000-11-12 Thread Ashley Yakeley
te :: (Integer,[Byte]) - HandleOperation () withFile :: HandleOperation a - String - IO a Of course, I'd then need to provide functions to compose/concatenate HandleOperation values. But I can't help thinking this problem is already well-known and there's a straightforward solution... -- Ashley

RE: Imperative Object Destruction

2000-11-13 Thread Ashley Yakeley
in Haskell's existing monadic imperative model, something that shouldn't need any runtime extensions. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Imperative Object Destruction

2000-11-13 Thread Ashley Yakeley
handle) stealHandle = read -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

RE: Imperative Object Destruction

2000-11-13 Thread Ashley Yakeley
() withFile (withFile copyFile "dest") "source" ...but I'm not sure how to write copyFile. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Imperative Object Destruction

2000-11-13 Thread Ashley Yakeley
destruction, so that this kind of error is always caught at compile-time. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Union Types for Haskell!?

2000-11-24 Thread Ashley Yakeley
to modify the concept of 'principal type'? Do any papers exist about this topic? Is there any Haskell compiler supporting union types? You might look at O'Haskell, which I understand has some kind of OOP-style polymorphism. I don't know if it has union types though. -- Ashley Yakeley,

Re: Union Types for Haskell!?

2000-11-24 Thread Ashley Yakeley
. Informally, you want the type most general in the type-substitution sense, but probably most specific in the subtype sense. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: old easter egg

2000-12-02 Thread Ashley Yakeley
n - 1) * 19) 26) + 1 engql c = renum (letter c) engq = (foldl (+) 0) . (map engql) -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

GHC for Darwin?

2000-12-20 Thread Ashley Yakeley
Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant that runs on the PowerPC processor. http://www.opensource.apple.com/projects/darwin/. I was going to compile it myself before I remembered that compilers do platform-specific code-generation. Duh. -- Ashley Yakeley

O'Haskell OOP Polymorphic Functions

2001-01-15 Thread Ashley Yakeley
to be of type Base, so x.value gives an error. I tried replacing it with theValue (x :: Derived) = Just (x.value) ...but that doesn't work either. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman

Re: O'Haskell OOP Polymorphic Functions

2001-01-16 Thread Ashley Yakeley
At 2001-01-16 00:03, Johan Nordlander wrote: Ashley Yakeley wrote: How do you do OOP-style polymorphic functions in O'Haskell? My first attempt looked something like this: struct Base struct Derived Base = value :: Int theValue :: Base - Maybe Int theValue x = Just (x.value

Re: O'Haskell OOP Polymorphic Functions

2001-01-16 Thread Ashley Yakeley
this imply that run-time type information is kept with the structs? Consider: d :: Derived d = struct value = 3 b :: Base b = d idb :: Base - Base idb x = x f1 = theValue d f2 = theValue b f3 = theValue (idb d) f4 = theValue (idb b) What are the values of f1, f2, f3 f4? -- Ashley Yakeley, Seattle

Re: O'Haskell OOP Polymorphic Functions

2001-01-16 Thread Ashley Yakeley
At 2001-01-16 13:18, Magnus Carlsson wrote: f1 = Just 3 f2 = f3 = f4 = Nothing So I've declared b = d, but 'theValue b' and 'theValue d' are different because theValue is looking at the static type of its argument? What's to stop 'instance TheValue Base' applying in 'theValue d'? -- Ashley

Re: A simple problem

2001-01-18 Thread Ashley Yakeley
is not always an Integer. It's of type "(Num a) = a". I couldn't find a way to say that every Num is a C. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: A simple problem

2001-01-18 Thread Ashley Yakeley
it is one) but 3.1 cannot be. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

RE: Combinator library gets software prize

2001-01-21 Thread Ashley Yakeley
At 2001-01-21 10:57, David Bakin wrote: What's a 'quant' ... and is it good or bad to be one? I think that depends on exactly how much of a quant you are. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http

Synonym Type Constructors

2001-02-19 Thread Ashley Yakeley
foo :: a - c a type T m = IO m instance MyClass T where foo = return -- Hugs gives: (line 6): Not enough arguments for type synonym "T" So is T a real type constructor or not? -- Ashley Yakeley, Seattle WA ___ Haskell mailing l

Re: Synonym Type Constructors

2001-02-19 Thread Ashley Yakeley
annoying. Is this really necessary? It would be nice if T were, as you say, a first-class type-constructor. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: unliftM

2001-02-23 Thread Ashley Yakeley
- Int comp n = unliftM (do x - ... return x) The correct way to express this is: comp :: Int - IO Int comp n = (do x - ... return x) I think of "IO Int" meaning "instructions for an imperative action, that, if performed, would return an Int". That's quite different from an Int

Re: Proposal: module namespaces.

2001-02-27 Thread Ashley Yakeley
be owned by Sun. Will it be standard practice for versions of Standard be included with Haskell compilers? Could the Prelude make use of Standard? Could Standard become an alternative to the Prelude? If answers to these last three are all "no", an alternative would be to

Re: Contexts in Existential Types

2001-03-13 Thread Ashley Yakeley
AnyCharable = forall c. (Charable c) = MkAnyCharable c anyA = MkAnyCharable 'a' recoverA = obtainChar ((\(MkAnyCharable c) - c) anyA) -- Whoops, my error. It is possible to do this: -- recoverA = (\(MkAnyCharable c) - obtainChar c) anyA -- Sorry... -- Ashley Yakeley, Seattle WA

Re: Dimensional analysis with fundeps

2001-04-09 Thread Ashley Yakeley
you can with C++ templates, you can't do strongly-typed dimensions in Haskell... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Dimensional analysis with fundeps

2001-04-09 Thread Ashley Yakeley
) (times (toUnit 3.7) inch) someLengthInches = fromUnit (divby someLength inch) -- -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: toRational problem

2001-04-16 Thread Ashley Yakeley
e when proportional accuracy is needed over a wide range of scales. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Dimensional analysis with fundeps

2001-04-19 Thread Ashley Yakeley
. -- Ashley Yakeley, Seattle WA MarkerType.hs

Re: Dimensional analysis with fundeps

2001-04-19 Thread Ashley Yakeley
At 2001-04-19 01:19, Ashley Yakeley wrote: Herewith my attempt. Sorry, that should have gone to the Haskell Cafe list. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: help!!!!

2001-04-26 Thread Ashley Yakeley
of a Midsummer morn)! England shall bide till Judgement Tide, By Oak, and Ash, and Thorn! (from _Puck of Pook's Hill_, Rudyard Kipling). -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman

Re: List of words

2001-05-02 Thread Ashley Yakeley
At 2001-05-02 04:54, Keith Wansbrough wrote: Ah, but (i) not all the solutions are correct (sorry Ashley); That rather depends on what you mean by CAPITALISE, does it not? capitalise, -ize to print or write with capital letters [Chambers] -- Ashley Yakeley, Seattle WA

Re: question on type classes

2001-05-08 Thread Ashley Yakeley
Char is not an instance of Foo. See the Anomalous Class Fundep Inference thread. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: BAL paper available

2001-05-16 Thread Ashley Yakeley
libraries written for that. I'm less interested in Haskell 98, since it means muckier solutions to the same problems. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Monads

2001-05-17 Thread Ashley Yakeley
. Monads happen to be a useful pattern for such things. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Monads

2001-05-17 Thread Ashley Yakeley
of Moggi. They are natural thus to construct parsers. Imperative programming is just one facet of the true story. Perhaps, but mostly monads are used to model imperative actions. And their use in imperative programming is the obvious starting point to learning about them. -- Ashley Yakeley, Seattle

Unicode

2001-05-24 Thread Ashley Yakeley
Word16 newtype UCS4CodePoint = MkUCS4CodePoint Word31 type Char = UCS4CodePoint toUCS4 :: UCS2CodePoint - UCS4CodePoint fromUCS4 :: UCS4CodePoint - Maybe UCS2CodePoint encodeUTF16 :: [UCS4CodePoint] - Maybe [UCS2CodePoint] decodeUTF16 :: [UCS2CodePoint] - Maybe [UCS4CodePoint] -- -- Ashley

Re: (no subject)

2001-05-27 Thread Ashley Yakeley
At 2001-05-26 00:47, Rab Lee wrote: hi, i'm having a bit more touble, can anyone help me or give me any hints on how to do this : x 2 3 4 = (x, [2, 3, 4]) Generally we don't solve homework for people. Unless they're studying under Prof. Karczmarczuk, of course. -- Ashley Yakeley, Seattle WA

Monomorphism Restriction

2001-06-09 Thread Ashley Yakeley
Is there a point to the monomorphism restriction in GHC and Hugs? In practice, all it seems to mean is occasionally require unnecessary explicit type signatures. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http

Haskell-JNI Bridge

2001-07-05 Thread Ashley Yakeley
). Phase 2 is to figure out how to create classes on the fly that can call back to Haskell. Fortunately Java does provide functions for loading classes from a byte-array of bytecode. $ ./TestJNI Hello from Java! $ I intend to release it open source at some point. -- Ashley Yakeley, Seattle WA

Re: Need help

2001-07-14 Thread Ashley Yakeley
) was the last thing that successfully loaded, and that it's ready to interpret stuff. If you pass the name of a Haskell file to Hugs, it should load the Prelude and then load the file you gave it. -- Ashley Yakeley, Seattle WA ___ Haskell mailing

Re: Machine bit representations

2001-07-24 Thread Ashley Yakeley
to _standard_ platform-independent bit representations... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Haskell-JNI Bridge

2001-08-03 Thread Ashley Yakeley
At 2001-07-05 02:23, I wrote: In this apparent absence I'm writing my own Haskell-JNI bridge. This now has a home at http://sourceforge.net/projects/jvm-bridge/, and I'm licensing it under LGPL. -- Ashley Yakeley, Seattle WA ___ Haskell mailing

Re: RFC: GUI Library Task Force

2001-09-24 Thread Ashley Yakeley
) A straightforward addition, but not part of my core effort. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

RE: GUI Library Task Force

2001-09-25 Thread Ashley Yakeley
hand with the full Java API hopefully there's less necessity to use normal IO at all anymore so perhaps it will be less of an issue. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo

Re: Wish list: expanded defaulting, dependent types, reflection

2001-09-29 Thread Ashley Yakeley
a bug for this, see http://sourceforge.net/tracker/?func=detailaid=441389group_id=8032atid= 108032. I don't know if this has been fixed in 5.02. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman

Re: Haskell - Java and floats

2001-09-30 Thread Ashley Yakeley
tested it yet, though. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Unicode support

2001-09-30 Thread Ashley Yakeley
correspondence between any kind of n-bit unit and displayed characters. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Empty Datatypes

2001-10-04 Thread Ashley Yakeley
? It isn't in 5.00.2. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Haskell 2: Enum Classes

2001-10-24 Thread Ashley Yakeley
one' functions, those go with numeric classes, which many Enum types would not be instances of. For instance, the letter 'q' is the successor of the letter 'p', but that does not mean that 'q' = 'p' + 1 is meaningful. -- Ashley Yakeley, Seattle WA

Re: GHC modules and packages

2001-10-28 Thread Ashley Yakeley
Quite apart from the documentation, the Haskell library situation in general seems to be widely acknowledged as a bit of a shambles, and a serious improvement effort is ongoing. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED

RE: rank 2-polymorphism and type checking

2001-10-28 Thread Ashley Yakeley
? But GHC doesn't allow it... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: varying number of arguments restriction

2001-10-30 Thread Ashley Yakeley
At 2001-10-30 11:01, Hal Daume wrote: obviously i can rewrite: foo [] = foo s = (snd . head) s but this is uglier. I'm not sure. I actually prefer it written out so that the number of arguments in the cases matches (as GHC enforces). -- Ashley Yakeley, Seattle WA

'Forall' Polymorphism Question

2001-10-31 Thread Ashley Yakeley
a) ...? Is this something GHC could ever do, or are there good reasons why it would never work in Haskell? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Transmitting parameters

2001-11-02 Thread Ashley Yakeley
At 2001-11-01 22:10, raul sierra alcocer wrote: What mechanism of transmiting parameters does Haskell implement? By value. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: URGENT: File exists

2001-11-03 Thread Ashley Yakeley
Bool ... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Wish list: expanded defaulting, dependent types, reflection

2001-09-29 Thread Ashley Yakeley
know about fundeps, right? This may help: class Add a b c | a b - c where {add :: a - b - c;}; -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Wish list: expanded defaulting, dependent types, reflection

2001-09-29 Thread Ashley Yakeley
of the types I define. Do you have a code example of what you're trying to do? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: 0-based versus 1-based

2001-09-27 Thread Ashley Yakeley
element. The element at 37 is the 38th element. It's quite consistent. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

RE: Cash Prizes Win!

2001-09-27 Thread Ashley Yakeley
announcements sent to the list ([EMAIL PROTECTED] in particular)? I'm not really bothered by the way it is... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Global variables

2001-11-29 Thread Ashley Yakeley
: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/~checkout~/jvm-bridge/sourc e/Haskell/IOLiftedMonad.hs?rev=HEADcontent-type=text/plain -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo

Re: Global variables

2001-11-29 Thread Ashley Yakeley
At 2001-11-29 11:13, Ashley Yakeley wrote: Lifted monads look something like this: data MyAction a = MkMyAction ((consts,vars) - (vars,a)); instance Monad MyAction where etc. Whoops, should be data MyAction a = MkMyAction ((consts,vars) - IO (vars,a)); -- Ashley Yakeley

Re: Unicode support

2001-10-09 Thread Ashley Yakeley
. Lots of work for someone. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Unicode support

2001-10-09 Thread Ashley Yakeley
a codepoint has a non-Cn GC, it cannot be changed. But confusingly, some of the GCs are 'normative', whereas others are merely 'informative' -- perhaps these last are subject to revision. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL

Re: Monomorphism, monomorphism...

2001-10-10 Thread Ashley Yakeley
set of types for A. I'm convinced extensible datatypes are the cleanest and most in-spirit extenstion to Haskell to solve this. data T = _; ... data T |= MkAT A; upA = MkAT; downA (MkAT a) = Just a; downA _ = Nothing; -- Ashley Yakeley, Seattle WA

Re: class parameters to existential datatypes

2001-12-06 Thread Ashley Yakeley
At 2001-12-06 13:04, John Hughes wrote: data Foo c = forall a . c a = Foo a What are you trying to say? In 'data Foo c' you are saying that c is a type (as a parameter). In 'c a =' you are saying that c is a class. So naturally Haskell complains. -- Ashley Yakeley, Seattle WA

Re: class parameters to existential datatypes

2001-12-06 Thread Ashley Yakeley
At 2001-12-06 13:11, Ashley Yakeley wrote: At 2001-12-06 13:04, John Hughes wrote: data Foo c = forall a . c a = Foo a What are you trying to say? In 'data Foo c' you are saying that c is a type (as a parameter). In 'c a =' you are saying that c is a class. So naturally Haskell

Re: ANNOUNCE: GCJNI - Java Native Interface for Haskell

2001-12-16 Thread Ashley Yakeley
no idea anyone else was working on this. Nevertheless, I suspect I'm further along. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

ANN: Release 0.1 of Haskell/Java VM Bridge

2001-12-16 Thread Ashley Yakeley
as soon as there's a port of GHC 5.02 with a working createAdjustor. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Library Report Omission

2002-01-05 Thread Ashley Yakeley
... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: dependent type query

2002-01-18 Thread Ashley Yakeley
mkMyData2 :: (MyClass f a) = f - MyData2 f mkMyData2 = MyData2 Looks like extended Haskell is being excessively restricted. Comments? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo

Re: question about kinds

2002-01-18 Thread Ashley Yakeley
, or a List of Lists is traversable. If the Tree type constructor is Traversable, then it's Traversable no matter what it's applied to. You've provided a instance for traversing Trees of anything, it's going to overlap with any instance for Trees of Lists. -- Ashley Yakeley, Seattle WA

Re: question about kinds

2002-01-18 Thread Ashley Yakeley
= ... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Ambiguous types

2002-01-21 Thread Ashley Yakeley
of `isempty': null emptyList Hugs says: ERROR ActorTest.hs (line 7): Cannot justify constraints in explicitly typed binding *** Expression: isempty *** Type : Bool *** Given context : () *** Constraints : Ord a -- Ashley Yakeley, Seattle WA

Re: Translation of SML into Haskell

2002-01-23 Thread Ashley Yakeley
/001258.html Haskell http://haskell.org/pipermail/haskell-cafe/2002-January/001261.html I'd be interested if this really is always possible, or whether someone has an ML structures/functors example that can't be straightforwardly converted into Haskell. -- Ashley Yakeley, Seattle WA

Re: type specs not making it in to functions

2002-01-25 Thread Ashley Yakeley
from putting in an inappropriate back channel in the member for some instance of the class. 3. It avoids use of 'undefined', which is just plain ugly. After all, intuitively everything is defined. -- Ashley Yakeley, Seattle WA Almost empty page: http://semantic.org

Re: using composition with multiple argument functions

2002-02-01 Thread Ashley Yakeley
At 2002-02-01 10:45, Dean Herington wrote: h1 :: (a - a - (a,a)) - (a - a - (a,a)) - (a - a - (a,a)) h1 = f1 # g1 I think you mean: h1 :: (a - a - (a,a)) - (a - a - (a,a)) - (a - a - (a,a)) h1 f g = f # g -- Ashley Yakeley, Seattle WA

Re: RFC: Syntax for implicit parameter bindings

2002-02-03 Thread Ashley Yakeley
story to work as recursive bindings, but I don't know any details here. Even if this happens, we can still hold onto := for explicit value bindings, if that's a useful feature. -- Ashley Yakeley, Seattle WA Never trust whitespace. ___ Haskell mailing

Implicit Parameter Bug?

2002-02-03 Thread Ashley Yakeley
checking ...and spins there. There's a workaround for ghci, but it doesn't help hugs: h :: a - a h = f (g with ?param = ?param) This is very odd, as surely the type of (g with ?param = ?param) is the same as the type of g? -- Ashley Yakeley, Seattle WA

Another Implicit Parameter Infelicity

2002-02-03 Thread Ashley Yakeley
- a q b = g (which works fine with both). However, this _does_ work, but only in ghci: f :: ((?param :: a) = b) - a - b f foo a = foo with ?param=a Hugs just spins trying to do 'Type checking'. -- Ashley Yakeley, Seattle WA ___ Haskell

Re: RFC: Syntax for implicit parameter bindings

2002-02-04 Thread Ashley Yakeley
At 2002-02-04 01:45, Koen Claessen wrote: | addBase{?base=7} 5 I like this! It is the least polluting syntax of all. Hmm... you have braces without following a keyword. I think in all other cases, braces follow a keyword (where, let, do, of). -- Ashley Yakeley, Seattle WA

Re: Reference types

2002-02-05 Thread Ashley Yakeley
of members of the form a - b, where the a's are all the same, it's a clue to consider using a data type instead. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Reference types

2002-02-05 Thread Ashley Yakeley
- newIORef a; return MkRef (readIORef r) (writeIORef r) (modifyIORef r) }; }; instance RefMonad (ST s) where etc. The point is that the m - r dependency is also unnecessary, except when you want a new standard ref for a monad. -- Ashley Yakeley

Re: Reference types

2002-02-06 Thread Ashley Yakeley
the programmer have two different kinds of reference for the same monad, and 'readRef' and 'writeRef' will work on any Ref. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Reference types

2002-02-06 Thread Ashley Yakeley
equally well as 'Ref (ST s) a' as they will as 'Ref TransformedMonad a'. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Reference types

2002-02-06 Thread Ashley Yakeley
m) = Ref m Int ...i.e., references that work with multiple monads. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Reference types

2002-02-06 Thread Ashley Yakeley
or a tremendously early riser! Um, yeah, that's a side effect of unemployment, along with haemorrhaging open-source software (see Truth). Does anyone need a Haskell developer in the greater Seattle area? -- Ashley Yakeley, Seattle WA ___ Haskell mailing

Re: Reference types

2002-02-07 Thread Ashley Yakeley
a - (a - a) - m (); modify ref map = (get ref) = ((set ref) . map); -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Reference types

2002-02-07 Thread Ashley Yakeley
monads. I'm quite happy to have references depend on a state identifier myself. For instance...? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

RE: Reference types

2002-02-07 Thread Ashley Yakeley
Haskell do the clever generalisation stuff. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

RE: Reference types

2002-02-07 Thread Ashley Yakeley
porting code between monads to be as easy as possible. The way forward for this is classes and types in the standard libraries that generalise over any monad which has the necessary properties. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL

Specifying Kinds of Types

2002-02-08 Thread Ashley Yakeley
::: * - *) = MkCMap0; ...or perhaps data ({* - *} p,{* - *} q) = CMap0 p q = MkCMap0; ...or whatever. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Kinds Workaround

2002-02-08 Thread Ashley Yakeley
; }; data (T (p Bool),T (q Bool)) = CMap0 p q = MkCMap0; type Composer c = forall x y z. (T (x Bool)) = (c y z) - (c x y) - (c x z); Neat, huh? Finally, a reason for allowing contexts in data type declarations! -- Ashley Yakeley, Seattle WA

foralls in class assertions

2002-02-16 Thread Ashley Yakeley
context: foo :: (forall a. (C a b) = D a c) = T b c; Does this make sense? Would it have unpleasant consequences? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Composition Monad

2002-02-17 Thread Ashley Yakeley
-- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: a universal printer for Haskell?

2002-02-18 Thread Ashley Yakeley
Generics are just as bad, but I'm hoping they won't catch on. Speaking of which, can you not do this sort of thing with Generics anyway? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Scheme in Haskell?

2002-02-18 Thread Ashley Yakeley
Has anyone attempted any kind of Scheme interpreter in Haskell? -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Scheme in Haskell?

2002-02-18 Thread Ashley Yakeley
as a general user scripting language for such things as transforming XML documents, etc., as part of my project (Truth) to provide a user interface to all information [insert maniacal Bond villain laugh here]. A bit like Guile, I suppose. -- Ashley Yakeley, Seattle WA

RE: foralls in class assertions

2002-02-19 Thread Ashley Yakeley
an instance HasIdentity (m a a), and also for all types a b c, there's an instance Composable (m b c) (m a b) (m a c)'. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Monadic Call/CC?

2002-02-20 Thread Ashley Yakeley
function: peirce :: ((a - b) - a) - a; probably can't be defined. -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: FW: Haskell 98 lexical syntax again

2002-02-28 Thread Ashley Yakeley
-Update1/PropList-3.1.1.html -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: first-class polymorphism beats rank-2 polymorphism

2002-03-06 Thread Ashley Yakeley
this: combinator :: (forall y. Class y = y - y) - (forall x. Class x = x - x) combinator f x = combinator' f x but for some reason GHC 5.02.2 complains. I think this is a bug. Apparently 5.03 has rank-N polymorphism so maybe this is fixed too. -- Ashley Yakeley, Seattle WA

JVM-Bridge Current Status

2002-04-02 Thread Ashley Yakeley
a 0.2 release, say when both examples work on all three platforms. 3. I have created a new mailing list: http://lists.sourceforge.net/lists/listinfo/jvm-bridge-devel If you are using JVM-Bridge I encourage you to subscribe. -- Ashley Yakeley, Seattle WA

Re: deriving over renamed types

2002-04-03 Thread Ashley Yakeley
inference... -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

  1   2   3   4   5   6   7   >