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

oleg at okmij.org oleg at okmij.org
Thu May 10 09:29:41 CEST 2012


> 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]]





More information about the Haskell-Cafe mailing list