Re: [Haskell-cafe] Type family fun

2008-08-24 Thread Stefan Holdermans

Chris,

In the inferred type, there should be IxMap l instead of IxMap i,  
does anybody know what I'm doing wrong?


Your calls to empty are just ambiguous.

Let's say I want to get a hold of an empty map for A :|: B for some  
types A and B. And let's say that you've instance for A hanging around  
that specifies type IxMap A = C. Now our call to empty for A :|: B  
delegates to empty to get the left map. Clearly you expect it to call  
to the instance for A, but any type D with IxMap D = C would do.


Does that make sense?

Cheers,

  Stefan

On Aug 23, 2008, at 4:55 PM, Chris Eidhof wrote:


Hey all,

I was playing around with type families, and I have a strange problem.

Suppose we have an alternative to an Either datatype:

 data (:|:) a b = Inl a | Inr b

and a class Ix:

 class Ix i where
   type IxMap i :: * - *
   empty  :: IxMap i [Int]

Now I want to give an instance for (a :|: b):

 instance (Ix l, Ix r) = Ix (l :|: r) where
   type IxMap (l :|: r) = BiApp (IxMap l) (IxMap r)
   empty = BiApp empty empty

BiApp is defined as following:

 data BiApp a b c = BiApp (a c) (b c)

However, it looks like the recursive calls to empty can't be  
unified, I get the following error message:


   Couldn't match expected type `IxMap l'
  against inferred type `IxMap i'
 Expected type: IxMap (l :|: r) [Int]
 Inferred type: BiApp (IxMap i) (IxMap i1) [Int]
   In the expression: BiApp empty empty
   In the definition of `empty': empty = BiApp empty empty

In the inferred type, there should be IxMap l instead of IxMap i,  
does anybody know what I'm doing wrong?


Thanks,

-chris

___
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] Type family fun

2008-08-24 Thread Ryan Ingram
On Sun, Aug 24, 2008 at 1:44 AM, Stefan Holdermans [EMAIL PROTECTED] wrote:
] Your calls to empty are just ambiguous.

Now, you are probably wondering how to fix it.  Here's two different solutions:

 {-# LANGUAGE TypeFamilies, TypeOperators, ScopedTypeVariables #-}
 module Ix where

The first solution still uses type families, but empty takes a
parameter so that the which instance to use can be chosen
unambiguously.

 class Ix i where
 type IxMap i :: * - *
 empty :: i - IxMap i [Int]

 -- uses ScopedTypeVariables
 instance (Ix left, Ix right) = Ix (left :|: right) where
type IxMap (left :|: right) = BiApp (IxMap left) (IxMap right)
empty _ = BiApp (empty (undefined :: left)) (empty (undefined :: right))

The second solution uses data families instead, because no such
ambiguity can exist.

 class IxD i where
 data IxMapD i :: * - *
 emptyD :: IxMapD i [Int]

 instance (IxD left, IxD right) = IxD (left :|: right) where
 data IxMapD (left :|: right) a = BiAppD (IxMapD left a) (IxMapD right a)
 emptyD = BiAppD emptyD emptyD

  -- ryan

 data (:|:) a b = Inl a | Inr b
 data BiApp a b c = BiApp (a c) (b c)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type family fun

2008-08-23 Thread Chris Eidhof

Hey all,

I was playing around with type families, and I have a strange problem.

Suppose we have an alternative to an Either datatype:

 data (:|:) a b = Inl a | Inr b

and a class Ix:

 class Ix i where
   type IxMap i :: * - *
   empty  :: IxMap i [Int]

Now I want to give an instance for (a :|: b):

 instance (Ix l, Ix r) = Ix (l :|: r) where
   type IxMap (l :|: r) = BiApp (IxMap l) (IxMap r)
   empty = BiApp empty empty

BiApp is defined as following:

 data BiApp a b c = BiApp (a c) (b c)

However, it looks like the recursive calls to empty can't be unified,  
I get the following error message:


Couldn't match expected type `IxMap l'
   against inferred type `IxMap i'
  Expected type: IxMap (l :|: r) [Int]
  Inferred type: BiApp (IxMap i) (IxMap i1) [Int]
In the expression: BiApp empty empty
In the definition of `empty': empty = BiApp empty empty

In the inferred type, there should be IxMap l instead of IxMap i, does  
anybody know what I'm doing wrong?


Thanks,

-chris

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


Re: [Haskell-cafe] Type family fun

2008-08-23 Thread Alexander Dunlap
On Sat, Aug 23, 2008 at 7:55 AM, Chris Eidhof [EMAIL PROTECTED] wrote:
 Hey all,

 I was playing around with type families, and I have a strange problem.

 Suppose we have an alternative to an Either datatype:

 data (:|:) a b = Inl a | Inr b

 and a class Ix:

 class Ix i where
   type IxMap i :: * - *
   empty  :: IxMap i [Int]

 Now I want to give an instance for (a :|: b):

 instance (Ix l, Ix r) = Ix (l :|: r) where
   type IxMap (l :|: r) = BiApp (IxMap l) (IxMap r)
   empty = BiApp empty empty

 BiApp is defined as following:

 data BiApp a b c = BiApp (a c) (b c)

 However, it looks like the recursive calls to empty can't be unified, I get
 the following error message:

Couldn't match expected type `IxMap l'
   against inferred type `IxMap i'
  Expected type: IxMap (l :|: r) [Int]
  Inferred type: BiApp (IxMap i) (IxMap i1) [Int]
In the expression: BiApp empty empty
In the definition of `empty': empty = BiApp empty empty

 In the inferred type, there should be IxMap l instead of IxMap i, does
 anybody know what I'm doing wrong?

 Thanks,

 -chris

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


Hi,

I'm not very familiar with type families, but shouldn't BiApp be defined as

 data BiApp a b c = BiApp (a b) (a c)

since you're applying it as BiApp (IxMap l) (IxMap r)?

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