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

2010-09-30 Thread Ryan Ingram
On Wed, Sep 29, 2010 at 9:13 PM, Alexander Solla  wrote:
>  On 09/29/2010 02:15 PM, DavidA wrote:
>>>
>>> instance Monad (\v ->  Vect k (Monomial v))
>>> >
>>
>> Yes, that is exactly what I am trying to say. And since I'm not allowed to
>> say
>> it like that, I was trying to say it using a type synonym parameterised
>> over v
>> instead.
>
> Why not:
>
> instance Monad ((->) Vect k (Monomial v))

No, what he's trying to say is

> instance Monad (Vect k . Monomial)

with some type-level composition for .

which would give these signatures:

> return :: forall a. a -> Vect k (Monomial a)
> (>>=) :: forall a b. Vect k (Monomial a) -> (a -> Vect k (Monomial b)) -> 
> Vect k (Monomial b)

Notice that the "forall" variables are inside parentheses in the type;
this is what Haskell doesn't allow.

Of course you can

> newtype VectMonomial k a = VM { unVM :: Vect k (Monomial a) }
> instance Monad (VectMonomial k) where ...

But now you need to wrap/unwrap using VM/unVM.

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


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

2010-09-29 Thread Stefan Holdermans
David,

Ryan Ingram wrote:

>>> Haskell doesn't have true type functions; what you are really saying
>>> is
>>> 
>>> instance Monad (\v -> Vect k (Monomial v))

Daniel Fischer wrote:

> I think there was a theoretical reason why that isn't allowed (making type 
> inference undecidable? I don't remember, I don't recall ...).

Indeed: type inference in the presence of type-level lambdas requires 
higher-order unification, which is undecidable [1].

Cheers,

  Stefan

[1] Gérard P. Huet: The Undecidability of Unification in Third Order Logic 
Information and Control 22(3): 257-267 (1973)


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


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

2010-09-29 Thread Alexander Solla

 On 09/29/2010 09:13 PM, Alexander Solla wrote:

 On 09/29/2010 02:15 PM, DavidA wrote:

instance Monad (\v ->  Vect k (Monomial v))
> 
Yes, that is exactly what I am trying to say. And since I'm not 
allowed to say
it like that, I was trying to say it using a type synonym 
parameterised over v

instead.


Why not:

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


Sorry, I guess this is a bit off.  I don't think you "really" want a 
monad.  I think you want something like the dual to the reader monad 
(i.e, a comonad)

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


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

2010-09-29 Thread Alexander Solla

 On 09/29/2010 02:15 PM, DavidA wrote:

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

Yes, that is exactly what I am trying to say. And since I'm not allowed to say
it like that, I was trying to say it using a type synonym parameterised over v
instead.


Why not:

instance Monad ((->) Vect k (Monomial v))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-09-29 Thread Gábor Lehel
On Wed, Sep 29, 2010 at 11:15 PM, DavidA  wrote:
> Ryan Ingram  gmail.com> writes:
>
>> Haskell doesn't have true type functions; what you are really saying is
>>
>> instance Monad (\v -> Vect k (Monomial v))
>>
>
> Yes, that is exactly what I am trying to say. And since I'm not allowed to say
> it like that, I was trying to say it using a type synonym parameterised over v
> instead. It appears that GHC won't let you use partially applied type synonyms
> as type constructors for instance declarations. Is this simply because the GHC
> developers didn't think anyone would want to, or is there some theoretical
> reason why it's hard, or a bad idea?

The version of the lambda calculus (System Fc) GHC uses for its
internal representation doesn't support lambdas at the type level.
I've bumped up against this limitation myself, and don't know of any
way to 'cheat' it (which makes sense, given that it's so fundamental).
You can use newtypes, and recursive definitions (sometimes with
overlap and/or fundeps) work for some cases, though they can get quite
nasty in the harder ones. I have to assume upgrading the type system
to support this would highly nontrivial, though I don't know exactly
how high, nor what drawbacks there might be.


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



-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-09-29 Thread Ryan Ingram
It's hard.  Here's a simple example:

type Foo f = f Int

class C (f :: (* -> *) -> *) where
   thingy :: f [] -> f IO

-- Should this ever typecheck?  I would say no; there's no way to
unify f [] with [Int].
callThingy :: [Int] -> IO Int
callThingy = thingy

-- but what if you say this?
instance C Foo where
 -- thingy :: Foo [] -> Foo IO
 -- therefore,
 -- thingy :: [Int] -> IO Int
 thingy (x:_) = return x

Basically, allowing instances for type functions requires you to
*un-apply* any type functions to attempt to do instance selection.

  -- ryan

On Wed, Sep 29, 2010 at 2:15 PM, DavidA  wrote:
> Ryan Ingram  gmail.com> writes:
>
>> Haskell doesn't have true type functions; what you are really saying is
>>
>> instance Monad (\v -> Vect k (Monomial v))
>>
>
> Yes, that is exactly what I am trying to say. And since I'm not allowed to say
> it like that, I was trying to say it using a type synonym parameterised over v
> instead. It appears that GHC won't let you use partially applied type synonyms
> as type constructors for instance declarations. Is this simply because the GHC
> developers didn't think anyone would want to, or is there some theoretical
> reason why it's hard, or a bad idea?
>
>
> ___
> 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] Re: Monad instance for partially applied type constructor?

2010-09-29 Thread Daniel Fischer
On Wednesday 29 September 2010 23:15:14, DavidA wrote:
> Ryan Ingram  gmail.com> writes:
> > Haskell doesn't have true type functions; what you are really saying
> > is
> >
> > instance Monad (\v -> Vect k (Monomial v))
>
> Yes, that is exactly what I am trying to say. And since I'm not allowed
> to say it like that, I was trying to say it using a type synonym
> parameterised over v instead. It appears that GHC won't let you use
> partially applied type synonyms as type constructors for instance
> declarations. Is this simply because the GHC developers didn't think
> anyone would want to, or is there some theoretical reason why it's hard,
> or a bad idea?
>

I think there was a theoretical reason why that isn't allowed (making type 
inference undecidable? I don't remember, I don't recall ...).

For your problem, maybe

data Vect k m b = Vect [(k, m b)]

instance Monad (Vect k Monomial) where ...

is an option?

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


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

2010-09-29 Thread DavidA
Ryan Ingram  gmail.com> writes:

> Haskell doesn't have true type functions; what you are really saying is
> 
> instance Monad (\v -> Vect k (Monomial v))
> 

Yes, that is exactly what I am trying to say. And since I'm not allowed to say
it like that, I was trying to say it using a type synonym parameterised over v
instead. It appears that GHC won't let you use partially applied type synonyms
as type constructors for instance declarations. Is this simply because the GHC
developers didn't think anyone would want to, or is there some theoretical
reason why it's hard, or a bad idea?


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