Joel Reymont wrote:
I have a lot of boilerplate code like this and wonder how I can  scrape it.

instance Morpher Type C.Type where
    morph TyInt = return C.TyInt
    morph TyFloat = return C.TyFloat
    morph TyStr = return C.TyStr
    morph TyBool = return C.TyBool
    morph TyColor = return C.TyColor
    morph TyStyle = return C.TyStyle
    morph (TyList ty) = liftM C.TyList (morph ty)
    morph (TyArray ty) = liftM C.TyArray (morph ty)
    morph (TySeries ty) = liftM C.TySeries (morph ty)
    morph (TyInput ty) = liftM C.TyProp (morph ty)
    morph (TyRef ty) = liftM C.TyRef (morph ty)
    morph TyUnit = return C.TyUnit
    morph TyPrintDest = return C.TyPrintDest

One option is to change your data types. I would suggest something like this:
> data Type   = TyPrim   TyPrim | TyCon   TyCon Type
> data C.Type = C.TyPrim TyPrim | C.TyCon TyCon C.Type

where TyPrim and TyCon (primitves and constructors) can be shared:
> data TyPrim = TyInt | TyString | TyFloat | TyBool | etc.
> data TyCon  = TyList | TyArray | TySeries | TyInput | TyRef

Now the class instance can be:
> instance Morpher Type C.Type where
>     morph (TyPrim  p) = return (C.TyPrim p)
>     morph (TyCon c t) = C.TyCon c <$> morph t
>      -- or liftM for people not so in love with Applicative :)

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

Reply via email to