Re: [Haskell-cafe] [Q] multiparam class undecidable types

| instance (Table a c, Show c) => Show a where I would have thought that there is on overlap: the instance in my code above defines how to show a table if the cell is showable;
No, the instance defines how to show values of any type; that type must be an instance of Table. There is no `if' here: instances are selected regardless of the context such as (Table a c, Show c) above. The constraints in the context apply after the selection, not during. Please see ``Choosing a type-class instance based on the context'' http://okmij.org/ftp/Haskell/TypeClass.html#class-based-overloading for the explanation and the solution to essentially the same problem. There are other problems with the instance: | instance (Table a c, Show c) => Show a where For example, there is no information for the type checker to determine the type c. Presumably there could be instances Table [[Int]] Int Table [[Int]] Bool So, when the a in (Table a c) is instantiated to [[Int]] there could be two possibilities for c: Int and Bool. You can argue that the type of the table uniquely determines the type of its cells. You should tell the type checker of that, using functional dependencies or associated types: class Table table where type Cell table :: * toLists :: table -> [[Cell table]]

Thanks Oleg, that was very helpful. i can work with that. read the rest of this if you are curious where your hints took me. you are right, I need to make the functional dependency explicit: | class Table t c | t -> c where | toLists :: t -> [[c]] | fromLists :: [[c]] -> t | | instance Table [[c]] c where | toLists = id | fromLists = id | | instance (Table t c, Show c) => Show t where | showsPrec p t = showParen (p > 10) $ showString "fromLists " . shows (head . head $ toLists t) this compiles, and 'show' prints the first cell of each table. i also understand now why i can't just print all of them: [[Int]] is one of the types where the instances overlap. | instance Show Int | instance Show a => Show [a] vs. | instance Table [[Int]] Int | instance (Table [[Int]] Int, Show Int) => Show [[Int]] the advanced overlap code you are referencing below is fascinating, but isn't it a different problem? i don't want to distinguish different the cases "Show c" and "Typeable c", but i want to use whatever instance of "Show c" is available to implement "Show t". i can't make your solution work for this, because one of the two overlapping instances (namely "Show a => Show [a]") is already provided by the surrounding code that i cannot outfit with the advanced overlap trick. or am i missing something here? i think what i will do is to instantiate all table types individually: | instance Show c => Show (SimpleTable c) where | showsPrec p t = showParen (p > 10) $ showString "FastTable " . | shows (toLists t) cheers, matthias On Wed, May 09, 2012 at 06:41:00AM -0000, oleg@okmij.org wrote:
Date: 9 May 2012 06:41:00 -0000 From: oleg@okmij.org To: fis@etc-network.de CC: haskell-cafe@haskell.org Subject: Re: [Q] multiparam class undecidable types
| instance (Table a c, Show c) => Show a where I would have thought that there is on overlap: the instance in my code above defines how to show a table if the cell is showable;
No, the instance defines how to show values of any type; that type must be an instance of Table. There is no `if' here: instances are selected regardless of the context such as (Table a c, Show c) above. The constraints in the context apply after the selection, not during.
Please see ``Choosing a type-class instance based on the context'' http://okmij.org/ftp/Haskell/TypeClass.html#class-based-overloading
for the explanation and the solution to essentially the same problem.
There are other problems with the instance:
| instance (Table a c, Show c) => Show a where
For example, there is no information for the type checker to determine the type c. Presumably there could be instances Table [[Int]] Int Table [[Int]] Bool So, when the a in (Table a c) is instantiated to [[Int]] there could be two possibilities for c: Int and Bool. You can argue that the type of the table uniquely determines the type of its cells. You should tell the type checker of that, using functional dependencies or associated types:
class Table table where type Cell table :: * toLists :: table -> [[Cell table]]

i think what i will do is to instantiate all table types individually: | instance Show c => Show (SimpleTable c) where | showsPrec p t = showParen (p > 10) $ showString "FastTable " . | shows (toLists t)
I was going to propose this solution, as well as define newtype SlowType a = SlowType [[a]] for the ordinary table. That would avoid the conflict with Show [a] instance. It is also good idea to differentiate [[a]] intended to be a table from just any list of lists. (Presumably the table has rows of the same size). Enclosed is a bit spiffed up variation of that idea. {-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, UndecidableInstances #-} class Table t where data TName t :: * type TCell t :: * toLists :: TName t -> [[TCell t]] fromLists :: [[TCell t]] -> TName t instance Table [[a]] where newtype TName [[a]] = SlowTable [[a]] type TCell [[a]] = a toLists (SlowTable x) = x fromLists = SlowTable data FastMapRep a -- = ... instance Table (FastMapRep a) where newtype TName (FastMapRep a) = FastTable [[a]] type TCell (FastMapRep a) = a toLists = undefined fromLists = undefined instance Table Int where newtype TName Int = FastBoolTable Int type TCell Int = Bool toLists = undefined fromLists = undefined instance (Table t, Show (TCell t)) => Show (TName t) where showsPrec p t = showParen (p > 10) $ showString "fromLists " . shows (toLists t) t1 :: TName [[Int]] t1 = fromLists [[1..10],[2..20]] -- fromLists [[1,2,3,4,5,6,7,8,9,10], -- [2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]]
participants (2)
-
Matthias Fischmann
-
oleg@okmij.org