module Test.Feat.Modifiers(
NonEmpty(..),
mkNonEmpty,
Infinite(..),
Nat(..),
NonZero(..),
Unicode(..),
unicodes,
Printable(..),
printables
) where
import Test.Feat.Enumerate
import Test.Feat.Class
import Test.Feat.Internals.Newtypes
newtype NonEmpty a = NonEmpty {nonEmpty :: [a]}
deriving (Typeable, Show)
mkNonEmpty :: (a,[a]) -> NonEmpty a
mkNonEmpty (x,xs) = NonEmpty $ x:xs
instance Enumerable a => Enumerable (NonEmpty a) where
enumerate = unary $ mkNonEmpty
enumerateBounded :: (Enum a) => Int -> Int -> Enumerate a
enumerateBounded from to = let e = Enumerate prts (return e) in e
where
prts = toRev$ map (\p -> Finite (crd p) (sel p)) [0..]
crd p
| p <= 0 = 0
| p == 1 = 1
| 2^(p1) > num = max 0 (num 2^(p2))
| otherwise = 2^(p2)
sel 1 0 = toEnum from
sel p i = toEnum $ 2^(p2) + fromInteger i + from
num = toInteger $ to from
newtype Unicode = Unicode {unicode :: Char}
deriving (Typeable, Show, Eq, Ord)
instance Enumerable Unicode where
enumerate = fmap Unicode $ enumerateBounded
(fromEnum (minBound :: Char))
(fromEnum (maxBound :: Char))
unicodes :: [Unicode] -> String
unicodes = map unicode
newtype Printable = Printable {printable :: Char}
deriving (Typeable, Show)
instance Enumerable Printable where
enumerate = fmap Printable $ enumerateBounded 32 126
printables :: [Printable] -> String
printables = map printable