Re: [Haskell-cafe] Monad instance for partially applied type constructor?

2010-09-29 Thread Dan Doel
On Wednesday 29 September 2010 2:52:21 pm Christopher Done wrote:
> LiberalTypeSynonyms lets you partially apply type synonyms.

Not in general. LiberalTypeSynonyms only allows synonyms to be partially 
applied when expansions of other type synonyms will eventually cause them to 
become fully applied (or discarded, probably). So, for instance:

  type Foo a = (a, a)
  type Bar f = f Int

  Bar Foo ==> Foo Int ==> (Int, Int) -- valid

It does not make partially applied synonyms first class, such that they'd be 
able to be made instances, or parameters to datatypes, etc.

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


Re: [Haskell-cafe] Monad instance for partially applied type constructor?

2010-09-29 Thread Christopher Done
On 29 September 2010 20:48, Ryan Ingram  wrote:
> But it doesn't let you partially apply the type synonym.
>
> On the other hand, if you did this:
>
> newtype Compose f g a = O { unO :: f (g a) }
> type Poly k = Compose (Vect k) Monomial
>
> instance Monad (Poly k) where ...
>
> would work, but now you have to wrap/unwrap Compose in the instance 
> definition.

LiberalTypeSynonyms lets you partially apply type synonyms.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad instance for partially applied type constructor?

2010-09-29 Thread Ryan Ingram
On Wed, Sep 29, 2010 at 11:08 AM, DavidA  wrote:
> Hi,
>
> I have the following code:
>
> {-# LANGUAGE TypeSynonymInstances #-}
>
> data Vect k b = V [(k,b)]
> -- vector space over field k with basis b
> -- for example, V [(5, E 1), (7, E 2)] would represent the vector 5 e1 + 7 e2
>
> data Monomial v = M [(v,Int)]
> -- monomials over variables v
> -- for example, M [(A,3), (B,5)] would represent the monomial a^3 b^5
>
> type Poly k v = Vect k (Monomial v)
> -- multivariate polynomials over field k and variables v
>
> instance Monad (Poly k) where
>    return v = V [(1, M [(v,1)])]
>    p >>= f = ... -- variable substitution
>
> So my thinking is:
> 1. The Monad type class is for one parameter type constructors (eg [], IO)
> 2. Poly is a two-parameter type constructor
> 3. So Poly k is a one-parameter type constructor
> 4. What I'm trying to express, that polynomials over field k are a monad,
> is true.
>
> However, GHC 6.12.2 complains:
>
>    Type synonym `Poly' should have 2 arguments, but has been given 1
>    In the instance declaration for `Monad (Poly k)'
>
> What is going wrong?

Haskell doesn't have true type functions; what you are really saying is

instance Monad (\v -> Vect k (Monomial v))

TypeSynonymInstances just lets you write stuff like this

type Foo = [Int]
instance C Foo where ...

instead of

type Foo = [Int]
instance C [Int] where ...

But it doesn't let you partially apply the type synonym.

On the other hand, if you did this:

newtype Compose f g a = O { unO :: f (g a) }
type Poly k = Compose (Vect k) Monomial

instance Monad (Poly k) where ...

would work, but now you have to wrap/unwrap Compose in the instance definition.

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


Re: [Haskell-cafe] Monad instance for partially applied type constructor?

2010-09-29 Thread Christopher Done
Maybe -XLiberalTypeSynonyms is an option:
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions.html#type-synonyms

On 29 September 2010 20:08, DavidA  wrote:
> Hi,
>
> I have the following code:
>
> {-# LANGUAGE TypeSynonymInstances #-}
>
> data Vect k b = V [(k,b)]
> -- vector space over field k with basis b
> -- for example, V [(5, E 1), (7, E 2)] would represent the vector 5 e1 + 7 e2
>
> data Monomial v = M [(v,Int)]
> -- monomials over variables v
> -- for example, M [(A,3), (B,5)] would represent the monomial a^3 b^5
>
> type Poly k v = Vect k (Monomial v)
> -- multivariate polynomials over field k and variables v
>
> instance Monad (Poly k) where
>    return v = V [(1, M [(v,1)])]
>    p >>= f = ... -- variable substitution
>
> So my thinking is:
> 1. The Monad type class is for one parameter type constructors (eg [], IO)
> 2. Poly is a two-parameter type constructor
> 3. So Poly k is a one-parameter type constructor
> 4. What I'm trying to express, that polynomials over field k are a monad,
> is true.
>
> However, GHC 6.12.2 complains:
>
>    Type synonym `Poly' should have 2 arguments, but has been given 1
>    In the instance declaration for `Monad (Poly k)'
>
> What is going wrong?
>
>
> ___
> 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


[Haskell-cafe] Monad instance for partially applied type constructor?

2010-09-29 Thread DavidA
Hi,

I have the following code:

{-# LANGUAGE TypeSynonymInstances #-}

data Vect k b = V [(k,b)]
-- vector space over field k with basis b
-- for example, V [(5, E 1), (7, E 2)] would represent the vector 5 e1 + 7 e2

data Monomial v = M [(v,Int)]
-- monomials over variables v
-- for example, M [(A,3), (B,5)] would represent the monomial a^3 b^5

type Poly k v = Vect k (Monomial v)
-- multivariate polynomials over field k and variables v

instance Monad (Poly k) where
return v = V [(1, M [(v,1)])]
p >>= f = ... -- variable substitution

So my thinking is:
1. The Monad type class is for one parameter type constructors (eg [], IO)
2. Poly is a two-parameter type constructor
3. So Poly k is a one-parameter type constructor
4. What I'm trying to express, that polynomials over field k are a monad,
is true.

However, GHC 6.12.2 complains:

Type synonym `Poly' should have 2 arguments, but has been given 1
In the instance declaration for `Monad (Poly k)'

What is going wrong?


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