module Test.Feat.Class (
Enumerable(..),
Constructor,
nullary,
unary,
funcurry,
consts,
shared,
optimal,
FreePair(..),
deriveEnumerable,
deriveEnumerable',
ConstructorDeriv,
dAll,
dExcluding,
dExcept
) where
import Test.Feat.Enumerate
import Test.Feat.Internals.Tag(Tag(Class))
import Test.Feat.Internals.Derive
import Test.Feat.Internals.Newtypes
import Data.Typeable
import Data.Monoid
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Data.Word
import Data.Int
import Data.Bits
import Data.Ratio
class Typeable a => Enumerable a where
enumerate :: Enumerate a
shared :: Enumerable a => Enumerate a
shared = eShare Class enumerate
optimal :: Enumerable a => Enumerate a
optimal = optimise shared
newtype FreePair a b = Free {free :: (a,b)}
deriving (Show, Typeable)
funcurry :: (a -> b -> c) -> FreePair a b -> c
funcurry f = uncurry f . free
instance (Enumerable a, Enumerable b) =>
Enumerable (FreePair a b) where
enumerate = curry Free <$> shared <*> shared
type Constructor = Enumerate
nullary :: a -> Constructor a
nullary = pure
unary :: Enumerable a => (a -> b) -> Constructor b
unary f = f <$> shared
consts :: [Constructor a] -> Enumerate a
consts xs = pay $ mconcat xs
deriveEnumerable :: Name -> Q [Dec]
deriveEnumerable = deriveEnumerable' . dAll
type ConstructorDeriv = (Name, [(Name, ExpQ)])
dAll :: Name -> ConstructorDeriv
dAll n = (n,[])
dExcluding :: Name -> ConstructorDeriv -> ConstructorDeriv
dExcluding n (t,nrs) = (t,(n,[|mempty|]):nrs)
dExcept :: Name -> ExpQ -> ConstructorDeriv -> ConstructorDeriv
dExcept n e (t,nrs) = (t,(n,e):nrs)
deriveEnumerable' :: ConstructorDeriv -> Q [Dec]
deriveEnumerable' (n,cse) =
fmap return $ instanceFor ''Enumerable [enumDef] n
where
enumDef :: [(Name,[Type])] -> Q Dec
enumDef cons = do
sanityCheck
fmap mk_freqs_binding [|consts $ex |]
where
ex = listE $ map cone cons
cone xs@(n,_) = maybe (cone' xs) id $ lookup n cse
cone' (n,[]) = [|nullary $(conE n)|]
cone' (n,_:vs) =
[|unary $(foldr appE (conE n) (map (const [|funcurry|] ) vs) )|]
mk_freqs_binding :: Exp -> Dec
mk_freqs_binding e = ValD (VarP 'enumerate ) (NormalB e) []
sanityCheck = case filter (`notElem` map fst cons) (map fst cse) of
[] -> return ()
xs -> error $ "Invalid constructors for "++show n++": "++show xs
simpleEnum car sel =
let e = Enumerate
(toRev$ map (\p -> Finite (car p) (sel p)) [0..])
(return e)
in e
instance Infinite a => Enumerable (Nat a) where
enumerate = simpleEnum crd sel
where
crd p
| p <= 0 = 0
| p == 1 = 1
| otherwise = 2^(p2)
sel :: Num a => Int -> Index -> Nat a
sel 1 0 = Nat 0
sel p i = Nat $ 2^(p2) + fromInteger i
instance Enumerable Integer where
enumerate = unary f where
f (Free (b,Nat i)) = if b then i1 else i
instance (Infinite a, Enumerable a) => Enumerable (NonZero a) where
enumerate = unary (\a -> NonZero $ if a >= 0 then a+1 else a)
word :: (Bits a, Integral a) => Enumerate a
word = e where
e = cutOff (bitSize' e+1) $ unary (fromInteger . nat)
int :: (Bits a, Integral a) => Enumerate a
int = e where
e = cutOff (bitSize' e+1) $ unary fromInteger
cutOff :: Int -> Enumerate a -> Enumerate a
cutOff n e = Enumerate prts (fmap (cutOff n) (optimiser e)) where
prts = toRev$ take n $ parts e
bitSize' :: Bits a => f a -> Int
bitSize' f = hlp undefined f where
hlp :: Bits a => a -> f a -> Int
hlp a _ = bitSize a
instance Enumerable Word where
enumerate = word
instance Enumerable Word8 where
enumerate = word
instance Enumerable Word16 where
enumerate = word
instance Enumerable Word32 where
enumerate = word
instance Enumerable Word64 where
enumerate = word
instance Enumerable Int where
enumerate = int
instance Enumerable Int8 where
enumerate = int
instance Enumerable Int16 where
enumerate = int
instance Enumerable Int32 where
enumerate = int
instance Enumerable Int64 where
enumerate = int
instance Enumerable Double where
enumerate = unary (funcurry encodeFloat)
instance Enumerable Float where
enumerate = unary (funcurry encodeFloat)
instance (Infinite a, Enumerable a) => Enumerable (Ratio a) where
enumerate = unary $ funcurry $ \a b -> a % nonZero b
instance Enumerable Char where
enumerate = cutOff 8 $ unary (toEnum . fromIntegral :: Word -> Char)
instance Enumerable a_12 =>
Enumerable ([] a_12) where
enumerate
= consts
[pure [],
unary (funcurry (:))]
instance Enumerable Bool where
enumerate = consts [pure False, pure True]
instance Enumerable () where
enumerate = consts [pure ()]
instance (Enumerable a_12, Enumerable b_13) =>
Enumerable ((,) a_12 b_13) where
enumerate = consts [unary (funcurry (,))]
instance (Enumerable a_12, Enumerable b_13, Enumerable c_14) =>
Enumerable ((,,) a_12 b_13 c_14) where
enumerate
= consts [unary (funcurry (funcurry (,,)))]
instance (Enumerable a_12,
Enumerable b_13,
Enumerable c_14,
Enumerable d_15) =>
Enumerable ((,,,) a_12 b_13 c_14 d_15) where
enumerate
= consts
[unary (funcurry (funcurry (funcurry (,,,))))]
instance (Enumerable a_12,
Enumerable b_13,
Enumerable c_14,
Enumerable d_15,
Enumerable e_16) =>
Enumerable ((,,,,) a_12 b_13 c_14 d_15 e_16) where
enumerate
= consts
[unary
(funcurry
(funcurry (funcurry (funcurry (,,,,)))))]
instance (Enumerable a_12,
Enumerable b_13,
Enumerable c_14,
Enumerable d_15,
Enumerable e_16,
Enumerable f_17) =>
Enumerable ((,,,,,) a_12 b_13 c_14 d_15 e_16 f_17) where
enumerate
= consts
[unary
(funcurry
(funcurry
(funcurry (funcurry (funcurry (,,,,,))))))]
instance (Enumerable a_12,
Enumerable b_13,
Enumerable c_14,
Enumerable d_15,
Enumerable e_16,
Enumerable f_17,
Enumerable g_18) =>
Enumerable ((,,,,,,) a_12 b_13 c_14 d_15 e_16 f_17 g_18) where
enumerate
= consts
[unary
(funcurry
(funcurry
(funcurry
(funcurry (funcurry (funcurry (,,,,,,)))))))]
instance (Enumerable a_acKx, Enumerable b_acKy) =>
Enumerable (Either a_acKx b_acKy) where
enumerate = consts [unary Left, unary Right]
instance Enumerable a_a1aW => Enumerable (Maybe a_a1aW) where
enumerate = consts [pure Nothing, unary Just]
instance Enumerable Ordering where
enumerate = consts [pure LT, pure EQ, pure GT]