[Haskell-beginners] Need help with code duplication (types and
typeclasses)
Brent Yorgey
byorgey at seas.upenn.edu
Tue Oct 26 19:37:25 EDT 2010
On Sat, Oct 23, 2010 at 11:24:05PM -0400, Edward Turpin wrote:
> I can't seem to get my head around types and typeclasses (as well as
> many other things in Haskell). Here's the following code I need help
> with.
>
> In module 1:
> //////////////////////// Start of Code //////////////////////////////
> data NewtonRow = NewtonRow { iteration :: Integer,
> xn :: Double,
> fxn :: Double,
> errEst :: Double
> }
>
> instance Show NewtonRow where
> show row = show (iteration row) ++ "\t" ++
> showEFloat (Just 8) (xn row) "\t" ++
> showEFloat (Just 2) (fxn row) "\t" ++
> showEFloat (Just 2) (errEst row) "\n"
>
> newtype NewtonTable = NewtonTable { getNewtonTable :: [NewtonRow] }
>
> instance Show NewtonTable where
> show table = "n\t" ++ "xn\t\t\t" ++ "fxn\t\t" ++ "xn - xn-1\n" ++
> concatMap show (getNewtonTable table)
>
> instance Monoid NewtonTable where
> mempty = NewtonTable []
> table1 `mappend` table2 = NewtonTable $ (getNewtonTable table1) ++
> (getNewtonTable table2)
>
> cons :: NewtonRow -> NewtonTable -> NewtonTable
> row `cons` table = NewtonTable (row : getNewtonTable table)
How about something like this? The idea is to make the Table type
polymorphic, and to abstract the row-type-specific table header into a
new type class.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Table a = Table { getTable :: [a] }
deriving Monoid -- derive the Monoid instance from the
-- underlying list instance
cons :: a -> Table a -> Table a
row `cons` (Table t) = Table (row : t)
class HasTableHeader a where
tableHeader :: a -> String
instance TableHeader NewtonRow where
tableHeader _ = "n\t" ++ "wn\t\t\t" ++ "fxn\t\t" ++ "xn - xn-1\n"
instance HasTableHeader a => Show (Table a) where
show (Table []) = "---"
show (Table (r:rs)) = showHeader r ++ concatMap show (r:rs)
I think you can see how to extend this to work with the other row type
as well.
-Brent
More information about the Beginners
mailing list