module Test.StateMachine.Types.References
( Reference(..)
, concrete
, opaque
, Opaque(..)
, Symbolic(..)
, Concrete(..)
, Var(..)
) where
import Data.Functor.Classes
(Eq1(..), Ord1(..), Show1(..), compare1, eq1,
showsPrec1)
import Data.Typeable
(Typeable)
import Text.Read
(readPrec)
import Test.StateMachine.Types.HFunctor
data Reference v a = Reference (v a)
concrete :: Reference Concrete a -> a
concrete (Reference (Concrete x)) = x
opaque :: Reference Concrete (Opaque a) -> a
opaque (Reference (Concrete (Opaque x))) = x
instance (Eq1 v, Eq a) => Eq (Reference v a) where
(==) (Reference x) (Reference y) = eq1 x y
instance (Ord1 v, Ord a) => Ord (Reference v a) where
compare (Reference x) (Reference y) = compare1 x y
instance (Show a, Show1 v) => Show (Reference v a) where
showsPrec p (Reference x) =
showParen (p >= 11) $
showsPrec1 11 x
instance HTraversable Reference where
htraverse f (Reference v) = fmap Reference (f v)
instance HFunctor Reference
instance HFoldable Reference
newtype Opaque a = Opaque
{ unOpaque :: a
} deriving (Eq, Ord)
instance Show (Opaque a) where
showsPrec _ (Opaque _) = showString "Opaque"
newtype Var = Var Int
deriving (Eq, Ord, Show, Num, Read)
data Symbolic a where
Symbolic :: Typeable a => Var -> Symbolic a
deriving instance Eq (Symbolic a)
deriving instance Ord (Symbolic a)
instance Show (Symbolic a) where
showsPrec p (Symbolic x) = showsPrec p x
instance Show1 Symbolic where
liftShowsPrec _ _ p (Symbolic x) = showsPrec p x
instance Typeable a => Read (Symbolic a) where
readPrec = Symbolic <$> readPrec
instance Eq1 Symbolic where
liftEq _ (Symbolic x) (Symbolic y) = x == y
instance Ord1 Symbolic where
liftCompare _ (Symbolic x) (Symbolic y) = compare x y
newtype Concrete a where
Concrete :: a -> Concrete a
deriving (Eq, Ord, Functor, Foldable, Traversable)
instance Show a => Show (Concrete a) where
showsPrec = showsPrec1
instance Show1 Concrete where
liftShowsPrec sp _ p (Concrete x) = sp p x
instance Eq1 Concrete where
liftEq eq (Concrete x) (Concrete y) = eq x y
instance Ord1 Concrete where
liftCompare comp (Concrete x) (Concrete y) = comp x y