
On Thu, Dec 11, 2008 at 09:57, Neil Mitchell
HI Pedro,
Would this help?
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-}
module Data.Generics.Builders (empty) where
import Data.Data import Data.Generics.Aliases (extB)
-- | Construct the empty value for a datatype. For algebraic datatypes, the -- leftmost constructor is chosen. empty :: forall a. Data a => a empty = general `extB` char `extB` int `extB` integer `extB` float `extB` double where -- Generic case general :: Data a => a general = fromConstrB empty (indexConstr (dataTypeOf general) 1)
-- Base cases char = '\NUL' int = 0 :: Int integer = 0 :: Integer float = 0.0 :: Float double = 0.0 :: Double
Yep, that should do it!
It's slated for release with the next version of the SYB library, so in a near future you'll only need to import it. Cheers, Pedro