<span style="font-family: courier new,monospace;"><span style="font-family: arial,helvetica,sans-serif;">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.&nbsp; I get the following error because the compiler doesn&#39;t know enough about Maybe a for mkT to create the generic function that everywhere requires, I guess.<br>
<br>Test.hs:26:16:<br>&nbsp;&nbsp;&nbsp; Ambiguous type variable `a&#39; in the constraints:<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; `Typeable a&#39;<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; arising from a use of `mkT&#39; at Senior/Test2.hs:26:16-30<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; `Default a&#39;<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; arising from a use of `justDefault&#39; at Senior/Test2.hs:26:20-30<br>
&nbsp;&nbsp;&nbsp; Probable fix: add a type signature that fixes these type variable(s)<br><br>Here is the example.&nbsp; It all works except for &quot;test&quot;.&nbsp; Any suggestions how to do this?<br></span><br>{-# LANGUAGE&nbsp; DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, RankNTypes, TemplateHaskell, TypeSynonymInstances #-}</span><br style="font-family: courier new,monospace;">
<span style="font-family: courier new,monospace;">{-# OPTIONS_GHC -fallow-undecidable-instances #-}</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">module Test where</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">import Data.Generics</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;">
<span style="font-family: courier new,monospace;">class Default a where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; defaultValue :: a</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">instance Default Int where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; defaultValue = 0</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">instance Default String where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; defaultValue = &quot;&quot;</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">instance Default (Maybe a) where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; defaultValue = Nothing</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">data A = A {b :: Int, c :: Maybe String} deriving (Show, Data, Typeable)</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">instance Default A where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; defaultValue = A {b = defaultValue, c = defaultValue}</span><br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">test =</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; everywhere (mkT justDefault) (defaultValue :: A)</span><br style="font-family: courier new,monospace;">
<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; justDefault Nothing = Just defaultValue</span><br style="font-family: courier new,monospace;">
<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; justDefault (Just x) = Just x</span><br>