Re: [Haskell-cafe] Partially applied type synonyms in instance heads

2006-10-29 Thread Nicolas Frisby

Haskell's type system does not directly allow eta expansion, i.e.


instance Map (\x y - [(x, y)]) a b where
  ...


is not legal.



The straight-forward way to tackle this is with a newtype declaration, i.e.


newtype Assoc a b = Assoc [(a, b)]

instance Map Assoc a b where
  ...


works as expected. There's an avenue for you to continue with if you like.

In regards to what GHC was trying to tell you with its error message:
type synonyms (like your Assoc) can never be partially applied. In
your instance, Assoc is not applied to a and b (don't let the adjaceny
fool you), it's just sitting by itself... the most lonely version of
partial application. Hence it croaks.

Hope that helps,
Nick

ps - I've never pondered why it is that type synonyms can't be
partially applied. I'm sure someone will pipe up with the answer.

On 10/28/06, Mathieu Boespflug [EMAIL PROTECTED] wrote:

Hi everyone,

I'm running into trouble with type synonyms in instance heads and I
can't figure out what the resulting error message means. The case I'm
considering is as follows:

-- hoist a and b to class variables so that instances declarations may
-- constrain them.
class Map m a b where
toAssoc :: m a b - [(a, b)]
fromAssoc :: [(a, b)] - m a b

type Assoc a b = [(a, b)]

instance Map Assoc a b where
toAssoc = id
fromAssoc = id

The class Map is used to allow translation from one map type to
another (FiniteMap, arrays, etc...) by means of expressing the map as
an association list. Useful for defining isomorphisms and so on. Now
I'd like to define an association list as itself a trivial instance of
Map class, but I cannot do so without wrapping the type of an
association list, [(a, b)], behind a type synonym, as I'm not aware of
any way of writing a type constructor of kind (* - * - *)
constructing the type [(a, b)].
But when compiling the above code with GHC I get the following error:

Map.hs:9:0:
Type synonym `Assoc' should have 2 arguments, but has been given 0
In the instance declaration for `Map Assoc a b'

Any idea what this means? Also, is there any other way of declaring an
instance for [(a, b)] without using type synonyms?

Many thanks,

Mathieu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Partially-applied type synonyms?

2004-09-02 Thread Lyle Kopnicky
Chung-chieh,
Well, I tried what you suggested, and it seems to work.  Unfortunately, 
it's not very useful.  The point of creating MonadPCont, was, like 
MonadCont or MonadState, to automatically provide features to a monad 
built from a transformer, without having to redefine them.  Since ContT 
is the monad transformer, I want any monad created from it to 
automatically support the MonadPCont operations.  But they can't, 
because I can't make ContT an instance of MonadPCont.

I can make FlipContT an instance of MonadPCont, but I can't make 
FlipContT a monad transformer.  So what you have to do is create your 
layered monadwith ContT on top, and then apply the FlipCont constructor 
to get a monad with the methods of MonadPCont.  Now since FlipContT 
isn't a monad transformer, you can't lift things into it.  You can lift 
them into ContT and then write a wrapper around that.

My point is that, unfortunately,  I don't think it's very practical to 
create this type class.  I think the problem is that, although MonadCont 
attempts to describe a monad as having certain operations, MonadPCont 
attempts to describe a group of related monads as having certain 
operations.  They are related by being formed from the same type 
constructor.

Here's the modified code:
module MonadPCont where
import Control.Monad
import Control.Monad.Cont
import Control.Monad.Trans
import Control.Monad.Reader
import Control.Monad.Writer
import Control.Monad.State
import Control.Monad.RWS 

class (Monad (mc a), Monad (mc r)) = MonadPCont mc a r where
   shift :: ((forall b. Monad (mc b) = a - mc b r) - mc r r) - mc r a
   reset :: mc a a - mc r a
instance MonadPCont Cont a r where
   shift f = Cont (\c - runCont (f (\x - Cont (\c' - c' (c x id)
   reset m = Cont (\c - c (runCont m id))
data FlipContT m r a = FlipContT { unFlipContT :: (ContT r m a)}
instance Monad m = Monad (FlipContT m r) where
   return x = FlipContT $ return x
   (FlipContT m') = f = FlipContT $ m' = (unFlipContT . f)
runFlipContT :: FlipContT m r a - (a - m r) - m r
runFlipContT (FlipContT m) = runContT m
 
instance Monad m = MonadPCont (FlipContT m) a r where
   shift f = FlipContT $ ContT $ \c -
   runFlipContT (f (\x - FlipContT $ ContT $ \c' - c x 
= c'))
return
   reset m = FlipContT $ ContT $ \c - runFlipContT m return = c

- Lyle
Chung-chieh Shan wrote:
On 2004-08-31T09:55:10-0700, Lyle Kopnicky wrote:
 

Sorry, I don't think I made myself clear.  I'm not defining PI, it's the 
standard type binding operator, like lambda is the variable binding 
operator.  Maybe I could write it as 'II' so it looks more like a 
capital pi.  It's not a feature of Haskell, but part of type theory 
(dependent types).  I was mixing and matching and making it look like 
Haskell.  So instead of 'PI r - ContT r m', I could write 'flip ContT', 
except that 'flip' needs to work on a type level instead of a value 
level.  Or I could write '(`ContT` m)', or 'ContT _ m', where the '_' is 
a hole.  Does this make sense now?
   

Yes, it makes sense now.  You need to define
   newtype FlipContT m r a = FlipContT (ContT r m a)
or more generally,
   newtype Flip c (m :: * - *) r a = Flip (c r m a)
The rationale for disallowing matching partially-applied type synonyms
is that higher-order unification is undecidable.
See also:
Neubauer, Matthias, and Peter Thiemann. 2002.  Type classes with
more higher-order polymorphism.  In ICFP '02: Proceedings of the ACM
international conference on functional programming. New York: ACM Press.
http://www.informatik.uni-freiburg.de/~neubauer/papers/icfp02.pdf
http://www.informatik.uni-freiburg.de/~neubauer/papers/icfp02.ps.gz
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Partially-applied type synonyms?

2004-08-31 Thread Chung-chieh Shan
On 2004-08-31T09:55:10-0700, Lyle Kopnicky wrote:
 Sorry, I don't think I made myself clear.  I'm not defining PI, it's the 
 standard type binding operator, like lambda is the variable binding 
 operator.  Maybe I could write it as 'II' so it looks more like a 
 capital pi.  It's not a feature of Haskell, but part of type theory 
 (dependent types).  I was mixing and matching and making it look like 
 Haskell.  So instead of 'PI r - ContT r m', I could write 'flip ContT', 
 except that 'flip' needs to work on a type level instead of a value 
 level.  Or I could write '(`ContT` m)', or 'ContT _ m', where the '_' is 
 a hole.  Does this make sense now?

Yes, it makes sense now.  You need to define

newtype FlipContT m r a = FlipContT (ContT r m a)

or more generally,

newtype Flip c (m :: * - *) r a = Flip (c r m a)

The rationale for disallowing matching partially-applied type synonyms
is that higher-order unification is undecidable.

See also:

Neubauer, Matthias, and Peter Thiemann. 2002.  Type classes with
more higher-order polymorphism.  In ICFP '02: Proceedings of the ACM
international conference on functional programming. New York: ACM Press.
http://www.informatik.uni-freiburg.de/~neubauer/papers/icfp02.pdf
http://www.informatik.uni-freiburg.de/~neubauer/papers/icfp02.ps.gz

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
Haskell: lazy, yet functional.  http://haskell.org/
Aqsis: RenderMan for free.  http://aqsis.com/


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Partially-applied type synonyms?

2004-08-31 Thread Carl Witty
On Tue, 2004-08-31 at 10:00, Chung-chieh Shan wrote:
 The rationale for disallowing matching partially-applied type synonyms
 is that higher-order unification is undecidable.

Higher-order unification is worse than just undecidable (after all,
GHC's extended Haskell already includes constructs which are
undecidable, which means that sometimes the compiler will loop forever);
it's ambiguous.  There can be multiple unifiers, none of which is the
most general.  See my earlier Haskell-cafe message for the trouble this
can cause (search for technical note):

http://www.haskell.org/pipermail/haskell-cafe/2004-March/005965.html

Carl Witty


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Partially-applied type synonyms?

2004-08-30 Thread Chung-chieh Shan
On 2004-08-30T17:09:39-0700, Lyle Kopnicky wrote:
 Unfortunately, I need 'PI r - ContT r m', along with a and r, to be a 
 member of the MonadPCont class (PI is the type binding operator).  So I 
 thought I'd define ContT' to take the arguments the other way around.  
 Unfortunately, it can't be partially applied.

What's your definition of PI?  I suspect you simply need to define a
newtype that wraps around 'PI r - ContT r m'.

See also:

Wadler, Philip L. 1994.  Monads and composable continuations.  Lisp and
Symbolic Computation 7(1): 39-56.
http://homepages.inf.ed.ac.uk/wadler/topics/monads.html#composable

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
Green-Rainbow Party of Massachusetts
http://www.green-rainbow.org/
Rich Zitola for Massachusetts State Senate (Worcester and Middlesex District)
http://www.vote-zitola.org/


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe