[Haskell-cafe] SYB and opaque types

Neil Mitchell ndmitchell at gmail.com
Wed Apr 18 10:15:03 EDT 2007


Hi Joel,

> import Data.Generics
> import qualified Text.ParserCombinators.Parsec as P
>
> instance Data SourcePos where
>      gfoldl r k x = k x
>
> typename_SourcePos = mkTyCon "SourcePos"
>
> instance Typeable SourcePos
>      where typeOf _ = mkTyConApp typename_SourcePos ([])
>
> strip = everywhere (mkT f)
>      where f (TokenPos a _) = a
>            f x = x
>
> I know that the warnings about gunfold, toConstr and dataTypeOf are
> harmless but how would I define them to avoid the warnings?

Once you find out, we can implement this in Derive as deriving
DataOpaque and TypeableOpaque - could be useful for some things, then
you can fake up an instance with data SourcePos = WHO_CARES.

> Also, the definition of strip above requires -fno-monomorphism-
> restriction. Should I not worry about it? The code runs just fine,
> locations are being stripped and tests pass.

If you eta-expand everything, i.e. strip x = everything ... x, or give
it a type signature, then you don't need monomorphism.

Thanks

Neil


More information about the Haskell-Cafe mailing list