[Haskell-cafe] Turning all the Nothings into Just defaultValue using Data.Generics

Jeremy Shaw jeremy at n-heptane.com
Wed Nov 12 17:17:54 EST 2008


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  <multipart/alternative (7bit)>]
> [1.1  <text/plain; ISO-8859-1 (7bit)>]
> 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  <text/html; ISO-8859-1 (7bit)>]
> 
> [2  <text/plain; us-ascii (7bit)>]
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list