Turning all the Nothings into Just defaultValue using Data.Generics

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

Hello, I can *almost* do it like this: test = (id `ext1T` justDefault) (defaultValue :: A) justDefault :: forall f. (Default f, Data f) => Maybe f -> Maybe f justDefault Nothing = defaultValue justDefault (Just x) = Just x Except it fails with: Could not deduce (Default d1) from the context (Data d1) arising from a use of `justDefault' at /tmp/type.hs:31:19-29 Possible fix: add (Default d1) to the context of the polymorphic type `forall d1. (Data d1) => t d1 -> t d1' In the second argument of `ext1T', namely `justDefault' In the expression: (id `ext1T` justDefault) (defaultValue :: A) In the definition of `test': test = (id `ext1T` justDefault) (defaultValue :: A) If we could figure out a way to write justDefault so that it did not require the Default class, then things would work. It would be nice if there was a way to do one thing if a value is an instance of Default and something else if it is not. Here is some psuedo-Haskell code showing what I mean: justDefault :: forall f. (Data f) => Maybe f -> Maybe f justDefault Nothing | (Default f) => defaultValue | _ => Nothing justDefault (Just x) = Just x Any ideas? j. At Wed, 12 Nov 2008 09:46:05 -0800, David Fox wrote:
[1
] [1.1 ] 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 [1.2
] [2
] _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi David!
2008/11/12 David Fox
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?
The mkT function is used to turn a *monomorphic* transformation into a polymorphic one. Because justDefault is polymorphic and because mkT does not fix the type of justDefault, the constraints of justDefault won't be resolved. So you may need to fix the type of justDefault. How to solve this? You could give up your type class design and write the type specific cases of justDefault using "extT". If you really want to use your type class design and hence keep "test" open to new Default instances, then SYB is most likely the wrong library for you. You could on the other hand use Scrap Your Boilerplate with class, which you can download from hackage[1]. This library was designed so that generic functions can be extended with additional type cases even after they have been defined. This fits your situation since you can give new default values using a type class. Using this library, your example looks like this:
import Data.Generics.SYB.WithClass.Basics import Data.Generics.SYB.WithClass.Derive import Data.Generics.SYB.WithClass.Instances import Language.Haskell.TH()
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 AB = AB {b :: Int, c :: Maybe String} deriving (Show)
-- Derive data instances $(derive [''AB])
instance Default AB where defaultValue = AB {b = defaultValue, c = defaultValue}
-- Dictionary and proxy for the justDefault function data JustDefaultD a = JustDefaultD { justDefaultD :: a -> a } justDefaultCtx :: Proxy JustDefaultD justDefaultCtx = undefined
-- Default case for justDefault (non Maybe type) instance Sat (JustDefaultD a) where dict = JustDefaultD id
-- Maybe case for justDefault instance Default a => Sat (JustDefaultD (Maybe a)) where dict = JustDefaultD justDefault where justDefault Nothing = Just defaultValue justDefault (Just x) = Just x
test = everywhere justDefaultCtx (justDefaultD dict) (defaultValue :: AB)
You will need the everywhere traversal which is not shipped in the package. You can download it from gp-bench[2]. Cheers, Alexey [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/syb-with-class [2] http://darcs.haskell.org/generics/comparison/syb3/Traversals.lhs
participants (3)
-
Alexey Rodriguez
-
David Fox
-
Jeremy Shaw