Hey Andy,
Now, some of those algebraic data type types happen to be
enumerations; in this case, my idea is to list the constructors, with
the rule that each constructor's position in the list is the Int which
gets converted into that constructor.
> class Enumerated a where
> constructors :: [a]
E.g. here's a type Bar with three constructors:
> data Bar = X | Y | Z deriving (Show)
> instance Enumerated Bar where
> constructors = [X, Y, Z]
(This is certainly ugly. Any suggestions?)
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
module Test 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
-- | Return a list of values of a datatype. Each value is one of the possible
-- constructors of the datatype, populated with 'empty' values.
constrs :: forall a. Data a => [a]
constrs = general
`extB` char
`extB` int
`extB` integer
`extB` float
`extB` double where
-- Generic case
general :: Data a => [a]
general = map (fromConstrB empty)
(dataTypeConstrs (dataTypeOf (unList general))) where
unList :: Data a => [a] -> a
unList = undefined
-- Base cases
char = "\NUL"
int = [0 :: Int]
integer = [0 :: Integer]
float = [0.0 :: Float]
double = [0.0 :: Double]
convert :: forall a. Data a => Int -> Maybe a
convert n = let cs :: [a]
cs = constrs
in if (length cs > n) then (Just (cs !! n)) else Nothing