
I want to use Data.Generics to write a function to turn all the Nothings in a data structure into Just defaultValue, as shown below. I get the following error because the compiler doesn't know enough about Maybe a for mkT to create the generic function that everywhere requires, I guess. Test.hs:26:16: Ambiguous type variable `a' in the constraints: `Typeable a' arising from a use of `mkT' at Senior/Test2.hs:26:16-30 `Default a' arising from a use of `justDefault' at Senior/Test2.hs:26:20-30 Probable fix: add a type signature that fixes these type variable(s) Here is the example. It all works except for "test". Any suggestions how to do this? {-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, RankNTypes, TemplateHaskell, TypeSynonymInstances #-} {-# OPTIONS_GHC -fallow-undecidable-instances #-} module Test where import Data.Generics class Default a where defaultValue :: a instance Default Int where defaultValue = 0 instance Default String where defaultValue = "" instance Default (Maybe a) where defaultValue = Nothing data A = A {b :: Int, c :: Maybe String} deriving (Show, Data, Typeable) instance Default A where defaultValue = A {b = defaultValue, c = defaultValue} test = everywhere (mkT justDefault) (defaultValue :: A) where justDefault Nothing = Just defaultValue justDefault (Just x) = Just x