{-# LANGUAGE DeriveDataTypeable #-}
module Isabelle.IsaSign where
import qualified Data.Map as Map
import Data.Data
import Data.List
import Common.Utils (splitOn)
type TName = String
data AltSyntax = AltSyntax String [Int] Int
deriving (Int -> AltSyntax -> ShowS
[AltSyntax] -> ShowS
AltSyntax -> String
(Int -> AltSyntax -> ShowS)
-> (AltSyntax -> String)
-> ([AltSyntax] -> ShowS)
-> Show AltSyntax
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AltSyntax] -> ShowS
$cshowList :: [AltSyntax] -> ShowS
show :: AltSyntax -> String
$cshow :: AltSyntax -> String
showsPrec :: Int -> AltSyntax -> ShowS
$cshowsPrec :: Int -> AltSyntax -> ShowS
Show, AltSyntax -> AltSyntax -> Bool
(AltSyntax -> AltSyntax -> Bool)
-> (AltSyntax -> AltSyntax -> Bool) -> Eq AltSyntax
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AltSyntax -> AltSyntax -> Bool
$c/= :: AltSyntax -> AltSyntax -> Bool
== :: AltSyntax -> AltSyntax -> Bool
$c== :: AltSyntax -> AltSyntax -> Bool
Eq, Eq AltSyntax
Eq AltSyntax =>
(AltSyntax -> AltSyntax -> Ordering)
-> (AltSyntax -> AltSyntax -> Bool)
-> (AltSyntax -> AltSyntax -> Bool)
-> (AltSyntax -> AltSyntax -> Bool)
-> (AltSyntax -> AltSyntax -> Bool)
-> (AltSyntax -> AltSyntax -> AltSyntax)
-> (AltSyntax -> AltSyntax -> AltSyntax)
-> Ord AltSyntax
AltSyntax -> AltSyntax -> Bool
AltSyntax -> AltSyntax -> Ordering
AltSyntax -> AltSyntax -> AltSyntax
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AltSyntax -> AltSyntax -> AltSyntax
$cmin :: AltSyntax -> AltSyntax -> AltSyntax
max :: AltSyntax -> AltSyntax -> AltSyntax
$cmax :: AltSyntax -> AltSyntax -> AltSyntax
>= :: AltSyntax -> AltSyntax -> Bool
$c>= :: AltSyntax -> AltSyntax -> Bool
> :: AltSyntax -> AltSyntax -> Bool
$c> :: AltSyntax -> AltSyntax -> Bool
<= :: AltSyntax -> AltSyntax -> Bool
$c<= :: AltSyntax -> AltSyntax -> Bool
< :: AltSyntax -> AltSyntax -> Bool
$c< :: AltSyntax -> AltSyntax -> Bool
compare :: AltSyntax -> AltSyntax -> Ordering
$ccompare :: AltSyntax -> AltSyntax -> Ordering
$cp1Ord :: Eq AltSyntax
Ord, Typeable, Typeable AltSyntax
Constr
DataType
Typeable AltSyntax =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltSyntax -> c AltSyntax)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AltSyntax)
-> (AltSyntax -> Constr)
-> (AltSyntax -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AltSyntax))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltSyntax))
-> ((forall b. Data b => b -> b) -> AltSyntax -> AltSyntax)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r)
-> (forall u. (forall d. Data d => d -> u) -> AltSyntax -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AltSyntax -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax)
-> Data AltSyntax
AltSyntax -> Constr
AltSyntax -> DataType
(forall b. Data b => b -> b) -> AltSyntax -> AltSyntax
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltSyntax -> c AltSyntax
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AltSyntax
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AltSyntax -> u
forall u. (forall d. Data d => d -> u) -> AltSyntax -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AltSyntax
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltSyntax -> c AltSyntax
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AltSyntax)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltSyntax)
$cAltSyntax :: Constr
$tAltSyntax :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
gmapMp :: (forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
gmapM :: (forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AltSyntax -> m AltSyntax
gmapQi :: Int -> (forall d. Data d => d -> u) -> AltSyntax -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AltSyntax -> u
gmapQ :: (forall d. Data d => d -> u) -> AltSyntax -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AltSyntax -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AltSyntax -> r
gmapT :: (forall b. Data b => b -> b) -> AltSyntax -> AltSyntax
$cgmapT :: (forall b. Data b => b -> b) -> AltSyntax -> AltSyntax
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltSyntax)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltSyntax)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c AltSyntax)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AltSyntax)
dataTypeOf :: AltSyntax -> DataType
$cdataTypeOf :: AltSyntax -> DataType
toConstr :: AltSyntax -> Constr
$ctoConstr :: AltSyntax -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AltSyntax
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AltSyntax
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltSyntax -> c AltSyntax
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AltSyntax -> c AltSyntax
$cp1Data :: Typeable AltSyntax
Data)
data VName = VName
{ VName -> String
new :: String
, VName -> Maybe AltSyntax
altSyn :: Maybe AltSyntax
} deriving (Int -> VName -> ShowS
[VName] -> ShowS
VName -> String
(Int -> VName -> ShowS)
-> (VName -> String) -> ([VName] -> ShowS) -> Show VName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VName] -> ShowS
$cshowList :: [VName] -> ShowS
show :: VName -> String
$cshow :: VName -> String
showsPrec :: Int -> VName -> ShowS
$cshowsPrec :: Int -> VName -> ShowS
Show, Typeable, Typeable VName
Constr
DataType
Typeable VName =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VName -> c VName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VName)
-> (VName -> Constr)
-> (VName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VName))
-> ((forall b. Data b => b -> b) -> VName -> VName)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r)
-> (forall u. (forall d. Data d => d -> u) -> VName -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> VName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VName -> m VName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VName -> m VName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VName -> m VName)
-> Data VName
VName -> Constr
VName -> DataType
(forall b. Data b => b -> b) -> VName -> VName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VName -> c VName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VName
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VName -> u
forall u. (forall d. Data d => d -> u) -> VName -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VName -> m VName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VName -> m VName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VName -> c VName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VName)
$cVName :: Constr
$tVName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> VName -> m VName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VName -> m VName
gmapMp :: (forall d. Data d => d -> m d) -> VName -> m VName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VName -> m VName
gmapM :: (forall d. Data d => d -> m d) -> VName -> m VName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VName -> m VName
gmapQi :: Int -> (forall d. Data d => d -> u) -> VName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VName -> u
gmapQ :: (forall d. Data d => d -> u) -> VName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VName -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VName -> r
gmapT :: (forall b. Data b => b -> b) -> VName -> VName
$cgmapT :: (forall b. Data b => b -> b) -> VName -> VName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VName)
dataTypeOf :: VName -> DataType
$cdataTypeOf :: VName -> DataType
toConstr :: VName -> Constr
$ctoConstr :: VName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VName -> c VName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VName -> c VName
$cp1Data :: Typeable VName
Data)
instance Eq VName where
v1 :: VName
v1 == :: VName -> VName -> Bool
== v2 :: VName
v2 = VName -> String
new VName
v1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== VName -> String
new VName
v2
instance Ord VName where
v1 :: VName
v1 <= :: VName -> VName -> Bool
<= v2 :: VName
v2 = VName -> String
new VName
v1 String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= VName -> String
new VName
v2
orig :: VName -> String
orig :: VName -> String
orig = VName -> String
new
data QName = QName
{ QName -> String
qname :: String
, QName -> [String]
qualifiers :: [String] }
deriving (QName -> QName -> Bool
(QName -> QName -> Bool) -> (QName -> QName -> Bool) -> Eq QName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QName -> QName -> Bool
$c/= :: QName -> QName -> Bool
== :: QName -> QName -> Bool
$c== :: QName -> QName -> Bool
Eq, Eq QName
Eq QName =>
(QName -> QName -> Ordering)
-> (QName -> QName -> Bool)
-> (QName -> QName -> Bool)
-> (QName -> QName -> Bool)
-> (QName -> QName -> Bool)
-> (QName -> QName -> QName)
-> (QName -> QName -> QName)
-> Ord QName
QName -> QName -> Bool
QName -> QName -> Ordering
QName -> QName -> QName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QName -> QName -> QName
$cmin :: QName -> QName -> QName
max :: QName -> QName -> QName
$cmax :: QName -> QName -> QName
>= :: QName -> QName -> Bool
$c>= :: QName -> QName -> Bool
> :: QName -> QName -> Bool
$c> :: QName -> QName -> Bool
<= :: QName -> QName -> Bool
$c<= :: QName -> QName -> Bool
< :: QName -> QName -> Bool
$c< :: QName -> QName -> Bool
compare :: QName -> QName -> Ordering
$ccompare :: QName -> QName -> Ordering
$cp1Ord :: Eq QName
Ord, Typeable, Typeable QName
Constr
DataType
Typeable QName =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QName -> c QName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QName)
-> (QName -> Constr)
-> (QName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QName))
-> ((forall b. Data b => b -> b) -> QName -> QName)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r)
-> (forall u. (forall d. Data d => d -> u) -> QName -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> QName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QName -> m QName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QName -> m QName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QName -> m QName)
-> Data QName
QName -> Constr
QName -> DataType
(forall b. Data b => b -> b) -> QName -> QName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QName -> c QName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QName
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> QName -> u
forall u. (forall d. Data d => d -> u) -> QName -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QName -> m QName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QName -> m QName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QName -> c QName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QName)
$cQName :: Constr
$tQName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> QName -> m QName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QName -> m QName
gmapMp :: (forall d. Data d => d -> m d) -> QName -> m QName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QName -> m QName
gmapM :: (forall d. Data d => d -> m d) -> QName -> m QName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QName -> m QName
gmapQi :: Int -> (forall d. Data d => d -> u) -> QName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QName -> u
gmapQ :: (forall d. Data d => d -> u) -> QName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> QName -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QName -> r
gmapT :: (forall b. Data b => b -> b) -> QName -> QName
$cgmapT :: (forall b. Data b => b -> b) -> QName -> QName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c QName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QName)
dataTypeOf :: QName -> DataType
$cdataTypeOf :: QName -> DataType
toConstr :: QName -> Constr
$ctoConstr :: QName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QName -> c QName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QName -> c QName
$cp1Data :: Typeable QName
Data)
instance Show QName where
show :: QName -> String
show q :: QName
q = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate "." ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ QName -> [String]
qualifiers QName
q [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [QName -> String
qname QName
q]
mkQName :: String -> QName
mkQName :: String -> QName
mkQName s :: String
s = case Char -> String -> [String]
forall a. Eq a => a -> [a] -> [[a]]
splitOn '.' String
s of
n :: String
n : q :: [String]
q -> QName :: String -> [String] -> QName
QName {qname :: String
qname = String
n, qualifiers :: [String]
qualifiers = [String]
q}
_ -> String -> QName
forall a. HasCallStack => String -> a
error (String -> QName) -> String -> QName
forall a b. (a -> b) -> a -> b
$ "empty name!" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s
data Indexname = Indexname
{ Indexname -> String
unindexed :: String
, Indexname -> Int
indexOffset :: Int
} deriving (Eq Indexname
Eq Indexname =>
(Indexname -> Indexname -> Ordering)
-> (Indexname -> Indexname -> Bool)
-> (Indexname -> Indexname -> Bool)
-> (Indexname -> Indexname -> Bool)
-> (Indexname -> Indexname -> Bool)
-> (Indexname -> Indexname -> Indexname)
-> (Indexname -> Indexname -> Indexname)
-> Ord Indexname
Indexname -> Indexname -> Bool
Indexname -> Indexname -> Ordering
Indexname -> Indexname -> Indexname
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Indexname -> Indexname -> Indexname
$cmin :: Indexname -> Indexname -> Indexname
max :: Indexname -> Indexname -> Indexname
$cmax :: Indexname -> Indexname -> Indexname
>= :: Indexname -> Indexname -> Bool
$c>= :: Indexname -> Indexname -> Bool
> :: Indexname -> Indexname -> Bool
$c> :: Indexname -> Indexname -> Bool
<= :: Indexname -> Indexname -> Bool
$c<= :: Indexname -> Indexname -> Bool
< :: Indexname -> Indexname -> Bool
$c< :: Indexname -> Indexname -> Bool
compare :: Indexname -> Indexname -> Ordering
$ccompare :: Indexname -> Indexname -> Ordering
$cp1Ord :: Eq Indexname
Ord, Indexname -> Indexname -> Bool
(Indexname -> Indexname -> Bool)
-> (Indexname -> Indexname -> Bool) -> Eq Indexname
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Indexname -> Indexname -> Bool
$c/= :: Indexname -> Indexname -> Bool
== :: Indexname -> Indexname -> Bool
$c== :: Indexname -> Indexname -> Bool
Eq, Int -> Indexname -> ShowS
[Indexname] -> ShowS
Indexname -> String
(Int -> Indexname -> ShowS)
-> (Indexname -> String)
-> ([Indexname] -> ShowS)
-> Show Indexname
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Indexname] -> ShowS
$cshowList :: [Indexname] -> ShowS
show :: Indexname -> String
$cshow :: Indexname -> String
showsPrec :: Int -> Indexname -> ShowS
$cshowsPrec :: Int -> Indexname -> ShowS
Show, Typeable, Typeable Indexname
Constr
DataType
Typeable Indexname =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Indexname -> c Indexname)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Indexname)
-> (Indexname -> Constr)
-> (Indexname -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Indexname))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Indexname))
-> ((forall b. Data b => b -> b) -> Indexname -> Indexname)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r)
-> (forall u. (forall d. Data d => d -> u) -> Indexname -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Indexname -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname)
-> Data Indexname
Indexname -> Constr
Indexname -> DataType
(forall b. Data b => b -> b) -> Indexname -> Indexname
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Indexname -> c Indexname
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Indexname
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Indexname -> u
forall u. (forall d. Data d => d -> u) -> Indexname -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Indexname
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Indexname -> c Indexname
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Indexname)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Indexname)
$cIndexname :: Constr
$tIndexname :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Indexname -> m Indexname
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname
gmapMp :: (forall d. Data d => d -> m d) -> Indexname -> m Indexname
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname
gmapM :: (forall d. Data d => d -> m d) -> Indexname -> m Indexname
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Indexname -> m Indexname
gmapQi :: Int -> (forall d. Data d => d -> u) -> Indexname -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Indexname -> u
gmapQ :: (forall d. Data d => d -> u) -> Indexname -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Indexname -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Indexname -> r
gmapT :: (forall b. Data b => b -> b) -> Indexname -> Indexname
$cgmapT :: (forall b. Data b => b -> b) -> Indexname -> Indexname
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Indexname)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Indexname)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Indexname)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Indexname)
dataTypeOf :: Indexname -> DataType
$cdataTypeOf :: Indexname -> DataType
toConstr :: Indexname -> Constr
$ctoConstr :: Indexname -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Indexname
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Indexname
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Indexname -> c Indexname
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Indexname -> c Indexname
$cp1Data :: Typeable Indexname
Data)
data IsaClass = IsaClass String deriving (Eq IsaClass
Eq IsaClass =>
(IsaClass -> IsaClass -> Ordering)
-> (IsaClass -> IsaClass -> Bool)
-> (IsaClass -> IsaClass -> Bool)
-> (IsaClass -> IsaClass -> Bool)
-> (IsaClass -> IsaClass -> Bool)
-> (IsaClass -> IsaClass -> IsaClass)
-> (IsaClass -> IsaClass -> IsaClass)
-> Ord IsaClass
IsaClass -> IsaClass -> Bool
IsaClass -> IsaClass -> Ordering
IsaClass -> IsaClass -> IsaClass
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IsaClass -> IsaClass -> IsaClass
$cmin :: IsaClass -> IsaClass -> IsaClass
max :: IsaClass -> IsaClass -> IsaClass
$cmax :: IsaClass -> IsaClass -> IsaClass
>= :: IsaClass -> IsaClass -> Bool
$c>= :: IsaClass -> IsaClass -> Bool
> :: IsaClass -> IsaClass -> Bool
$c> :: IsaClass -> IsaClass -> Bool
<= :: IsaClass -> IsaClass -> Bool
$c<= :: IsaClass -> IsaClass -> Bool
< :: IsaClass -> IsaClass -> Bool
$c< :: IsaClass -> IsaClass -> Bool
compare :: IsaClass -> IsaClass -> Ordering
$ccompare :: IsaClass -> IsaClass -> Ordering
$cp1Ord :: Eq IsaClass
Ord, IsaClass -> IsaClass -> Bool
(IsaClass -> IsaClass -> Bool)
-> (IsaClass -> IsaClass -> Bool) -> Eq IsaClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsaClass -> IsaClass -> Bool
$c/= :: IsaClass -> IsaClass -> Bool
== :: IsaClass -> IsaClass -> Bool
$c== :: IsaClass -> IsaClass -> Bool
Eq, Int -> IsaClass -> ShowS
[IsaClass] -> ShowS
IsaClass -> String
(Int -> IsaClass -> ShowS)
-> (IsaClass -> String) -> ([IsaClass] -> ShowS) -> Show IsaClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsaClass] -> ShowS
$cshowList :: [IsaClass] -> ShowS
show :: IsaClass -> String
$cshow :: IsaClass -> String
showsPrec :: Int -> IsaClass -> ShowS
$cshowsPrec :: Int -> IsaClass -> ShowS
Show, Typeable, Typeable IsaClass
Constr
DataType
Typeable IsaClass =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaClass -> c IsaClass)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaClass)
-> (IsaClass -> Constr)
-> (IsaClass -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsaClass))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaClass))
-> ((forall b. Data b => b -> b) -> IsaClass -> IsaClass)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r)
-> (forall u. (forall d. Data d => d -> u) -> IsaClass -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> IsaClass -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass)
-> Data IsaClass
IsaClass -> Constr
IsaClass -> DataType
(forall b. Data b => b -> b) -> IsaClass -> IsaClass
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaClass -> c IsaClass
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaClass
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IsaClass -> u
forall u. (forall d. Data d => d -> u) -> IsaClass -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaClass
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaClass -> c IsaClass
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsaClass)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaClass)
$cIsaClass :: Constr
$tIsaClass :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
gmapMp :: (forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
gmapM :: (forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IsaClass -> m IsaClass
gmapQi :: Int -> (forall d. Data d => d -> u) -> IsaClass -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IsaClass -> u
gmapQ :: (forall d. Data d => d -> u) -> IsaClass -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IsaClass -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaClass -> r
gmapT :: (forall b. Data b => b -> b) -> IsaClass -> IsaClass
$cgmapT :: (forall b. Data b => b -> b) -> IsaClass -> IsaClass
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaClass)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaClass)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c IsaClass)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsaClass)
dataTypeOf :: IsaClass -> DataType
$cdataTypeOf :: IsaClass -> DataType
toConstr :: IsaClass -> Constr
$ctoConstr :: IsaClass -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaClass
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaClass
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaClass -> c IsaClass
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaClass -> c IsaClass
$cp1Data :: Typeable IsaClass
Data)
type Sort = [IsaClass]
data Typ = Type { Typ -> String
typeId :: TName,
Typ -> [IsaClass]
typeSort :: Sort,
Typ -> [Typ]
typeArgs :: [Typ] }
| TFree { typeId :: TName,
typeSort :: Sort }
| TVar { Typ -> Indexname
indexname :: Indexname,
typeSort :: Sort }
deriving (Typ -> Typ -> Bool
(Typ -> Typ -> Bool) -> (Typ -> Typ -> Bool) -> Eq Typ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Typ -> Typ -> Bool
$c/= :: Typ -> Typ -> Bool
== :: Typ -> Typ -> Bool
$c== :: Typ -> Typ -> Bool
Eq, Eq Typ
Eq Typ =>
(Typ -> Typ -> Ordering)
-> (Typ -> Typ -> Bool)
-> (Typ -> Typ -> Bool)
-> (Typ -> Typ -> Bool)
-> (Typ -> Typ -> Bool)
-> (Typ -> Typ -> Typ)
-> (Typ -> Typ -> Typ)
-> Ord Typ
Typ -> Typ -> Bool
Typ -> Typ -> Ordering
Typ -> Typ -> Typ
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Typ -> Typ -> Typ
$cmin :: Typ -> Typ -> Typ
max :: Typ -> Typ -> Typ
$cmax :: Typ -> Typ -> Typ
>= :: Typ -> Typ -> Bool
$c>= :: Typ -> Typ -> Bool
> :: Typ -> Typ -> Bool
$c> :: Typ -> Typ -> Bool
<= :: Typ -> Typ -> Bool
$c<= :: Typ -> Typ -> Bool
< :: Typ -> Typ -> Bool
$c< :: Typ -> Typ -> Bool
compare :: Typ -> Typ -> Ordering
$ccompare :: Typ -> Typ -> Ordering
$cp1Ord :: Eq Typ
Ord, Int -> Typ -> ShowS
[Typ] -> ShowS
Typ -> String
(Int -> Typ -> ShowS)
-> (Typ -> String) -> ([Typ] -> ShowS) -> Show Typ
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Typ] -> ShowS
$cshowList :: [Typ] -> ShowS
show :: Typ -> String
$cshow :: Typ -> String
showsPrec :: Int -> Typ -> ShowS
$cshowsPrec :: Int -> Typ -> ShowS
Show, Typeable, Typeable Typ
Constr
DataType
Typeable Typ =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Typ -> c Typ)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Typ)
-> (Typ -> Constr)
-> (Typ -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Typ))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Typ))
-> ((forall b. Data b => b -> b) -> Typ -> Typ)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r)
-> (forall u. (forall d. Data d => d -> u) -> Typ -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Typ -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ)
-> Data Typ
Typ -> Constr
Typ -> DataType
(forall b. Data b => b -> b) -> Typ -> Typ
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Typ -> c Typ
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Typ
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Typ -> u
forall u. (forall d. Data d => d -> u) -> Typ -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Typ
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Typ -> c Typ
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Typ)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Typ)
$cTVar :: Constr
$cTFree :: Constr
$cType :: Constr
$tTyp :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Typ -> m Typ
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ
gmapMp :: (forall d. Data d => d -> m d) -> Typ -> m Typ
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ
gmapM :: (forall d. Data d => d -> m d) -> Typ -> m Typ
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Typ -> m Typ
gmapQi :: Int -> (forall d. Data d => d -> u) -> Typ -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Typ -> u
gmapQ :: (forall d. Data d => d -> u) -> Typ -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Typ -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typ -> r
gmapT :: (forall b. Data b => b -> b) -> Typ -> Typ
$cgmapT :: (forall b. Data b => b -> b) -> Typ -> Typ
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Typ)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Typ)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Typ)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Typ)
dataTypeOf :: Typ -> DataType
$cdataTypeOf :: Typ -> DataType
toConstr :: Typ -> Constr
$ctoConstr :: Typ -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Typ
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Typ
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Typ -> c Typ
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Typ -> c Typ
$cp1Data :: Typeable Typ
Data)
data Continuity = IsCont Bool | NotCont deriving (Continuity -> Continuity -> Bool
(Continuity -> Continuity -> Bool)
-> (Continuity -> Continuity -> Bool) -> Eq Continuity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Continuity -> Continuity -> Bool
$c/= :: Continuity -> Continuity -> Bool
== :: Continuity -> Continuity -> Bool
$c== :: Continuity -> Continuity -> Bool
Eq, Eq Continuity
Eq Continuity =>
(Continuity -> Continuity -> Ordering)
-> (Continuity -> Continuity -> Bool)
-> (Continuity -> Continuity -> Bool)
-> (Continuity -> Continuity -> Bool)
-> (Continuity -> Continuity -> Bool)
-> (Continuity -> Continuity -> Continuity)
-> (Continuity -> Continuity -> Continuity)
-> Ord Continuity
Continuity -> Continuity -> Bool
Continuity -> Continuity -> Ordering
Continuity -> Continuity -> Continuity
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Continuity -> Continuity -> Continuity
$cmin :: Continuity -> Continuity -> Continuity
max :: Continuity -> Continuity -> Continuity
$cmax :: Continuity -> Continuity -> Continuity
>= :: Continuity -> Continuity -> Bool
$c>= :: Continuity -> Continuity -> Bool
> :: Continuity -> Continuity -> Bool
$c> :: Continuity -> Continuity -> Bool
<= :: Continuity -> Continuity -> Bool
$c<= :: Continuity -> Continuity -> Bool
< :: Continuity -> Continuity -> Bool
$c< :: Continuity -> Continuity -> Bool
compare :: Continuity -> Continuity -> Ordering
$ccompare :: Continuity -> Continuity -> Ordering
$cp1Ord :: Eq Continuity
Ord, Int -> Continuity -> ShowS
[Continuity] -> ShowS
Continuity -> String
(Int -> Continuity -> ShowS)
-> (Continuity -> String)
-> ([Continuity] -> ShowS)
-> Show Continuity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Continuity] -> ShowS
$cshowList :: [Continuity] -> ShowS
show :: Continuity -> String
$cshow :: Continuity -> String
showsPrec :: Int -> Continuity -> ShowS
$cshowsPrec :: Int -> Continuity -> ShowS
Show, Typeable, Typeable Continuity
Constr
DataType
Typeable Continuity =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Continuity -> c Continuity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Continuity)
-> (Continuity -> Constr)
-> (Continuity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Continuity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Continuity))
-> ((forall b. Data b => b -> b) -> Continuity -> Continuity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r)
-> (forall u. (forall d. Data d => d -> u) -> Continuity -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Continuity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity)
-> Data Continuity
Continuity -> Constr
Continuity -> DataType
(forall b. Data b => b -> b) -> Continuity -> Continuity
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Continuity -> c Continuity
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Continuity
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Continuity -> u
forall u. (forall d. Data d => d -> u) -> Continuity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Continuity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Continuity -> c Continuity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Continuity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Continuity)
$cNotCont :: Constr
$cIsCont :: Constr
$tContinuity :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Continuity -> m Continuity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity
gmapMp :: (forall d. Data d => d -> m d) -> Continuity -> m Continuity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity
gmapM :: (forall d. Data d => d -> m d) -> Continuity -> m Continuity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Continuity -> m Continuity
gmapQi :: Int -> (forall d. Data d => d -> u) -> Continuity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Continuity -> u
gmapQ :: (forall d. Data d => d -> u) -> Continuity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Continuity -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Continuity -> r
gmapT :: (forall b. Data b => b -> b) -> Continuity -> Continuity
$cgmapT :: (forall b. Data b => b -> b) -> Continuity -> Continuity
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Continuity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Continuity)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Continuity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Continuity)
dataTypeOf :: Continuity -> DataType
$cdataTypeOf :: Continuity -> DataType
toConstr :: Continuity -> Constr
$ctoConstr :: Continuity -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Continuity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Continuity
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Continuity -> c Continuity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Continuity -> c Continuity
$cp1Data :: Typeable Continuity
Data)
data TAttr = TFun | TMet | TCon | NA deriving (TAttr -> TAttr -> Bool
(TAttr -> TAttr -> Bool) -> (TAttr -> TAttr -> Bool) -> Eq TAttr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TAttr -> TAttr -> Bool
$c/= :: TAttr -> TAttr -> Bool
== :: TAttr -> TAttr -> Bool
$c== :: TAttr -> TAttr -> Bool
Eq, Eq TAttr
Eq TAttr =>
(TAttr -> TAttr -> Ordering)
-> (TAttr -> TAttr -> Bool)
-> (TAttr -> TAttr -> Bool)
-> (TAttr -> TAttr -> Bool)
-> (TAttr -> TAttr -> Bool)
-> (TAttr -> TAttr -> TAttr)
-> (TAttr -> TAttr -> TAttr)
-> Ord TAttr
TAttr -> TAttr -> Bool
TAttr -> TAttr -> Ordering
TAttr -> TAttr -> TAttr
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TAttr -> TAttr -> TAttr
$cmin :: TAttr -> TAttr -> TAttr
max :: TAttr -> TAttr -> TAttr
$cmax :: TAttr -> TAttr -> TAttr
>= :: TAttr -> TAttr -> Bool
$c>= :: TAttr -> TAttr -> Bool
> :: TAttr -> TAttr -> Bool
$c> :: TAttr -> TAttr -> Bool
<= :: TAttr -> TAttr -> Bool
$c<= :: TAttr -> TAttr -> Bool
< :: TAttr -> TAttr -> Bool
$c< :: TAttr -> TAttr -> Bool
compare :: TAttr -> TAttr -> Ordering
$ccompare :: TAttr -> TAttr -> Ordering
$cp1Ord :: Eq TAttr
Ord, Int -> TAttr -> ShowS
[TAttr] -> ShowS
TAttr -> String
(Int -> TAttr -> ShowS)
-> (TAttr -> String) -> ([TAttr] -> ShowS) -> Show TAttr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TAttr] -> ShowS
$cshowList :: [TAttr] -> ShowS
show :: TAttr -> String
$cshow :: TAttr -> String
showsPrec :: Int -> TAttr -> ShowS
$cshowsPrec :: Int -> TAttr -> ShowS
Show, Typeable, Typeable TAttr
Constr
DataType
Typeable TAttr =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TAttr -> c TAttr)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TAttr)
-> (TAttr -> Constr)
-> (TAttr -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TAttr))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TAttr))
-> ((forall b. Data b => b -> b) -> TAttr -> TAttr)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r)
-> (forall u. (forall d. Data d => d -> u) -> TAttr -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> TAttr -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr)
-> Data TAttr
TAttr -> Constr
TAttr -> DataType
(forall b. Data b => b -> b) -> TAttr -> TAttr
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TAttr -> c TAttr
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TAttr
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TAttr -> u
forall u. (forall d. Data d => d -> u) -> TAttr -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TAttr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TAttr -> c TAttr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TAttr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TAttr)
$cNA :: Constr
$cTCon :: Constr
$cTMet :: Constr
$cTFun :: Constr
$tTAttr :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TAttr -> m TAttr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr
gmapMp :: (forall d. Data d => d -> m d) -> TAttr -> m TAttr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr
gmapM :: (forall d. Data d => d -> m d) -> TAttr -> m TAttr
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TAttr -> m TAttr
gmapQi :: Int -> (forall d. Data d => d -> u) -> TAttr -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TAttr -> u
gmapQ :: (forall d. Data d => d -> u) -> TAttr -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TAttr -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TAttr -> r
gmapT :: (forall b. Data b => b -> b) -> TAttr -> TAttr
$cgmapT :: (forall b. Data b => b -> b) -> TAttr -> TAttr
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TAttr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TAttr)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TAttr)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TAttr)
dataTypeOf :: TAttr -> DataType
$cdataTypeOf :: TAttr -> DataType
toConstr :: TAttr -> Constr
$ctoConstr :: TAttr -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TAttr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TAttr
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TAttr -> c TAttr
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TAttr -> c TAttr
$cp1Data :: Typeable TAttr
Data)
data DTyp = Hide { DTyp -> Typ
typ :: Typ,
DTyp -> TAttr
kon :: TAttr,
DTyp -> Maybe Int
arit :: Maybe Int }
| Disp { typ :: Typ,
kon :: TAttr,
arit :: Maybe Int }
deriving (DTyp -> DTyp -> Bool
(DTyp -> DTyp -> Bool) -> (DTyp -> DTyp -> Bool) -> Eq DTyp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DTyp -> DTyp -> Bool
$c/= :: DTyp -> DTyp -> Bool
== :: DTyp -> DTyp -> Bool
$c== :: DTyp -> DTyp -> Bool
Eq, Eq DTyp
Eq DTyp =>
(DTyp -> DTyp -> Ordering)
-> (DTyp -> DTyp -> Bool)
-> (DTyp -> DTyp -> Bool)
-> (DTyp -> DTyp -> Bool)
-> (DTyp -> DTyp -> Bool)
-> (DTyp -> DTyp -> DTyp)
-> (DTyp -> DTyp -> DTyp)
-> Ord DTyp
DTyp -> DTyp -> Bool
DTyp -> DTyp -> Ordering
DTyp -> DTyp -> DTyp
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DTyp -> DTyp -> DTyp
$cmin :: DTyp -> DTyp -> DTyp
max :: DTyp -> DTyp -> DTyp
$cmax :: DTyp -> DTyp -> DTyp
>= :: DTyp -> DTyp -> Bool
$c>= :: DTyp -> DTyp -> Bool
> :: DTyp -> DTyp -> Bool
$c> :: DTyp -> DTyp -> Bool
<= :: DTyp -> DTyp -> Bool
$c<= :: DTyp -> DTyp -> Bool
< :: DTyp -> DTyp -> Bool
$c< :: DTyp -> DTyp -> Bool
compare :: DTyp -> DTyp -> Ordering
$ccompare :: DTyp -> DTyp -> Ordering
$cp1Ord :: Eq DTyp
Ord, Int -> DTyp -> ShowS
[DTyp] -> ShowS
DTyp -> String
(Int -> DTyp -> ShowS)
-> (DTyp -> String) -> ([DTyp] -> ShowS) -> Show DTyp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DTyp] -> ShowS
$cshowList :: [DTyp] -> ShowS
show :: DTyp -> String
$cshow :: DTyp -> String
showsPrec :: Int -> DTyp -> ShowS
$cshowsPrec :: Int -> DTyp -> ShowS
Show, Typeable, Typeable DTyp
Constr
DataType
Typeable DTyp =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DTyp -> c DTyp)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DTyp)
-> (DTyp -> Constr)
-> (DTyp -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DTyp))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DTyp))
-> ((forall b. Data b => b -> b) -> DTyp -> DTyp)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r)
-> (forall u. (forall d. Data d => d -> u) -> DTyp -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> DTyp -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp)
-> Data DTyp
DTyp -> Constr
DTyp -> DataType
(forall b. Data b => b -> b) -> DTyp -> DTyp
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DTyp -> c DTyp
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DTyp
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DTyp -> u
forall u. (forall d. Data d => d -> u) -> DTyp -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DTyp
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DTyp -> c DTyp
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DTyp)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DTyp)
$cDisp :: Constr
$cHide :: Constr
$tDTyp :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> DTyp -> m DTyp
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp
gmapMp :: (forall d. Data d => d -> m d) -> DTyp -> m DTyp
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp
gmapM :: (forall d. Data d => d -> m d) -> DTyp -> m DTyp
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DTyp -> m DTyp
gmapQi :: Int -> (forall d. Data d => d -> u) -> DTyp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DTyp -> u
gmapQ :: (forall d. Data d => d -> u) -> DTyp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DTyp -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DTyp -> r
gmapT :: (forall b. Data b => b -> b) -> DTyp -> DTyp
$cgmapT :: (forall b. Data b => b -> b) -> DTyp -> DTyp
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DTyp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DTyp)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DTyp)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DTyp)
dataTypeOf :: DTyp -> DataType
$cdataTypeOf :: DTyp -> DataType
toConstr :: DTyp -> Constr
$ctoConstr :: DTyp -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DTyp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DTyp
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DTyp -> c DTyp
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DTyp -> c DTyp
$cp1Data :: Typeable DTyp
Data)
data Term =
Const { Term -> VName
termName :: VName,
Term -> DTyp
termType :: DTyp }
| Free { termName :: VName }
| Abs { Term -> Term
absVar :: Term,
Term -> Term
termId :: Term,
Term -> Continuity
continuity :: Continuity }
| App { Term -> Term
funId :: Term,
Term -> Term
argId :: Term,
continuity :: Continuity }
| If { Term -> Term
ifId :: Term,
Term -> Term
thenId :: Term,
Term -> Term
elseId :: Term,
continuity :: Continuity }
| Case { termId :: Term,
Term -> [(Term, Term)]
caseSubst :: [(Term, Term)] }
| Let { Term -> [(Term, Term)]
letSubst :: [(Term, Term)],
Term -> Term
inId :: Term }
| IsaEq { Term -> Term
firstTerm :: Term,
Term -> Term
secondTerm :: Term }
| Tuplex [Term] Continuity
| Set SetDecl
deriving (Term -> Term -> Bool
(Term -> Term -> Bool) -> (Term -> Term -> Bool) -> Eq Term
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Term -> Term -> Bool
$c/= :: Term -> Term -> Bool
== :: Term -> Term -> Bool
$c== :: Term -> Term -> Bool
Eq, Eq Term
Eq Term =>
(Term -> Term -> Ordering)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Term)
-> (Term -> Term -> Term)
-> Ord Term
Term -> Term -> Bool
Term -> Term -> Ordering
Term -> Term -> Term
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Term -> Term -> Term
$cmin :: Term -> Term -> Term
max :: Term -> Term -> Term
$cmax :: Term -> Term -> Term
>= :: Term -> Term -> Bool
$c>= :: Term -> Term -> Bool
> :: Term -> Term -> Bool
$c> :: Term -> Term -> Bool
<= :: Term -> Term -> Bool
$c<= :: Term -> Term -> Bool
< :: Term -> Term -> Bool
$c< :: Term -> Term -> Bool
compare :: Term -> Term -> Ordering
$ccompare :: Term -> Term -> Ordering
$cp1Ord :: Eq Term
Ord, Int -> Term -> ShowS
[Term] -> ShowS
Term -> String
(Int -> Term -> ShowS)
-> (Term -> String) -> ([Term] -> ShowS) -> Show Term
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Term] -> ShowS
$cshowList :: [Term] -> ShowS
show :: Term -> String
$cshow :: Term -> String
showsPrec :: Int -> Term -> ShowS
$cshowsPrec :: Int -> Term -> ShowS
Show, Typeable, Typeable Term
Constr
DataType
Typeable Term =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Term -> c Term)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Term)
-> (Term -> Constr)
-> (Term -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Term))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Term))
-> ((forall b. Data b => b -> b) -> Term -> Term)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r)
-> (forall u. (forall d. Data d => d -> u) -> Term -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Term -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Term -> m Term)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Term -> m Term)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Term -> m Term)
-> Data Term
Term -> Constr
Term -> DataType
(forall b. Data b => b -> b) -> Term -> Term
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Term -> c Term
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Term
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Term -> u
forall u. (forall d. Data d => d -> u) -> Term -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Term -> m Term
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Term -> m Term
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Term
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Term -> c Term
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Term)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Term)
$cSet :: Constr
$cTuplex :: Constr
$cIsaEq :: Constr
$cLet :: Constr
$cCase :: Constr
$cIf :: Constr
$cApp :: Constr
$cAbs :: Constr
$cFree :: Constr
$cConst :: Constr
$tTerm :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Term -> m Term
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Term -> m Term
gmapMp :: (forall d. Data d => d -> m d) -> Term -> m Term
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Term -> m Term
gmapM :: (forall d. Data d => d -> m d) -> Term -> m Term
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Term -> m Term
gmapQi :: Int -> (forall d. Data d => d -> u) -> Term -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Term -> u
gmapQ :: (forall d. Data d => d -> u) -> Term -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Term -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Term -> r
gmapT :: (forall b. Data b => b -> b) -> Term -> Term
$cgmapT :: (forall b. Data b => b -> b) -> Term -> Term
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Term)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Term)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Term)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Term)
dataTypeOf :: Term -> DataType
$cdataTypeOf :: Term -> DataType
toConstr :: Term -> Constr
$ctoConstr :: Term -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Term
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Term
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Term -> c Term
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Term -> c Term
$cp1Data :: Typeable Term
Data)
data Prop = Prop {
Prop -> Term
prop :: Term
, Prop -> [Term]
propPats :: [Term] } deriving (Prop -> Prop -> Bool
(Prop -> Prop -> Bool) -> (Prop -> Prop -> Bool) -> Eq Prop
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Prop -> Prop -> Bool
$c/= :: Prop -> Prop -> Bool
== :: Prop -> Prop -> Bool
$c== :: Prop -> Prop -> Bool
Eq, Eq Prop
Eq Prop =>
(Prop -> Prop -> Ordering)
-> (Prop -> Prop -> Bool)
-> (Prop -> Prop -> Bool)
-> (Prop -> Prop -> Bool)
-> (Prop -> Prop -> Bool)
-> (Prop -> Prop -> Prop)
-> (Prop -> Prop -> Prop)
-> Ord Prop
Prop -> Prop -> Bool
Prop -> Prop -> Ordering
Prop -> Prop -> Prop
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Prop -> Prop -> Prop
$cmin :: Prop -> Prop -> Prop
max :: Prop -> Prop -> Prop
$cmax :: Prop -> Prop -> Prop
>= :: Prop -> Prop -> Bool
$c>= :: Prop -> Prop -> Bool
> :: Prop -> Prop -> Bool
$c> :: Prop -> Prop -> Bool
<= :: Prop -> Prop -> Bool
$c<= :: Prop -> Prop -> Bool
< :: Prop -> Prop -> Bool
$c< :: Prop -> Prop -> Bool
compare :: Prop -> Prop -> Ordering
$ccompare :: Prop -> Prop -> Ordering
$cp1Ord :: Eq Prop
Ord, Int -> Prop -> ShowS
[Prop] -> ShowS
Prop -> String
(Int -> Prop -> ShowS)
-> (Prop -> String) -> ([Prop] -> ShowS) -> Show Prop
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Prop] -> ShowS
$cshowList :: [Prop] -> ShowS
show :: Prop -> String
$cshow :: Prop -> String
showsPrec :: Int -> Prop -> ShowS
$cshowsPrec :: Int -> Prop -> ShowS
Show, Typeable, Typeable Prop
Constr
DataType
Typeable Prop =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prop -> c Prop)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prop)
-> (Prop -> Constr)
-> (Prop -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Prop))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prop))
-> ((forall b. Data b => b -> b) -> Prop -> Prop)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r)
-> (forall u. (forall d. Data d => d -> u) -> Prop -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Prop -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop)
-> Data Prop
Prop -> Constr
Prop -> DataType
(forall b. Data b => b -> b) -> Prop -> Prop
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prop -> c Prop
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prop
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Prop -> u
forall u. (forall d. Data d => d -> u) -> Prop -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prop
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prop -> c Prop
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Prop)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prop)
$cProp :: Constr
$tProp :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Prop -> m Prop
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop
gmapMp :: (forall d. Data d => d -> m d) -> Prop -> m Prop
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop
gmapM :: (forall d. Data d => d -> m d) -> Prop -> m Prop
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Prop -> m Prop
gmapQi :: Int -> (forall d. Data d => d -> u) -> Prop -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Prop -> u
gmapQ :: (forall d. Data d => d -> u) -> Prop -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Prop -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prop -> r
gmapT :: (forall b. Data b => b -> b) -> Prop -> Prop
$cgmapT :: (forall b. Data b => b -> b) -> Prop -> Prop
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prop)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prop)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Prop)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Prop)
dataTypeOf :: Prop -> DataType
$cdataTypeOf :: Prop -> DataType
toConstr :: Prop -> Constr
$ctoConstr :: Prop -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prop
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Prop
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prop -> c Prop
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Prop -> c Prop
$cp1Data :: Typeable Prop
Data)
data Props = Props {
Props -> Maybe QName
propsName :: Maybe QName
, Props -> Maybe String
propsArgs :: Maybe String
, Props -> [Prop]
props :: [Prop] } deriving (Props -> Props -> Bool
(Props -> Props -> Bool) -> (Props -> Props -> Bool) -> Eq Props
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Props -> Props -> Bool
$c/= :: Props -> Props -> Bool
== :: Props -> Props -> Bool
$c== :: Props -> Props -> Bool
Eq, Eq Props
Eq Props =>
(Props -> Props -> Ordering)
-> (Props -> Props -> Bool)
-> (Props -> Props -> Bool)
-> (Props -> Props -> Bool)
-> (Props -> Props -> Bool)
-> (Props -> Props -> Props)
-> (Props -> Props -> Props)
-> Ord Props
Props -> Props -> Bool
Props -> Props -> Ordering
Props -> Props -> Props
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Props -> Props -> Props
$cmin :: Props -> Props -> Props
max :: Props -> Props -> Props
$cmax :: Props -> Props -> Props
>= :: Props -> Props -> Bool
$c>= :: Props -> Props -> Bool
> :: Props -> Props -> Bool
$c> :: Props -> Props -> Bool
<= :: Props -> Props -> Bool
$c<= :: Props -> Props -> Bool
< :: Props -> Props -> Bool
$c< :: Props -> Props -> Bool
compare :: Props -> Props -> Ordering
$ccompare :: Props -> Props -> Ordering
$cp1Ord :: Eq Props
Ord, Int -> Props -> ShowS
[Props] -> ShowS
Props -> String
(Int -> Props -> ShowS)
-> (Props -> String) -> ([Props] -> ShowS) -> Show Props
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Props] -> ShowS
$cshowList :: [Props] -> ShowS
show :: Props -> String
$cshow :: Props -> String
showsPrec :: Int -> Props -> ShowS
$cshowsPrec :: Int -> Props -> ShowS
Show, Typeable, Typeable Props
Constr
DataType
Typeable Props =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Props -> c Props)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Props)
-> (Props -> Constr)
-> (Props -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Props))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Props))
-> ((forall b. Data b => b -> b) -> Props -> Props)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r)
-> (forall u. (forall d. Data d => d -> u) -> Props -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Props -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Props -> m Props)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Props -> m Props)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Props -> m Props)
-> Data Props
Props -> Constr
Props -> DataType
(forall b. Data b => b -> b) -> Props -> Props
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Props -> c Props
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Props
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Props -> u
forall u. (forall d. Data d => d -> u) -> Props -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Props -> m Props
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Props -> m Props
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Props
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Props -> c Props
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Props)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Props)
$cProps :: Constr
$tProps :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Props -> m Props
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Props -> m Props
gmapMp :: (forall d. Data d => d -> m d) -> Props -> m Props
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Props -> m Props
gmapM :: (forall d. Data d => d -> m d) -> Props -> m Props
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Props -> m Props
gmapQi :: Int -> (forall d. Data d => d -> u) -> Props -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Props -> u
gmapQ :: (forall d. Data d => d -> u) -> Props -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Props -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Props -> r
gmapT :: (forall b. Data b => b -> b) -> Props -> Props
$cgmapT :: (forall b. Data b => b -> b) -> Props -> Props
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Props)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Props)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Props)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Props)
dataTypeOf :: Props -> DataType
$cdataTypeOf :: Props -> DataType
toConstr :: Props -> Constr
$ctoConstr :: Props -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Props
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Props
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Props -> c Props
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Props -> c Props
$cp1Data :: Typeable Props
Data)
data Sentence =
Sentence { Sentence -> Bool
isSimp :: Bool
, Sentence -> Bool
isRefuteAux :: Bool
, Sentence -> MetaTerm
metaTerm :: MetaTerm
, Sentence -> Maybe IsaProof
thmProof :: Maybe IsaProof }
| Instance { Sentence -> String
tName :: TName
, Sentence -> [[IsaClass]]
arityArgs :: [Sort]
, Sentence -> [IsaClass]
arityRes :: Sort
, Sentence -> [(String, Term)]
definitions :: [(String, Term)]
, Sentence -> IsaProof
instProof :: IsaProof }
| ConstDef { Sentence -> Term
senTerm :: Term }
| RecDef { Sentence -> Maybe String
keyword :: Maybe String
, Sentence -> VName
constName :: VName
, Sentence -> Maybe Typ
constType :: Maybe Typ
, Sentence -> [Term]
primRecSenTerms :: [Term] }
| TypeDef { Sentence -> Typ
newType :: Typ
, Sentence -> SetDecl
typeDef :: SetDecl
, Sentence -> IsaProof
nonEmptyPr :: IsaProof}
| Lemmas { Sentence -> String
lemmaName :: String
, Sentence -> [String]
lemmasList :: [String]}
| Locale { Sentence -> QName
localeName :: QName,
Sentence -> Ctxt
localeContext :: Ctxt,
Sentence -> [QName]
localeParents :: [QName],
Sentence -> [Sentence]
localeBody :: [Sentence] }
| Class { Sentence -> QName
className :: QName,
Sentence -> Ctxt
classContext :: Ctxt,
Sentence -> [QName]
classParents :: [QName],
Sentence -> [Sentence]
classBody :: [Sentence] }
| Datatypes [Datatype]
| Domains [Domain]
| Consts [(String, Maybe Mixfix, Typ)]
| TypeSynonym QName (Maybe Mixfix) [String] Typ
| Axioms [Axiom]
| Lemma {
Sentence -> Maybe QName
lemmaTarget :: Maybe QName,
Sentence -> Ctxt
lemmaContext :: Ctxt,
Sentence -> Maybe String
lemmaProof :: Maybe String,
Sentence -> [Props]
lemmaProps :: [Props] }
| Definition {
Sentence -> QName
definitionName :: QName,
Sentence -> Maybe Mixfix
definitionMixfix :: Maybe Mixfix,
Sentence -> Maybe String
definitionTarget :: Maybe String,
Sentence -> Typ
definitionType :: Typ,
Sentence -> [Term]
definitionVars :: [Term],
Sentence -> Term
definitionTerm :: Term }
| Fun {
Sentence -> Maybe QName
funTarget :: Maybe QName,
Sentence -> Bool
funSequential :: Bool,
Sentence -> Maybe String
funDefault :: Maybe String,
Sentence -> Bool
funDomintros :: Bool,
Sentence -> Bool
funPartials :: Bool,
Sentence -> [(String, Maybe Mixfix, Typ, [([Term], Term)])]
funEquations :: [(String, Maybe Mixfix, Typ, [([Term], Term)])] }
| Primrec {
Sentence -> Maybe QName
primrecTarget :: Maybe QName,
Sentence -> [(String, Maybe Mixfix, Typ, [([Term], Term)])]
primrecEquations :: [(String, Maybe Mixfix, Typ, [([Term], Term)])] }
| Fixrec [(String, Maybe Mixfix, Typ, [FixrecEquation])]
| Instantiation {
Sentence -> String
instantiationType :: TName,
Sentence -> ([IsaClass], [[IsaClass]])
instantiationArity :: (Sort, [Sort]),
Sentence -> [Sentence]
instantiationBody :: [Sentence] }
| InstanceProof {
Sentence -> String
instanceProof :: String }
| InstanceArity {
Sentence -> [String]
instanceTypes :: [TName],
Sentence -> ([IsaClass], [[IsaClass]])
instanceArity :: (Sort, [Sort]),
instanceProof :: String }
| InstanceSubclass {
Sentence -> String
instanceClass :: String,
Sentence -> String
instanceRel :: String,
Sentence -> String
instanceClass1 :: String,
instanceProof :: String }
| Subclass {
Sentence -> String
subclassClass :: String,
Sentence -> Maybe QName
subclassTarget :: Maybe QName,
Sentence -> String
subclassProof :: String
}
| Typedef {
Sentence -> QName
typedefName :: QName,
Sentence -> [(String, [IsaClass])]
typedefVars :: [(String, Sort)],
Sentence -> Maybe Mixfix
typedefMixfix :: Maybe Mixfix,
Sentence -> Maybe (QName, QName)
typedefMorphisms :: Maybe (QName, QName),
Sentence -> Term
typedefTerm :: Term,
Sentence -> String
typedefProof :: String }
| Defs {
Sentence -> Bool
defsUnchecked :: Bool,
Sentence -> Bool
defsOverloaded :: Bool,
Sentence -> [DefEquation]
defsEquations :: [DefEquation] }
deriving (Sentence -> Sentence -> Bool
(Sentence -> Sentence -> Bool)
-> (Sentence -> Sentence -> Bool) -> Eq Sentence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sentence -> Sentence -> Bool
$c/= :: Sentence -> Sentence -> Bool
== :: Sentence -> Sentence -> Bool
$c== :: Sentence -> Sentence -> Bool
Eq, Eq Sentence
Eq Sentence =>
(Sentence -> Sentence -> Ordering)
-> (Sentence -> Sentence -> Bool)
-> (Sentence -> Sentence -> Bool)
-> (Sentence -> Sentence -> Bool)
-> (Sentence -> Sentence -> Bool)
-> (Sentence -> Sentence -> Sentence)
-> (Sentence -> Sentence -> Sentence)
-> Ord Sentence
Sentence -> Sentence -> Bool
Sentence -> Sentence -> Ordering
Sentence -> Sentence -> Sentence
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Sentence -> Sentence -> Sentence
$cmin :: Sentence -> Sentence -> Sentence
max :: Sentence -> Sentence -> Sentence
$cmax :: Sentence -> Sentence -> Sentence
>= :: Sentence -> Sentence -> Bool
$c>= :: Sentence -> Sentence -> Bool
> :: Sentence -> Sentence -> Bool
$c> :: Sentence -> Sentence -> Bool
<= :: Sentence -> Sentence -> Bool
$c<= :: Sentence -> Sentence -> Bool
< :: Sentence -> Sentence -> Bool
$c< :: Sentence -> Sentence -> Bool
compare :: Sentence -> Sentence -> Ordering
$ccompare :: Sentence -> Sentence -> Ordering
$cp1Ord :: Eq Sentence
Ord, Int -> Sentence -> ShowS
[Sentence] -> ShowS
Sentence -> String
(Int -> Sentence -> ShowS)
-> (Sentence -> String) -> ([Sentence] -> ShowS) -> Show Sentence
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Sentence] -> ShowS
$cshowList :: [Sentence] -> ShowS
show :: Sentence -> String
$cshow :: Sentence -> String
showsPrec :: Int -> Sentence -> ShowS
$cshowsPrec :: Int -> Sentence -> ShowS
Show, Typeable, Typeable Sentence
Constr
DataType
Typeable Sentence =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sentence -> c Sentence)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Sentence)
-> (Sentence -> Constr)
-> (Sentence -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Sentence))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sentence))
-> ((forall b. Data b => b -> b) -> Sentence -> Sentence)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r)
-> (forall u. (forall d. Data d => d -> u) -> Sentence -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Sentence -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence)
-> Data Sentence
Sentence -> Constr
Sentence -> DataType
(forall b. Data b => b -> b) -> Sentence -> Sentence
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sentence -> c Sentence
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Sentence
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Sentence -> u
forall u. (forall d. Data d => d -> u) -> Sentence -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Sentence
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sentence -> c Sentence
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Sentence)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sentence)
$cDefs :: Constr
$cTypedef :: Constr
$cSubclass :: Constr
$cInstanceSubclass :: Constr
$cInstanceArity :: Constr
$cInstanceProof :: Constr
$cInstantiation :: Constr
$cFixrec :: Constr
$cPrimrec :: Constr
$cFun :: Constr
$cDefinition :: Constr
$cLemma :: Constr
$cAxioms :: Constr
$cTypeSynonym :: Constr
$cConsts :: Constr
$cDomains :: Constr
$cDatatypes :: Constr
$cClass :: Constr
$cLocale :: Constr
$cLemmas :: Constr
$cTypeDef :: Constr
$cRecDef :: Constr
$cConstDef :: Constr
$cInstance :: Constr
$cSentence :: Constr
$tSentence :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Sentence -> m Sentence
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence
gmapMp :: (forall d. Data d => d -> m d) -> Sentence -> m Sentence
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence
gmapM :: (forall d. Data d => d -> m d) -> Sentence -> m Sentence
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Sentence -> m Sentence
gmapQi :: Int -> (forall d. Data d => d -> u) -> Sentence -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Sentence -> u
gmapQ :: (forall d. Data d => d -> u) -> Sentence -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Sentence -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Sentence -> r
gmapT :: (forall b. Data b => b -> b) -> Sentence -> Sentence
$cgmapT :: (forall b. Data b => b -> b) -> Sentence -> Sentence
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sentence)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sentence)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Sentence)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Sentence)
dataTypeOf :: Sentence -> DataType
$cdataTypeOf :: Sentence -> DataType
toConstr :: Sentence -> Constr
$ctoConstr :: Sentence -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Sentence
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Sentence
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sentence -> c Sentence
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Sentence -> c Sentence
$cp1Data :: Typeable Sentence
Data)
data DefEquation = DefEquation {
DefEquation -> QName
defEquationName :: QName,
DefEquation -> String
defEquationConst :: String,
DefEquation -> Typ
defEquationConstType :: Typ,
DefEquation -> Term
defEquationTerm :: Term,
DefEquation -> String
defEquationArgs :: String } deriving (DefEquation -> DefEquation -> Bool
(DefEquation -> DefEquation -> Bool)
-> (DefEquation -> DefEquation -> Bool) -> Eq DefEquation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefEquation -> DefEquation -> Bool
$c/= :: DefEquation -> DefEquation -> Bool
== :: DefEquation -> DefEquation -> Bool
$c== :: DefEquation -> DefEquation -> Bool
Eq, Eq DefEquation
Eq DefEquation =>
(DefEquation -> DefEquation -> Ordering)
-> (DefEquation -> DefEquation -> Bool)
-> (DefEquation -> DefEquation -> Bool)
-> (DefEquation -> DefEquation -> Bool)
-> (DefEquation -> DefEquation -> Bool)
-> (DefEquation -> DefEquation -> DefEquation)
-> (DefEquation -> DefEquation -> DefEquation)
-> Ord DefEquation
DefEquation -> DefEquation -> Bool
DefEquation -> DefEquation -> Ordering
DefEquation -> DefEquation -> DefEquation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DefEquation -> DefEquation -> DefEquation
$cmin :: DefEquation -> DefEquation -> DefEquation
max :: DefEquation -> DefEquation -> DefEquation
$cmax :: DefEquation -> DefEquation -> DefEquation
>= :: DefEquation -> DefEquation -> Bool
$c>= :: DefEquation -> DefEquation -> Bool
> :: DefEquation -> DefEquation -> Bool
$c> :: DefEquation -> DefEquation -> Bool
<= :: DefEquation -> DefEquation -> Bool
$c<= :: DefEquation -> DefEquation -> Bool
< :: DefEquation -> DefEquation -> Bool
$c< :: DefEquation -> DefEquation -> Bool
compare :: DefEquation -> DefEquation -> Ordering
$ccompare :: DefEquation -> DefEquation -> Ordering
$cp1Ord :: Eq DefEquation
Ord, Int -> DefEquation -> ShowS
[DefEquation] -> ShowS
DefEquation -> String
(Int -> DefEquation -> ShowS)
-> (DefEquation -> String)
-> ([DefEquation] -> ShowS)
-> Show DefEquation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DefEquation] -> ShowS
$cshowList :: [DefEquation] -> ShowS
show :: DefEquation -> String
$cshow :: DefEquation -> String
showsPrec :: Int -> DefEquation -> ShowS
$cshowsPrec :: Int -> DefEquation -> ShowS
Show, Typeable, Typeable DefEquation
Constr
DataType
Typeable DefEquation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DefEquation -> c DefEquation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DefEquation)
-> (DefEquation -> Constr)
-> (DefEquation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DefEquation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DefEquation))
-> ((forall b. Data b => b -> b) -> DefEquation -> DefEquation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r)
-> (forall u. (forall d. Data d => d -> u) -> DefEquation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DefEquation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation)
-> Data DefEquation
DefEquation -> Constr
DefEquation -> DataType
(forall b. Data b => b -> b) -> DefEquation -> DefEquation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DefEquation -> c DefEquation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DefEquation
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DefEquation -> u
forall u. (forall d. Data d => d -> u) -> DefEquation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DefEquation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DefEquation -> c DefEquation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DefEquation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DefEquation)
$cDefEquation :: Constr
$tDefEquation :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
gmapMp :: (forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
gmapM :: (forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DefEquation -> m DefEquation
gmapQi :: Int -> (forall d. Data d => d -> u) -> DefEquation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DefEquation -> u
gmapQ :: (forall d. Data d => d -> u) -> DefEquation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DefEquation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DefEquation -> r
gmapT :: (forall b. Data b => b -> b) -> DefEquation -> DefEquation
$cgmapT :: (forall b. Data b => b -> b) -> DefEquation -> DefEquation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DefEquation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DefEquation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DefEquation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DefEquation)
dataTypeOf :: DefEquation -> DataType
$cdataTypeOf :: DefEquation -> DataType
toConstr :: DefEquation -> Constr
$ctoConstr :: DefEquation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DefEquation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DefEquation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DefEquation -> c DefEquation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DefEquation -> c DefEquation
$cp1Data :: Typeable DefEquation
Data)
data FixrecEquation = FixrecEquation {
FixrecEquation -> Bool
fixrecEquationUnchecked :: Bool,
FixrecEquation -> [Term]
fixrecEquationPremises :: [Term],
FixrecEquation -> [Term]
fixrecEquationPatterns :: [Term],
FixrecEquation -> Term
fixrecEquationTerm :: Term } deriving (FixrecEquation -> FixrecEquation -> Bool
(FixrecEquation -> FixrecEquation -> Bool)
-> (FixrecEquation -> FixrecEquation -> Bool) -> Eq FixrecEquation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FixrecEquation -> FixrecEquation -> Bool
$c/= :: FixrecEquation -> FixrecEquation -> Bool
== :: FixrecEquation -> FixrecEquation -> Bool
$c== :: FixrecEquation -> FixrecEquation -> Bool
Eq, Eq FixrecEquation
Eq FixrecEquation =>
(FixrecEquation -> FixrecEquation -> Ordering)
-> (FixrecEquation -> FixrecEquation -> Bool)
-> (FixrecEquation -> FixrecEquation -> Bool)
-> (FixrecEquation -> FixrecEquation -> Bool)
-> (FixrecEquation -> FixrecEquation -> Bool)
-> (FixrecEquation -> FixrecEquation -> FixrecEquation)
-> (FixrecEquation -> FixrecEquation -> FixrecEquation)
-> Ord FixrecEquation
FixrecEquation -> FixrecEquation -> Bool
FixrecEquation -> FixrecEquation -> Ordering
FixrecEquation -> FixrecEquation -> FixrecEquation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FixrecEquation -> FixrecEquation -> FixrecEquation
$cmin :: FixrecEquation -> FixrecEquation -> FixrecEquation
max :: FixrecEquation -> FixrecEquation -> FixrecEquation
$cmax :: FixrecEquation -> FixrecEquation -> FixrecEquation
>= :: FixrecEquation -> FixrecEquation -> Bool
$c>= :: FixrecEquation -> FixrecEquation -> Bool
> :: FixrecEquation -> FixrecEquation -> Bool
$c> :: FixrecEquation -> FixrecEquation -> Bool
<= :: FixrecEquation -> FixrecEquation -> Bool
$c<= :: FixrecEquation -> FixrecEquation -> Bool
< :: FixrecEquation -> FixrecEquation -> Bool
$c< :: FixrecEquation -> FixrecEquation -> Bool
compare :: FixrecEquation -> FixrecEquation -> Ordering
$ccompare :: FixrecEquation -> FixrecEquation -> Ordering
$cp1Ord :: Eq FixrecEquation
Ord, Int -> FixrecEquation -> ShowS
[FixrecEquation] -> ShowS
FixrecEquation -> String
(Int -> FixrecEquation -> ShowS)
-> (FixrecEquation -> String)
-> ([FixrecEquation] -> ShowS)
-> Show FixrecEquation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FixrecEquation] -> ShowS
$cshowList :: [FixrecEquation] -> ShowS
show :: FixrecEquation -> String
$cshow :: FixrecEquation -> String
showsPrec :: Int -> FixrecEquation -> ShowS
$cshowsPrec :: Int -> FixrecEquation -> ShowS
Show, Typeable, Typeable FixrecEquation
Constr
DataType
Typeable FixrecEquation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixrecEquation -> c FixrecEquation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixrecEquation)
-> (FixrecEquation -> Constr)
-> (FixrecEquation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FixrecEquation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixrecEquation))
-> ((forall b. Data b => b -> b)
-> FixrecEquation -> FixrecEquation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r)
-> (forall u.
(forall d. Data d => d -> u) -> FixrecEquation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FixrecEquation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation)
-> Data FixrecEquation
FixrecEquation -> Constr
FixrecEquation -> DataType
(forall b. Data b => b -> b) -> FixrecEquation -> FixrecEquation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixrecEquation -> c FixrecEquation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixrecEquation
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FixrecEquation -> u
forall u. (forall d. Data d => d -> u) -> FixrecEquation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixrecEquation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixrecEquation -> c FixrecEquation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FixrecEquation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixrecEquation)
$cFixrecEquation :: Constr
$tFixrecEquation :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
gmapMp :: (forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
gmapM :: (forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FixrecEquation -> m FixrecEquation
gmapQi :: Int -> (forall d. Data d => d -> u) -> FixrecEquation -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FixrecEquation -> u
gmapQ :: (forall d. Data d => d -> u) -> FixrecEquation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FixrecEquation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixrecEquation -> r
gmapT :: (forall b. Data b => b -> b) -> FixrecEquation -> FixrecEquation
$cgmapT :: (forall b. Data b => b -> b) -> FixrecEquation -> FixrecEquation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixrecEquation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixrecEquation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FixrecEquation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FixrecEquation)
dataTypeOf :: FixrecEquation -> DataType
$cdataTypeOf :: FixrecEquation -> DataType
toConstr :: FixrecEquation -> Constr
$ctoConstr :: FixrecEquation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixrecEquation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixrecEquation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixrecEquation -> c FixrecEquation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixrecEquation -> c FixrecEquation
$cp1Data :: Typeable FixrecEquation
Data)
data Ctxt = Ctxt {
Ctxt -> [(String, Maybe Mixfix, Typ)]
fixes :: [(String, Maybe Mixfix, Typ)],
Ctxt -> [(String, Term)]
assumes :: [(String, Term)] } deriving (Ctxt -> Ctxt -> Bool
(Ctxt -> Ctxt -> Bool) -> (Ctxt -> Ctxt -> Bool) -> Eq Ctxt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ctxt -> Ctxt -> Bool
$c/= :: Ctxt -> Ctxt -> Bool
== :: Ctxt -> Ctxt -> Bool
$c== :: Ctxt -> Ctxt -> Bool
Eq, Eq Ctxt
Eq Ctxt =>
(Ctxt -> Ctxt -> Ordering)
-> (Ctxt -> Ctxt -> Bool)
-> (Ctxt -> Ctxt -> Bool)
-> (Ctxt -> Ctxt -> Bool)
-> (Ctxt -> Ctxt -> Bool)
-> (Ctxt -> Ctxt -> Ctxt)
-> (Ctxt -> Ctxt -> Ctxt)
-> Ord Ctxt
Ctxt -> Ctxt -> Bool
Ctxt -> Ctxt -> Ordering
Ctxt -> Ctxt -> Ctxt
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Ctxt -> Ctxt -> Ctxt
$cmin :: Ctxt -> Ctxt -> Ctxt
max :: Ctxt -> Ctxt -> Ctxt
$cmax :: Ctxt -> Ctxt -> Ctxt
>= :: Ctxt -> Ctxt -> Bool
$c>= :: Ctxt -> Ctxt -> Bool
> :: Ctxt -> Ctxt -> Bool
$c> :: Ctxt -> Ctxt -> Bool
<= :: Ctxt -> Ctxt -> Bool
$c<= :: Ctxt -> Ctxt -> Bool
< :: Ctxt -> Ctxt -> Bool
$c< :: Ctxt -> Ctxt -> Bool
compare :: Ctxt -> Ctxt -> Ordering
$ccompare :: Ctxt -> Ctxt -> Ordering
$cp1Ord :: Eq Ctxt
Ord, Int -> Ctxt -> ShowS
[Ctxt] -> ShowS
Ctxt -> String
(Int -> Ctxt -> ShowS)
-> (Ctxt -> String) -> ([Ctxt] -> ShowS) -> Show Ctxt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ctxt] -> ShowS
$cshowList :: [Ctxt] -> ShowS
show :: Ctxt -> String
$cshow :: Ctxt -> String
showsPrec :: Int -> Ctxt -> ShowS
$cshowsPrec :: Int -> Ctxt -> ShowS
Show, Typeable, Typeable Ctxt
Constr
DataType
Typeable Ctxt =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ctxt -> c Ctxt)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ctxt)
-> (Ctxt -> Constr)
-> (Ctxt -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ctxt))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ctxt))
-> ((forall b. Data b => b -> b) -> Ctxt -> Ctxt)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r)
-> (forall u. (forall d. Data d => d -> u) -> Ctxt -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Ctxt -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt)
-> Data Ctxt
Ctxt -> Constr
Ctxt -> DataType
(forall b. Data b => b -> b) -> Ctxt -> Ctxt
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ctxt -> c Ctxt
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ctxt
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Ctxt -> u
forall u. (forall d. Data d => d -> u) -> Ctxt -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ctxt
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ctxt -> c Ctxt
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ctxt)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ctxt)
$cCtxt :: Constr
$tCtxt :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
gmapMp :: (forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
gmapM :: (forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ctxt -> m Ctxt
gmapQi :: Int -> (forall d. Data d => d -> u) -> Ctxt -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Ctxt -> u
gmapQ :: (forall d. Data d => d -> u) -> Ctxt -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Ctxt -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ctxt -> r
gmapT :: (forall b. Data b => b -> b) -> Ctxt -> Ctxt
$cgmapT :: (forall b. Data b => b -> b) -> Ctxt -> Ctxt
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ctxt)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ctxt)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Ctxt)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ctxt)
dataTypeOf :: Ctxt -> DataType
$cdataTypeOf :: Ctxt -> DataType
toConstr :: Ctxt -> Constr
$ctoConstr :: Ctxt -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ctxt
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ctxt
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ctxt -> c Ctxt
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ctxt -> c Ctxt
$cp1Data :: Typeable Ctxt
Data)
data Mixfix = Mixfix {
Mixfix -> Int
mixfixNargs :: Int,
Mixfix -> Int
mixfixPrio :: Int,
Mixfix -> String
mixfixPretty :: String,
Mixfix -> [MixfixTemplate]
mixfixTemplate :: [MixfixTemplate] }
deriving (Mixfix -> Mixfix -> Bool
(Mixfix -> Mixfix -> Bool)
-> (Mixfix -> Mixfix -> Bool) -> Eq Mixfix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mixfix -> Mixfix -> Bool
$c/= :: Mixfix -> Mixfix -> Bool
== :: Mixfix -> Mixfix -> Bool
$c== :: Mixfix -> Mixfix -> Bool
Eq, Eq Mixfix
Eq Mixfix =>
(Mixfix -> Mixfix -> Ordering)
-> (Mixfix -> Mixfix -> Bool)
-> (Mixfix -> Mixfix -> Bool)
-> (Mixfix -> Mixfix -> Bool)
-> (Mixfix -> Mixfix -> Bool)
-> (Mixfix -> Mixfix -> Mixfix)
-> (Mixfix -> Mixfix -> Mixfix)
-> Ord Mixfix
Mixfix -> Mixfix -> Bool
Mixfix -> Mixfix -> Ordering
Mixfix -> Mixfix -> Mixfix
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Mixfix -> Mixfix -> Mixfix
$cmin :: Mixfix -> Mixfix -> Mixfix
max :: Mixfix -> Mixfix -> Mixfix
$cmax :: Mixfix -> Mixfix -> Mixfix
>= :: Mixfix -> Mixfix -> Bool
$c>= :: Mixfix -> Mixfix -> Bool
> :: Mixfix -> Mixfix -> Bool
$c> :: Mixfix -> Mixfix -> Bool
<= :: Mixfix -> Mixfix -> Bool
$c<= :: Mixfix -> Mixfix -> Bool
< :: Mixfix -> Mixfix -> Bool
$c< :: Mixfix -> Mixfix -> Bool
compare :: Mixfix -> Mixfix -> Ordering
$ccompare :: Mixfix -> Mixfix -> Ordering
$cp1Ord :: Eq Mixfix
Ord, Int -> Mixfix -> ShowS
[Mixfix] -> ShowS
Mixfix -> String
(Int -> Mixfix -> ShowS)
-> (Mixfix -> String) -> ([Mixfix] -> ShowS) -> Show Mixfix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mixfix] -> ShowS
$cshowList :: [Mixfix] -> ShowS
show :: Mixfix -> String
$cshow :: Mixfix -> String
showsPrec :: Int -> Mixfix -> ShowS
$cshowsPrec :: Int -> Mixfix -> ShowS
Show, Typeable, Typeable Mixfix
Constr
DataType
Typeable Mixfix =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mixfix -> c Mixfix)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mixfix)
-> (Mixfix -> Constr)
-> (Mixfix -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mixfix))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mixfix))
-> ((forall b. Data b => b -> b) -> Mixfix -> Mixfix)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Mixfix -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Mixfix -> r)
-> (forall u. (forall d. Data d => d -> u) -> Mixfix -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Mixfix -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix)
-> Data Mixfix
Mixfix -> Constr
Mixfix -> DataType
(forall b. Data b => b -> b) -> Mixfix -> Mixfix
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mixfix -> c Mixfix
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mixfix
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Mixfix -> u
forall u. (forall d. Data d => d -> u) -> Mixfix -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mixfix -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mixfix -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mixfix
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mixfix -> c Mixfix
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mixfix)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mixfix)
$cMixfix :: Constr
$tMixfix :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
gmapMp :: (forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
gmapM :: (forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Mixfix -> m Mixfix
gmapQi :: Int -> (forall d. Data d => d -> u) -> Mixfix -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Mixfix -> u
gmapQ :: (forall d. Data d => d -> u) -> Mixfix -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Mixfix -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mixfix -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mixfix -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mixfix -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mixfix -> r
gmapT :: (forall b. Data b => b -> b) -> Mixfix -> Mixfix
$cgmapT :: (forall b. Data b => b -> b) -> Mixfix -> Mixfix
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mixfix)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mixfix)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Mixfix)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mixfix)
dataTypeOf :: Mixfix -> DataType
$cdataTypeOf :: Mixfix -> DataType
toConstr :: Mixfix -> Constr
$ctoConstr :: Mixfix -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mixfix
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mixfix
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mixfix -> c Mixfix
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mixfix -> c Mixfix
$cp1Data :: Typeable Mixfix
Data)
data MixfixTemplate = Arg Int | Str String | Break Int |
Block Int [MixfixTemplate]
deriving (MixfixTemplate -> MixfixTemplate -> Bool
(MixfixTemplate -> MixfixTemplate -> Bool)
-> (MixfixTemplate -> MixfixTemplate -> Bool) -> Eq MixfixTemplate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MixfixTemplate -> MixfixTemplate -> Bool
$c/= :: MixfixTemplate -> MixfixTemplate -> Bool
== :: MixfixTemplate -> MixfixTemplate -> Bool
$c== :: MixfixTemplate -> MixfixTemplate -> Bool
Eq, Eq MixfixTemplate
Eq MixfixTemplate =>
(MixfixTemplate -> MixfixTemplate -> Ordering)
-> (MixfixTemplate -> MixfixTemplate -> Bool)
-> (MixfixTemplate -> MixfixTemplate -> Bool)
-> (MixfixTemplate -> MixfixTemplate -> Bool)
-> (MixfixTemplate -> MixfixTemplate -> Bool)
-> (MixfixTemplate -> MixfixTemplate -> MixfixTemplate)
-> (MixfixTemplate -> MixfixTemplate -> MixfixTemplate)
-> Ord MixfixTemplate
MixfixTemplate -> MixfixTemplate -> Bool
MixfixTemplate -> MixfixTemplate -> Ordering
MixfixTemplate -> MixfixTemplate -> MixfixTemplate
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MixfixTemplate -> MixfixTemplate -> MixfixTemplate
$cmin :: MixfixTemplate -> MixfixTemplate -> MixfixTemplate
max :: MixfixTemplate -> MixfixTemplate -> MixfixTemplate
$cmax :: MixfixTemplate -> MixfixTemplate -> MixfixTemplate
>= :: MixfixTemplate -> MixfixTemplate -> Bool
$c>= :: MixfixTemplate -> MixfixTemplate -> Bool
> :: MixfixTemplate -> MixfixTemplate -> Bool
$c> :: MixfixTemplate -> MixfixTemplate -> Bool
<= :: MixfixTemplate -> MixfixTemplate -> Bool
$c<= :: MixfixTemplate -> MixfixTemplate -> Bool
< :: MixfixTemplate -> MixfixTemplate -> Bool
$c< :: MixfixTemplate -> MixfixTemplate -> Bool
compare :: MixfixTemplate -> MixfixTemplate -> Ordering
$ccompare :: MixfixTemplate -> MixfixTemplate -> Ordering
$cp1Ord :: Eq MixfixTemplate
Ord, Int -> MixfixTemplate -> ShowS
[MixfixTemplate] -> ShowS
MixfixTemplate -> String
(Int -> MixfixTemplate -> ShowS)
-> (MixfixTemplate -> String)
-> ([MixfixTemplate] -> ShowS)
-> Show MixfixTemplate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MixfixTemplate] -> ShowS
$cshowList :: [MixfixTemplate] -> ShowS
show :: MixfixTemplate -> String
$cshow :: MixfixTemplate -> String
showsPrec :: Int -> MixfixTemplate -> ShowS
$cshowsPrec :: Int -> MixfixTemplate -> ShowS
Show, Typeable, Typeable MixfixTemplate
Constr
DataType
Typeable MixfixTemplate =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MixfixTemplate -> c MixfixTemplate)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MixfixTemplate)
-> (MixfixTemplate -> Constr)
-> (MixfixTemplate -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MixfixTemplate))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MixfixTemplate))
-> ((forall b. Data b => b -> b)
-> MixfixTemplate -> MixfixTemplate)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r)
-> (forall u.
(forall d. Data d => d -> u) -> MixfixTemplate -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MixfixTemplate -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate)
-> Data MixfixTemplate
MixfixTemplate -> Constr
MixfixTemplate -> DataType
(forall b. Data b => b -> b) -> MixfixTemplate -> MixfixTemplate
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MixfixTemplate -> c MixfixTemplate
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MixfixTemplate
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> MixfixTemplate -> u
forall u. (forall d. Data d => d -> u) -> MixfixTemplate -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MixfixTemplate
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MixfixTemplate -> c MixfixTemplate
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MixfixTemplate)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MixfixTemplate)
$cBlock :: Constr
$cBreak :: Constr
$cStr :: Constr
$cArg :: Constr
$tMixfixTemplate :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
gmapMp :: (forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
gmapM :: (forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MixfixTemplate -> m MixfixTemplate
gmapQi :: Int -> (forall d. Data d => d -> u) -> MixfixTemplate -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MixfixTemplate -> u
gmapQ :: (forall d. Data d => d -> u) -> MixfixTemplate -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MixfixTemplate -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MixfixTemplate -> r
gmapT :: (forall b. Data b => b -> b) -> MixfixTemplate -> MixfixTemplate
$cgmapT :: (forall b. Data b => b -> b) -> MixfixTemplate -> MixfixTemplate
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MixfixTemplate)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MixfixTemplate)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c MixfixTemplate)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MixfixTemplate)
dataTypeOf :: MixfixTemplate -> DataType
$cdataTypeOf :: MixfixTemplate -> DataType
toConstr :: MixfixTemplate -> Constr
$ctoConstr :: MixfixTemplate -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MixfixTemplate
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MixfixTemplate
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MixfixTemplate -> c MixfixTemplate
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MixfixTemplate -> c MixfixTemplate
$cp1Data :: Typeable MixfixTemplate
Data)
data Datatype = Datatype {
Datatype -> QName
datatypeName :: QName,
Datatype -> [Typ]
datatypeTVars :: [Typ],
Datatype -> Maybe Mixfix
datatypeMixfix :: Maybe Mixfix,
Datatype -> [DatatypeConstructor]
datatypeConstructors :: [DatatypeConstructor] }
deriving (Datatype -> Datatype -> Bool
(Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool) -> Eq Datatype
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Datatype -> Datatype -> Bool
$c/= :: Datatype -> Datatype -> Bool
== :: Datatype -> Datatype -> Bool
$c== :: Datatype -> Datatype -> Bool
Eq, Eq Datatype
Eq Datatype =>
(Datatype -> Datatype -> Ordering)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Datatype)
-> (Datatype -> Datatype -> Datatype)
-> Ord Datatype
Datatype -> Datatype -> Bool
Datatype -> Datatype -> Ordering
Datatype -> Datatype -> Datatype
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Datatype -> Datatype -> Datatype
$cmin :: Datatype -> Datatype -> Datatype
max :: Datatype -> Datatype -> Datatype
$cmax :: Datatype -> Datatype -> Datatype
>= :: Datatype -> Datatype -> Bool
$c>= :: Datatype -> Datatype -> Bool
> :: Datatype -> Datatype -> Bool
$c> :: Datatype -> Datatype -> Bool
<= :: Datatype -> Datatype -> Bool
$c<= :: Datatype -> Datatype -> Bool
< :: Datatype -> Datatype -> Bool
$c< :: Datatype -> Datatype -> Bool
compare :: Datatype -> Datatype -> Ordering
$ccompare :: Datatype -> Datatype -> Ordering
$cp1Ord :: Eq Datatype
Ord, Int -> Datatype -> ShowS
[Datatype] -> ShowS
Datatype -> String
(Int -> Datatype -> ShowS)
-> (Datatype -> String) -> ([Datatype] -> ShowS) -> Show Datatype
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Datatype] -> ShowS
$cshowList :: [Datatype] -> ShowS
show :: Datatype -> String
$cshow :: Datatype -> String
showsPrec :: Int -> Datatype -> ShowS
$cshowsPrec :: Int -> Datatype -> ShowS
Show, Typeable, Typeable Datatype
Constr
DataType
Typeable Datatype =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Datatype -> c Datatype)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Datatype)
-> (Datatype -> Constr)
-> (Datatype -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Datatype))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datatype))
-> ((forall b. Data b => b -> b) -> Datatype -> Datatype)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r)
-> (forall u. (forall d. Data d => d -> u) -> Datatype -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Datatype -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype)
-> Data Datatype
Datatype -> Constr
Datatype -> DataType
(forall b. Data b => b -> b) -> Datatype -> Datatype
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Datatype -> c Datatype
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Datatype
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Datatype -> u
forall u. (forall d. Data d => d -> u) -> Datatype -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Datatype
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Datatype -> c Datatype
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Datatype)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datatype)
$cDatatype :: Constr
$tDatatype :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Datatype -> m Datatype
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype
gmapMp :: (forall d. Data d => d -> m d) -> Datatype -> m Datatype
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype
gmapM :: (forall d. Data d => d -> m d) -> Datatype -> m Datatype
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Datatype -> m Datatype
gmapQi :: Int -> (forall d. Data d => d -> u) -> Datatype -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Datatype -> u
gmapQ :: (forall d. Data d => d -> u) -> Datatype -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Datatype -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Datatype -> r
gmapT :: (forall b. Data b => b -> b) -> Datatype -> Datatype
$cgmapT :: (forall b. Data b => b -> b) -> Datatype -> Datatype
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datatype)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datatype)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Datatype)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Datatype)
dataTypeOf :: Datatype -> DataType
$cdataTypeOf :: Datatype -> DataType
toConstr :: Datatype -> Constr
$ctoConstr :: Datatype -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Datatype
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Datatype
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Datatype -> c Datatype
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Datatype -> c Datatype
$cp1Data :: Typeable Datatype
Data)
data DatatypeConstructor = DatatypeConstructor {
DatatypeConstructor -> QName
constructorName :: QName,
DatatypeConstructor -> Typ
constructorType :: Typ,
DatatypeConstructor -> Maybe Mixfix
constructorMixfix :: Maybe Mixfix,
DatatypeConstructor -> [Typ]
constructorArgs :: [Typ] } |
DatatypeNoConstructor {
constructorArgs :: [Typ] }
deriving (DatatypeConstructor -> DatatypeConstructor -> Bool
(DatatypeConstructor -> DatatypeConstructor -> Bool)
-> (DatatypeConstructor -> DatatypeConstructor -> Bool)
-> Eq DatatypeConstructor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatatypeConstructor -> DatatypeConstructor -> Bool
$c/= :: DatatypeConstructor -> DatatypeConstructor -> Bool
== :: DatatypeConstructor -> DatatypeConstructor -> Bool
$c== :: DatatypeConstructor -> DatatypeConstructor -> Bool
Eq, Eq DatatypeConstructor
Eq DatatypeConstructor =>
(DatatypeConstructor -> DatatypeConstructor -> Ordering)
-> (DatatypeConstructor -> DatatypeConstructor -> Bool)
-> (DatatypeConstructor -> DatatypeConstructor -> Bool)
-> (DatatypeConstructor -> DatatypeConstructor -> Bool)
-> (DatatypeConstructor -> DatatypeConstructor -> Bool)
-> (DatatypeConstructor
-> DatatypeConstructor -> DatatypeConstructor)
-> (DatatypeConstructor
-> DatatypeConstructor -> DatatypeConstructor)
-> Ord DatatypeConstructor
DatatypeConstructor -> DatatypeConstructor -> Bool
DatatypeConstructor -> DatatypeConstructor -> Ordering
DatatypeConstructor -> DatatypeConstructor -> DatatypeConstructor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DatatypeConstructor -> DatatypeConstructor -> DatatypeConstructor
$cmin :: DatatypeConstructor -> DatatypeConstructor -> DatatypeConstructor
max :: DatatypeConstructor -> DatatypeConstructor -> DatatypeConstructor
$cmax :: DatatypeConstructor -> DatatypeConstructor -> DatatypeConstructor
>= :: DatatypeConstructor -> DatatypeConstructor -> Bool
$c>= :: DatatypeConstructor -> DatatypeConstructor -> Bool
> :: DatatypeConstructor -> DatatypeConstructor -> Bool
$c> :: DatatypeConstructor -> DatatypeConstructor -> Bool
<= :: DatatypeConstructor -> DatatypeConstructor -> Bool
$c<= :: DatatypeConstructor -> DatatypeConstructor -> Bool
< :: DatatypeConstructor -> DatatypeConstructor -> Bool
$c< :: DatatypeConstructor -> DatatypeConstructor -> Bool
compare :: DatatypeConstructor -> DatatypeConstructor -> Ordering
$ccompare :: DatatypeConstructor -> DatatypeConstructor -> Ordering
$cp1Ord :: Eq DatatypeConstructor
Ord, Int -> DatatypeConstructor -> ShowS
[DatatypeConstructor] -> ShowS
DatatypeConstructor -> String
(Int -> DatatypeConstructor -> ShowS)
-> (DatatypeConstructor -> String)
-> ([DatatypeConstructor] -> ShowS)
-> Show DatatypeConstructor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatatypeConstructor] -> ShowS
$cshowList :: [DatatypeConstructor] -> ShowS
show :: DatatypeConstructor -> String
$cshow :: DatatypeConstructor -> String
showsPrec :: Int -> DatatypeConstructor -> ShowS
$cshowsPrec :: Int -> DatatypeConstructor -> ShowS
Show, Typeable, Typeable DatatypeConstructor
Constr
DataType
Typeable DatatypeConstructor =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DatatypeConstructor
-> c DatatypeConstructor)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DatatypeConstructor)
-> (DatatypeConstructor -> Constr)
-> (DatatypeConstructor -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DatatypeConstructor))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DatatypeConstructor))
-> ((forall b. Data b => b -> b)
-> DatatypeConstructor -> DatatypeConstructor)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r)
-> (forall u.
(forall d. Data d => d -> u) -> DatatypeConstructor -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DatatypeConstructor -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor)
-> Data DatatypeConstructor
DatatypeConstructor -> Constr
DatatypeConstructor -> DataType
(forall b. Data b => b -> b)
-> DatatypeConstructor -> DatatypeConstructor
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DatatypeConstructor
-> c DatatypeConstructor
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DatatypeConstructor
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> DatatypeConstructor -> u
forall u.
(forall d. Data d => d -> u) -> DatatypeConstructor -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DatatypeConstructor
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DatatypeConstructor
-> c DatatypeConstructor
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DatatypeConstructor)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DatatypeConstructor)
$cDatatypeNoConstructor :: Constr
$cDatatypeConstructor :: Constr
$tDatatypeConstructor :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
gmapMp :: (forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
gmapM :: (forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DatatypeConstructor -> m DatatypeConstructor
gmapQi :: Int -> (forall d. Data d => d -> u) -> DatatypeConstructor -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> DatatypeConstructor -> u
gmapQ :: (forall d. Data d => d -> u) -> DatatypeConstructor -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> DatatypeConstructor -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DatatypeConstructor -> r
gmapT :: (forall b. Data b => b -> b)
-> DatatypeConstructor -> DatatypeConstructor
$cgmapT :: (forall b. Data b => b -> b)
-> DatatypeConstructor -> DatatypeConstructor
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DatatypeConstructor)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DatatypeConstructor)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DatatypeConstructor)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DatatypeConstructor)
dataTypeOf :: DatatypeConstructor -> DataType
$cdataTypeOf :: DatatypeConstructor -> DataType
toConstr :: DatatypeConstructor -> Constr
$ctoConstr :: DatatypeConstructor -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DatatypeConstructor
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DatatypeConstructor
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DatatypeConstructor
-> c DatatypeConstructor
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DatatypeConstructor
-> c DatatypeConstructor
$cp1Data :: Typeable DatatypeConstructor
Data)
data Domain = Domain {
Domain -> QName
domainName :: QName,
Domain -> [Typ]
domainTVars :: [Typ],
Domain -> Maybe Mixfix
domainMixfix :: Maybe Mixfix,
Domain -> [DomainConstructor]
domainConstructors :: [DomainConstructor] }
deriving (Domain -> Domain -> Bool
(Domain -> Domain -> Bool)
-> (Domain -> Domain -> Bool) -> Eq Domain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Domain -> Domain -> Bool
$c/= :: Domain -> Domain -> Bool
== :: Domain -> Domain -> Bool
$c== :: Domain -> Domain -> Bool
Eq, Eq Domain
Eq Domain =>
(Domain -> Domain -> Ordering)
-> (Domain -> Domain -> Bool)
-> (Domain -> Domain -> Bool)
-> (Domain -> Domain -> Bool)
-> (Domain -> Domain -> Bool)
-> (Domain -> Domain -> Domain)
-> (Domain -> Domain -> Domain)
-> Ord Domain
Domain -> Domain -> Bool
Domain -> Domain -> Ordering
Domain -> Domain -> Domain
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Domain -> Domain -> Domain
$cmin :: Domain -> Domain -> Domain
max :: Domain -> Domain -> Domain
$cmax :: Domain -> Domain -> Domain
>= :: Domain -> Domain -> Bool
$c>= :: Domain -> Domain -> Bool
> :: Domain -> Domain -> Bool
$c> :: Domain -> Domain -> Bool
<= :: Domain -> Domain -> Bool
$c<= :: Domain -> Domain -> Bool
< :: Domain -> Domain -> Bool
$c< :: Domain -> Domain -> Bool
compare :: Domain -> Domain -> Ordering
$ccompare :: Domain -> Domain -> Ordering
$cp1Ord :: Eq Domain
Ord, Int -> Domain -> ShowS
[Domain] -> ShowS
Domain -> String
(Int -> Domain -> ShowS)
-> (Domain -> String) -> ([Domain] -> ShowS) -> Show Domain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Domain] -> ShowS
$cshowList :: [Domain] -> ShowS
show :: Domain -> String
$cshow :: Domain -> String
showsPrec :: Int -> Domain -> ShowS
$cshowsPrec :: Int -> Domain -> ShowS
Show, Typeable, Typeable Domain
Constr
DataType
Typeable Domain =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Domain -> c Domain)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Domain)
-> (Domain -> Constr)
-> (Domain -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Domain))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Domain))
-> ((forall b. Data b => b -> b) -> Domain -> Domain)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Domain -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Domain -> r)
-> (forall u. (forall d. Data d => d -> u) -> Domain -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Domain -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain)
-> Data Domain
Domain -> Constr
Domain -> DataType
(forall b. Data b => b -> b) -> Domain -> Domain
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Domain -> c Domain
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Domain
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Domain -> u
forall u. (forall d. Data d => d -> u) -> Domain -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Domain -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Domain -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Domain
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Domain -> c Domain
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Domain)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Domain)
$cDomain :: Constr
$tDomain :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Domain -> m Domain
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain
gmapMp :: (forall d. Data d => d -> m d) -> Domain -> m Domain
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain
gmapM :: (forall d. Data d => d -> m d) -> Domain -> m Domain
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Domain -> m Domain
gmapQi :: Int -> (forall d. Data d => d -> u) -> Domain -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Domain -> u
gmapQ :: (forall d. Data d => d -> u) -> Domain -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Domain -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Domain -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Domain -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Domain -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Domain -> r
gmapT :: (forall b. Data b => b -> b) -> Domain -> Domain
$cgmapT :: (forall b. Data b => b -> b) -> Domain -> Domain
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Domain)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Domain)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Domain)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Domain)
dataTypeOf :: Domain -> DataType
$cdataTypeOf :: Domain -> DataType
toConstr :: Domain -> Constr
$ctoConstr :: Domain -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Domain
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Domain
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Domain -> c Domain
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Domain -> c Domain
$cp1Data :: Typeable Domain
Data)
data DomainConstructor = DomainConstructor {
DomainConstructor -> QName
domainConstructorName :: QName,
DomainConstructor -> Typ
domainConstructorType :: Typ,
DomainConstructor -> [DomainConstructorArg]
domainConstructorArgs :: [DomainConstructorArg] }
deriving (DomainConstructor -> DomainConstructor -> Bool
(DomainConstructor -> DomainConstructor -> Bool)
-> (DomainConstructor -> DomainConstructor -> Bool)
-> Eq DomainConstructor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DomainConstructor -> DomainConstructor -> Bool
$c/= :: DomainConstructor -> DomainConstructor -> Bool
== :: DomainConstructor -> DomainConstructor -> Bool
$c== :: DomainConstructor -> DomainConstructor -> Bool
Eq, Eq DomainConstructor
Eq DomainConstructor =>
(DomainConstructor -> DomainConstructor -> Ordering)
-> (DomainConstructor -> DomainConstructor -> Bool)
-> (DomainConstructor -> DomainConstructor -> Bool)
-> (DomainConstructor -> DomainConstructor -> Bool)
-> (DomainConstructor -> DomainConstructor -> Bool)
-> (DomainConstructor -> DomainConstructor -> DomainConstructor)
-> (DomainConstructor -> DomainConstructor -> DomainConstructor)
-> Ord DomainConstructor
DomainConstructor -> DomainConstructor -> Bool
DomainConstructor -> DomainConstructor -> Ordering
DomainConstructor -> DomainConstructor -> DomainConstructor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DomainConstructor -> DomainConstructor -> DomainConstructor
$cmin :: DomainConstructor -> DomainConstructor -> DomainConstructor
max :: DomainConstructor -> DomainConstructor -> DomainConstructor
$cmax :: DomainConstructor -> DomainConstructor -> DomainConstructor
>= :: DomainConstructor -> DomainConstructor -> Bool
$c>= :: DomainConstructor -> DomainConstructor -> Bool
> :: DomainConstructor -> DomainConstructor -> Bool
$c> :: DomainConstructor -> DomainConstructor -> Bool
<= :: DomainConstructor -> DomainConstructor -> Bool
$c<= :: DomainConstructor -> DomainConstructor -> Bool
< :: DomainConstructor -> DomainConstructor -> Bool
$c< :: DomainConstructor -> DomainConstructor -> Bool
compare :: DomainConstructor -> DomainConstructor -> Ordering
$ccompare :: DomainConstructor -> DomainConstructor -> Ordering
$cp1Ord :: Eq DomainConstructor
Ord, Int -> DomainConstructor -> ShowS
[DomainConstructor] -> ShowS
DomainConstructor -> String
(Int -> DomainConstructor -> ShowS)
-> (DomainConstructor -> String)
-> ([DomainConstructor] -> ShowS)
-> Show DomainConstructor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DomainConstructor] -> ShowS
$cshowList :: [DomainConstructor] -> ShowS
show :: DomainConstructor -> String
$cshow :: DomainConstructor -> String
showsPrec :: Int -> DomainConstructor -> ShowS
$cshowsPrec :: Int -> DomainConstructor -> ShowS
Show, Typeable, Typeable DomainConstructor
Constr
DataType
Typeable DomainConstructor =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DomainConstructor
-> c DomainConstructor)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructor)
-> (DomainConstructor -> Constr)
-> (DomainConstructor -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DomainConstructor))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructor))
-> ((forall b. Data b => b -> b)
-> DomainConstructor -> DomainConstructor)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r)
-> (forall u.
(forall d. Data d => d -> u) -> DomainConstructor -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DomainConstructor -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor)
-> Data DomainConstructor
DomainConstructor -> Constr
DomainConstructor -> DataType
(forall b. Data b => b -> b)
-> DomainConstructor -> DomainConstructor
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DomainConstructor -> c DomainConstructor
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructor
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> DomainConstructor -> u
forall u. (forall d. Data d => d -> u) -> DomainConstructor -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructor
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DomainConstructor -> c DomainConstructor
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DomainConstructor)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructor)
$cDomainConstructor :: Constr
$tDomainConstructor :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
gmapMp :: (forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
gmapM :: (forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DomainConstructor -> m DomainConstructor
gmapQi :: Int -> (forall d. Data d => d -> u) -> DomainConstructor -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> DomainConstructor -> u
gmapQ :: (forall d. Data d => d -> u) -> DomainConstructor -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DomainConstructor -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructor -> r
gmapT :: (forall b. Data b => b -> b)
-> DomainConstructor -> DomainConstructor
$cgmapT :: (forall b. Data b => b -> b)
-> DomainConstructor -> DomainConstructor
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructor)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructor)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DomainConstructor)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DomainConstructor)
dataTypeOf :: DomainConstructor -> DataType
$cdataTypeOf :: DomainConstructor -> DataType
toConstr :: DomainConstructor -> Constr
$ctoConstr :: DomainConstructor -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructor
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructor
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DomainConstructor -> c DomainConstructor
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DomainConstructor -> c DomainConstructor
$cp1Data :: Typeable DomainConstructor
Data)
data DomainConstructorArg = DomainConstructorArg {
DomainConstructorArg -> Maybe QName
domainConstructorArgSel :: Maybe QName,
DomainConstructorArg -> Typ
domainConstructorArgType :: Typ,
DomainConstructorArg -> Bool
domainConstructorArgLazy :: Bool }
deriving (DomainConstructorArg -> DomainConstructorArg -> Bool
(DomainConstructorArg -> DomainConstructorArg -> Bool)
-> (DomainConstructorArg -> DomainConstructorArg -> Bool)
-> Eq DomainConstructorArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DomainConstructorArg -> DomainConstructorArg -> Bool
$c/= :: DomainConstructorArg -> DomainConstructorArg -> Bool
== :: DomainConstructorArg -> DomainConstructorArg -> Bool
$c== :: DomainConstructorArg -> DomainConstructorArg -> Bool
Eq, Eq DomainConstructorArg
Eq DomainConstructorArg =>
(DomainConstructorArg -> DomainConstructorArg -> Ordering)
-> (DomainConstructorArg -> DomainConstructorArg -> Bool)
-> (DomainConstructorArg -> DomainConstructorArg -> Bool)
-> (DomainConstructorArg -> DomainConstructorArg -> Bool)
-> (DomainConstructorArg -> DomainConstructorArg -> Bool)
-> (DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg)
-> (DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg)
-> Ord DomainConstructorArg
DomainConstructorArg -> DomainConstructorArg -> Bool
DomainConstructorArg -> DomainConstructorArg -> Ordering
DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg
$cmin :: DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg
max :: DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg
$cmax :: DomainConstructorArg
-> DomainConstructorArg -> DomainConstructorArg
>= :: DomainConstructorArg -> DomainConstructorArg -> Bool
$c>= :: DomainConstructorArg -> DomainConstructorArg -> Bool
> :: DomainConstructorArg -> DomainConstructorArg -> Bool
$c> :: DomainConstructorArg -> DomainConstructorArg -> Bool
<= :: DomainConstructorArg -> DomainConstructorArg -> Bool
$c<= :: DomainConstructorArg -> DomainConstructorArg -> Bool
< :: DomainConstructorArg -> DomainConstructorArg -> Bool
$c< :: DomainConstructorArg -> DomainConstructorArg -> Bool
compare :: DomainConstructorArg -> DomainConstructorArg -> Ordering
$ccompare :: DomainConstructorArg -> DomainConstructorArg -> Ordering
$cp1Ord :: Eq DomainConstructorArg
Ord, Int -> DomainConstructorArg -> ShowS
[DomainConstructorArg] -> ShowS
DomainConstructorArg -> String
(Int -> DomainConstructorArg -> ShowS)
-> (DomainConstructorArg -> String)
-> ([DomainConstructorArg] -> ShowS)
-> Show DomainConstructorArg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DomainConstructorArg] -> ShowS
$cshowList :: [DomainConstructorArg] -> ShowS
show :: DomainConstructorArg -> String
$cshow :: DomainConstructorArg -> String
showsPrec :: Int -> DomainConstructorArg -> ShowS
$cshowsPrec :: Int -> DomainConstructorArg -> ShowS
Show, Typeable, Typeable DomainConstructorArg
Constr
DataType
Typeable DomainConstructorArg =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DomainConstructorArg
-> c DomainConstructorArg)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructorArg)
-> (DomainConstructorArg -> Constr)
-> (DomainConstructorArg -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DomainConstructorArg))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructorArg))
-> ((forall b. Data b => b -> b)
-> DomainConstructorArg -> DomainConstructorArg)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r)
-> (forall u.
(forall d. Data d => d -> u) -> DomainConstructorArg -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DomainConstructorArg -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg)
-> Data DomainConstructorArg
DomainConstructorArg -> Constr
DomainConstructorArg -> DataType
(forall b. Data b => b -> b)
-> DomainConstructorArg -> DomainConstructorArg
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DomainConstructorArg
-> c DomainConstructorArg
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructorArg
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> DomainConstructorArg -> u
forall u.
(forall d. Data d => d -> u) -> DomainConstructorArg -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructorArg
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DomainConstructorArg
-> c DomainConstructorArg
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DomainConstructorArg)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructorArg)
$cDomainConstructorArg :: Constr
$tDomainConstructorArg :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
gmapMp :: (forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
gmapM :: (forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DomainConstructorArg -> m DomainConstructorArg
gmapQi :: Int -> (forall d. Data d => d -> u) -> DomainConstructorArg -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> DomainConstructorArg -> u
gmapQ :: (forall d. Data d => d -> u) -> DomainConstructorArg -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> DomainConstructorArg -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DomainConstructorArg -> r
gmapT :: (forall b. Data b => b -> b)
-> DomainConstructorArg -> DomainConstructorArg
$cgmapT :: (forall b. Data b => b -> b)
-> DomainConstructorArg -> DomainConstructorArg
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructorArg)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c DomainConstructorArg)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DomainConstructorArg)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DomainConstructorArg)
dataTypeOf :: DomainConstructorArg -> DataType
$cdataTypeOf :: DomainConstructorArg -> DataType
toConstr :: DomainConstructorArg -> Constr
$ctoConstr :: DomainConstructorArg -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructorArg
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DomainConstructorArg
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DomainConstructorArg
-> c DomainConstructorArg
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DomainConstructorArg
-> c DomainConstructorArg
$cp1Data :: Typeable DomainConstructorArg
Data)
data Axiom = Axiom {
Axiom -> QName
axiomName :: QName,
Axiom -> String
axiomArgs :: String,
Axiom -> Term
axiomTerm :: Term } deriving (Axiom -> Axiom -> Bool
(Axiom -> Axiom -> Bool) -> (Axiom -> Axiom -> Bool) -> Eq Axiom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Axiom -> Axiom -> Bool
$c/= :: Axiom -> Axiom -> Bool
== :: Axiom -> Axiom -> Bool
$c== :: Axiom -> Axiom -> Bool
Eq, Eq Axiom
Eq Axiom =>
(Axiom -> Axiom -> Ordering)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Axiom)
-> (Axiom -> Axiom -> Axiom)
-> Ord Axiom
Axiom -> Axiom -> Bool
Axiom -> Axiom -> Ordering
Axiom -> Axiom -> Axiom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Axiom -> Axiom -> Axiom
$cmin :: Axiom -> Axiom -> Axiom
max :: Axiom -> Axiom -> Axiom
$cmax :: Axiom -> Axiom -> Axiom
>= :: Axiom -> Axiom -> Bool
$c>= :: Axiom -> Axiom -> Bool
> :: Axiom -> Axiom -> Bool
$c> :: Axiom -> Axiom -> Bool
<= :: Axiom -> Axiom -> Bool
$c<= :: Axiom -> Axiom -> Bool
< :: Axiom -> Axiom -> Bool
$c< :: Axiom -> Axiom -> Bool
compare :: Axiom -> Axiom -> Ordering
$ccompare :: Axiom -> Axiom -> Ordering
$cp1Ord :: Eq Axiom
Ord, Int -> Axiom -> ShowS
[Axiom] -> ShowS
Axiom -> String
(Int -> Axiom -> ShowS)
-> (Axiom -> String) -> ([Axiom] -> ShowS) -> Show Axiom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Axiom] -> ShowS
$cshowList :: [Axiom] -> ShowS
show :: Axiom -> String
$cshow :: Axiom -> String
showsPrec :: Int -> Axiom -> ShowS
$cshowsPrec :: Int -> Axiom -> ShowS
Show, Typeable, Typeable Axiom
Constr
DataType
Typeable Axiom =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Axiom -> c Axiom)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Axiom)
-> (Axiom -> Constr)
-> (Axiom -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Axiom))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Axiom))
-> ((forall b. Data b => b -> b) -> Axiom -> Axiom)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r)
-> (forall u. (forall d. Data d => d -> u) -> Axiom -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Axiom -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom)
-> Data Axiom
Axiom -> Constr
Axiom -> DataType
(forall b. Data b => b -> b) -> Axiom -> Axiom
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Axiom -> c Axiom
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Axiom
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Axiom -> u
forall u. (forall d. Data d => d -> u) -> Axiom -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Axiom
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Axiom -> c Axiom
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Axiom)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Axiom)
$cAxiom :: Constr
$tAxiom :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Axiom -> m Axiom
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom
gmapMp :: (forall d. Data d => d -> m d) -> Axiom -> m Axiom
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom
gmapM :: (forall d. Data d => d -> m d) -> Axiom -> m Axiom
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Axiom -> m Axiom
gmapQi :: Int -> (forall d. Data d => d -> u) -> Axiom -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Axiom -> u
gmapQ :: (forall d. Data d => d -> u) -> Axiom -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Axiom -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r
gmapT :: (forall b. Data b => b -> b) -> Axiom -> Axiom
$cgmapT :: (forall b. Data b => b -> b) -> Axiom -> Axiom
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Axiom)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Axiom)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Axiom)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Axiom)
dataTypeOf :: Axiom -> DataType
$cdataTypeOf :: Axiom -> DataType
toConstr :: Axiom -> Constr
$ctoConstr :: Axiom -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Axiom
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Axiom
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Axiom -> c Axiom
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Axiom -> c Axiom
$cp1Data :: Typeable Axiom
Data)
data FunSig = FunSig {
FunSig -> QName
funSigName :: QName,
FunSig -> Maybe Typ
funSigType :: Maybe Typ } deriving (FunSig -> FunSig -> Bool
(FunSig -> FunSig -> Bool)
-> (FunSig -> FunSig -> Bool) -> Eq FunSig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunSig -> FunSig -> Bool
$c/= :: FunSig -> FunSig -> Bool
== :: FunSig -> FunSig -> Bool
$c== :: FunSig -> FunSig -> Bool
Eq, Eq FunSig
Eq FunSig =>
(FunSig -> FunSig -> Ordering)
-> (FunSig -> FunSig -> Bool)
-> (FunSig -> FunSig -> Bool)
-> (FunSig -> FunSig -> Bool)
-> (FunSig -> FunSig -> Bool)
-> (FunSig -> FunSig -> FunSig)
-> (FunSig -> FunSig -> FunSig)
-> Ord FunSig
FunSig -> FunSig -> Bool
FunSig -> FunSig -> Ordering
FunSig -> FunSig -> FunSig
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FunSig -> FunSig -> FunSig
$cmin :: FunSig -> FunSig -> FunSig
max :: FunSig -> FunSig -> FunSig
$cmax :: FunSig -> FunSig -> FunSig
>= :: FunSig -> FunSig -> Bool
$c>= :: FunSig -> FunSig -> Bool
> :: FunSig -> FunSig -> Bool
$c> :: FunSig -> FunSig -> Bool
<= :: FunSig -> FunSig -> Bool
$c<= :: FunSig -> FunSig -> Bool
< :: FunSig -> FunSig -> Bool
$c< :: FunSig -> FunSig -> Bool
compare :: FunSig -> FunSig -> Ordering
$ccompare :: FunSig -> FunSig -> Ordering
$cp1Ord :: Eq FunSig
Ord, Int -> FunSig -> ShowS
[FunSig] -> ShowS
FunSig -> String
(Int -> FunSig -> ShowS)
-> (FunSig -> String) -> ([FunSig] -> ShowS) -> Show FunSig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunSig] -> ShowS
$cshowList :: [FunSig] -> ShowS
show :: FunSig -> String
$cshow :: FunSig -> String
showsPrec :: Int -> FunSig -> ShowS
$cshowsPrec :: Int -> FunSig -> ShowS
Show, Typeable, Typeable FunSig
Constr
DataType
Typeable FunSig =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunSig -> c FunSig)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunSig)
-> (FunSig -> Constr)
-> (FunSig -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunSig))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunSig))
-> ((forall b. Data b => b -> b) -> FunSig -> FunSig)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunSig -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunSig -> r)
-> (forall u. (forall d. Data d => d -> u) -> FunSig -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> FunSig -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig)
-> Data FunSig
FunSig -> Constr
FunSig -> DataType
(forall b. Data b => b -> b) -> FunSig -> FunSig
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunSig -> c FunSig
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunSig
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FunSig -> u
forall u. (forall d. Data d => d -> u) -> FunSig -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunSig -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunSig -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunSig
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunSig -> c FunSig
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunSig)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunSig)
$cFunSig :: Constr
$tFunSig :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FunSig -> m FunSig
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig
gmapMp :: (forall d. Data d => d -> m d) -> FunSig -> m FunSig
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig
gmapM :: (forall d. Data d => d -> m d) -> FunSig -> m FunSig
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunSig -> m FunSig
gmapQi :: Int -> (forall d. Data d => d -> u) -> FunSig -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FunSig -> u
gmapQ :: (forall d. Data d => d -> u) -> FunSig -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FunSig -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunSig -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunSig -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunSig -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunSig -> r
gmapT :: (forall b. Data b => b -> b) -> FunSig -> FunSig
$cgmapT :: (forall b. Data b => b -> b) -> FunSig -> FunSig
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunSig)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunSig)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FunSig)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunSig)
dataTypeOf :: FunSig -> DataType
$cdataTypeOf :: FunSig -> DataType
toConstr :: FunSig -> Constr
$ctoConstr :: FunSig -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunSig
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunSig
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunSig -> c FunSig
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunSig -> c FunSig
$cp1Data :: Typeable FunSig
Data)
data SetDecl
= SubSet Term Typ Term
| FixedSet [Term]
deriving (SetDecl -> SetDecl -> Bool
(SetDecl -> SetDecl -> Bool)
-> (SetDecl -> SetDecl -> Bool) -> Eq SetDecl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetDecl -> SetDecl -> Bool
$c/= :: SetDecl -> SetDecl -> Bool
== :: SetDecl -> SetDecl -> Bool
$c== :: SetDecl -> SetDecl -> Bool
Eq, Eq SetDecl
Eq SetDecl =>
(SetDecl -> SetDecl -> Ordering)
-> (SetDecl -> SetDecl -> Bool)
-> (SetDecl -> SetDecl -> Bool)
-> (SetDecl -> SetDecl -> Bool)
-> (SetDecl -> SetDecl -> Bool)
-> (SetDecl -> SetDecl -> SetDecl)
-> (SetDecl -> SetDecl -> SetDecl)
-> Ord SetDecl
SetDecl -> SetDecl -> Bool
SetDecl -> SetDecl -> Ordering
SetDecl -> SetDecl -> SetDecl
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SetDecl -> SetDecl -> SetDecl
$cmin :: SetDecl -> SetDecl -> SetDecl
max :: SetDecl -> SetDecl -> SetDecl
$cmax :: SetDecl -> SetDecl -> SetDecl
>= :: SetDecl -> SetDecl -> Bool
$c>= :: SetDecl -> SetDecl -> Bool
> :: SetDecl -> SetDecl -> Bool
$c> :: SetDecl -> SetDecl -> Bool
<= :: SetDecl -> SetDecl -> Bool
$c<= :: SetDecl -> SetDecl -> Bool
< :: SetDecl -> SetDecl -> Bool
$c< :: SetDecl -> SetDecl -> Bool
compare :: SetDecl -> SetDecl -> Ordering
$ccompare :: SetDecl -> SetDecl -> Ordering
$cp1Ord :: Eq SetDecl
Ord, Int -> SetDecl -> ShowS
[SetDecl] -> ShowS
SetDecl -> String
(Int -> SetDecl -> ShowS)
-> (SetDecl -> String) -> ([SetDecl] -> ShowS) -> Show SetDecl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetDecl] -> ShowS
$cshowList :: [SetDecl] -> ShowS
show :: SetDecl -> String
$cshow :: SetDecl -> String
showsPrec :: Int -> SetDecl -> ShowS
$cshowsPrec :: Int -> SetDecl -> ShowS
Show, Typeable, Typeable SetDecl
Constr
DataType
Typeable SetDecl =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SetDecl -> c SetDecl)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetDecl)
-> (SetDecl -> Constr)
-> (SetDecl -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SetDecl))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetDecl))
-> ((forall b. Data b => b -> b) -> SetDecl -> SetDecl)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r)
-> (forall u. (forall d. Data d => d -> u) -> SetDecl -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> SetDecl -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl)
-> Data SetDecl
SetDecl -> Constr
SetDecl -> DataType
(forall b. Data b => b -> b) -> SetDecl -> SetDecl
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SetDecl -> c SetDecl
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetDecl
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SetDecl -> u
forall u. (forall d. Data d => d -> u) -> SetDecl -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetDecl
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SetDecl -> c SetDecl
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SetDecl)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetDecl)
$cFixedSet :: Constr
$cSubSet :: Constr
$tSetDecl :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
gmapMp :: (forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
gmapM :: (forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SetDecl -> m SetDecl
gmapQi :: Int -> (forall d. Data d => d -> u) -> SetDecl -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SetDecl -> u
gmapQ :: (forall d. Data d => d -> u) -> SetDecl -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SetDecl -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetDecl -> r
gmapT :: (forall b. Data b => b -> b) -> SetDecl -> SetDecl
$cgmapT :: (forall b. Data b => b -> b) -> SetDecl -> SetDecl
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetDecl)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetDecl)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SetDecl)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SetDecl)
dataTypeOf :: SetDecl -> DataType
$cdataTypeOf :: SetDecl -> DataType
toConstr :: SetDecl -> Constr
$ctoConstr :: SetDecl -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetDecl
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetDecl
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SetDecl -> c SetDecl
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SetDecl -> c SetDecl
$cp1Data :: Typeable SetDecl
Data)
data MetaTerm = Term Term
| Conditional [Term] Term
deriving (MetaTerm -> MetaTerm -> Bool
(MetaTerm -> MetaTerm -> Bool)
-> (MetaTerm -> MetaTerm -> Bool) -> Eq MetaTerm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetaTerm -> MetaTerm -> Bool
$c/= :: MetaTerm -> MetaTerm -> Bool
== :: MetaTerm -> MetaTerm -> Bool
$c== :: MetaTerm -> MetaTerm -> Bool
Eq, Eq MetaTerm
Eq MetaTerm =>
(MetaTerm -> MetaTerm -> Ordering)
-> (MetaTerm -> MetaTerm -> Bool)
-> (MetaTerm -> MetaTerm -> Bool)
-> (MetaTerm -> MetaTerm -> Bool)
-> (MetaTerm -> MetaTerm -> Bool)
-> (MetaTerm -> MetaTerm -> MetaTerm)
-> (MetaTerm -> MetaTerm -> MetaTerm)
-> Ord MetaTerm
MetaTerm -> MetaTerm -> Bool
MetaTerm -> MetaTerm -> Ordering
MetaTerm -> MetaTerm -> MetaTerm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MetaTerm -> MetaTerm -> MetaTerm
$cmin :: MetaTerm -> MetaTerm -> MetaTerm
max :: MetaTerm -> MetaTerm -> MetaTerm
$cmax :: MetaTerm -> MetaTerm -> MetaTerm
>= :: MetaTerm -> MetaTerm -> Bool
$c>= :: MetaTerm -> MetaTerm -> Bool
> :: MetaTerm -> MetaTerm -> Bool
$c> :: MetaTerm -> MetaTerm -> Bool
<= :: MetaTerm -> MetaTerm -> Bool
$c<= :: MetaTerm -> MetaTerm -> Bool
< :: MetaTerm -> MetaTerm -> Bool
$c< :: MetaTerm -> MetaTerm -> Bool
compare :: MetaTerm -> MetaTerm -> Ordering
$ccompare :: MetaTerm -> MetaTerm -> Ordering
$cp1Ord :: Eq MetaTerm
Ord, Int -> MetaTerm -> ShowS
[MetaTerm] -> ShowS
MetaTerm -> String
(Int -> MetaTerm -> ShowS)
-> (MetaTerm -> String) -> ([MetaTerm] -> ShowS) -> Show MetaTerm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetaTerm] -> ShowS
$cshowList :: [MetaTerm] -> ShowS
show :: MetaTerm -> String
$cshow :: MetaTerm -> String
showsPrec :: Int -> MetaTerm -> ShowS
$cshowsPrec :: Int -> MetaTerm -> ShowS
Show, Typeable, Typeable MetaTerm
Constr
DataType
Typeable MetaTerm =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaTerm -> c MetaTerm)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaTerm)
-> (MetaTerm -> Constr)
-> (MetaTerm -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaTerm))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaTerm))
-> ((forall b. Data b => b -> b) -> MetaTerm -> MetaTerm)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r)
-> (forall u. (forall d. Data d => d -> u) -> MetaTerm -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> MetaTerm -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm)
-> Data MetaTerm
MetaTerm -> Constr
MetaTerm -> DataType
(forall b. Data b => b -> b) -> MetaTerm -> MetaTerm
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaTerm -> c MetaTerm
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaTerm
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MetaTerm -> u
forall u. (forall d. Data d => d -> u) -> MetaTerm -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaTerm
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaTerm -> c MetaTerm
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaTerm)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaTerm)
$cConditional :: Constr
$cTerm :: Constr
$tMetaTerm :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
gmapMp :: (forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
gmapM :: (forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaTerm -> m MetaTerm
gmapQi :: Int -> (forall d. Data d => d -> u) -> MetaTerm -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MetaTerm -> u
gmapQ :: (forall d. Data d => d -> u) -> MetaTerm -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MetaTerm -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaTerm -> r
gmapT :: (forall b. Data b => b -> b) -> MetaTerm -> MetaTerm
$cgmapT :: (forall b. Data b => b -> b) -> MetaTerm -> MetaTerm
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaTerm)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaTerm)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c MetaTerm)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaTerm)
dataTypeOf :: MetaTerm -> DataType
$cdataTypeOf :: MetaTerm -> DataType
toConstr :: MetaTerm -> Constr
$ctoConstr :: MetaTerm -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaTerm
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaTerm
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaTerm -> c MetaTerm
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaTerm -> c MetaTerm
$cp1Data :: Typeable MetaTerm
Data)
mkSenAux :: Bool -> MetaTerm -> Sentence
mkSenAux :: Bool -> MetaTerm -> Sentence
mkSenAux b :: Bool
b t :: MetaTerm
t = Sentence :: Bool -> Bool -> MetaTerm -> Maybe IsaProof -> Sentence
Sentence
{ isSimp :: Bool
isSimp = Bool
False
, isRefuteAux :: Bool
isRefuteAux = Bool
b
, thmProof :: Maybe IsaProof
thmProof = Maybe IsaProof
forall a. Maybe a
Nothing
, metaTerm :: MetaTerm
metaTerm = MetaTerm
t }
mkSen :: Term -> Sentence
mkSen :: Term -> Sentence
mkSen = Bool -> MetaTerm -> Sentence
mkSenAux Bool
False (MetaTerm -> Sentence) -> (Term -> MetaTerm) -> Term -> Sentence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term -> MetaTerm
Term
mkCond :: [Term] -> Term -> Sentence
mkCond :: [Term] -> Term -> Sentence
mkCond conds :: [Term]
conds = Bool -> MetaTerm -> Sentence
mkSenAux Bool
False (MetaTerm -> Sentence) -> (Term -> MetaTerm) -> Term -> Sentence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Term] -> Term -> MetaTerm
Conditional [Term]
conds
mkRefuteSen :: Term -> Sentence
mkRefuteSen :: Term -> Sentence
mkRefuteSen = Bool -> MetaTerm -> Sentence
mkSenAux Bool
True (MetaTerm -> Sentence) -> (Term -> MetaTerm) -> Term -> Sentence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term -> MetaTerm
Term
isRefute :: Sentence -> Bool
isRefute :: Sentence -> Bool
isRefute s :: Sentence
s = case Sentence
s of
Sentence { isRefuteAux :: Sentence -> Bool
isRefuteAux = Bool
b } -> Bool
b
_ -> Bool
False
type ClassDecl = ([IsaClass], [(String, Term)], [(String, Typ)])
type Classrel = Map.Map IsaClass ClassDecl
type LocaleDecl = ([String], [(String, Term)], [(String, Term)],
[(String, Typ, Maybe AltSyntax)])
type Def = (Typ, [(String, Typ)], Term)
type FunDef = (Typ, [([Term], Term)])
type Locales = Map.Map String LocaleDecl
type Defs = Map.Map String Def
type Funs = Map.Map String FunDef
type Arities = Map.Map TName [(IsaClass, [(Typ, Sort)])]
type Abbrs = Map.Map TName ([TName], Typ)
data TypeSig =
TySg {
TypeSig -> Classrel
classrel :: Classrel,
TypeSig -> Locales
locales :: Locales,
TypeSig -> Defs
defs :: Defs,
TypeSig -> Funs
funs :: Funs,
TypeSig -> [IsaClass]
defaultSort :: Sort,
TypeSig -> [String]
log_types :: [TName],
TypeSig -> Maybe (Typ, [IsaClass])
univ_witness :: Maybe (Typ, Sort),
TypeSig -> Abbrs
abbrs :: Abbrs,
TypeSig -> Arities
arities :: Arities }
deriving (TypeSig -> TypeSig -> Bool
(TypeSig -> TypeSig -> Bool)
-> (TypeSig -> TypeSig -> Bool) -> Eq TypeSig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSig -> TypeSig -> Bool
$c/= :: TypeSig -> TypeSig -> Bool
== :: TypeSig -> TypeSig -> Bool
$c== :: TypeSig -> TypeSig -> Bool
Eq, Eq TypeSig
Eq TypeSig =>
(TypeSig -> TypeSig -> Ordering)
-> (TypeSig -> TypeSig -> Bool)
-> (TypeSig -> TypeSig -> Bool)
-> (TypeSig -> TypeSig -> Bool)
-> (TypeSig -> TypeSig -> Bool)
-> (TypeSig -> TypeSig -> TypeSig)
-> (TypeSig -> TypeSig -> TypeSig)
-> Ord TypeSig
TypeSig -> TypeSig -> Bool
TypeSig -> TypeSig -> Ordering
TypeSig -> TypeSig -> TypeSig
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeSig -> TypeSig -> TypeSig
$cmin :: TypeSig -> TypeSig -> TypeSig
max :: TypeSig -> TypeSig -> TypeSig
$cmax :: TypeSig -> TypeSig -> TypeSig
>= :: TypeSig -> TypeSig -> Bool
$c>= :: TypeSig -> TypeSig -> Bool
> :: TypeSig -> TypeSig -> Bool
$c> :: TypeSig -> TypeSig -> Bool
<= :: TypeSig -> TypeSig -> Bool
$c<= :: TypeSig -> TypeSig -> Bool
< :: TypeSig -> TypeSig -> Bool
$c< :: TypeSig -> TypeSig -> Bool
compare :: TypeSig -> TypeSig -> Ordering
$ccompare :: TypeSig -> TypeSig -> Ordering
$cp1Ord :: Eq TypeSig
Ord, Int -> TypeSig -> ShowS
[TypeSig] -> ShowS
TypeSig -> String
(Int -> TypeSig -> ShowS)
-> (TypeSig -> String) -> ([TypeSig] -> ShowS) -> Show TypeSig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeSig] -> ShowS
$cshowList :: [TypeSig] -> ShowS
show :: TypeSig -> String
$cshow :: TypeSig -> String
showsPrec :: Int -> TypeSig -> ShowS
$cshowsPrec :: Int -> TypeSig -> ShowS
Show, Typeable)
emptyTypeSig :: TypeSig
emptyTypeSig :: TypeSig
emptyTypeSig = TySg :: Classrel
-> Locales
-> Defs
-> Funs
-> [IsaClass]
-> [String]
-> Maybe (Typ, [IsaClass])
-> Abbrs
-> Arities
-> TypeSig
TySg {
classrel :: Classrel
classrel = Classrel
forall k a. Map k a
Map.empty,
locales :: Locales
locales = Locales
forall k a. Map k a
Map.empty,
defs :: Defs
defs = Defs
forall k a. Map k a
Map.empty,
funs :: Funs
funs = Funs
forall k a. Map k a
Map.empty,
defaultSort :: [IsaClass]
defaultSort = [],
log_types :: [String]
log_types = [],
univ_witness :: Maybe (Typ, [IsaClass])
univ_witness = Maybe (Typ, [IsaClass])
forall a. Maybe a
Nothing,
abbrs :: Abbrs
abbrs = Abbrs
forall k a. Map k a
Map.empty,
arities :: Arities
arities = Arities
forall k a. Map k a
Map.empty }
isSubTypeSig :: TypeSig -> TypeSig -> Bool
isSubTypeSig :: TypeSig -> TypeSig -> Bool
isSubTypeSig t1 :: TypeSig
t1 t2 :: TypeSig
t2 =
[IsaClass] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (TypeSig -> [IsaClass]
defaultSort TypeSig
t1 [IsaClass] -> [IsaClass] -> [IsaClass]
forall a. Eq a => [a] -> [a] -> [a]
\\ TypeSig -> [IsaClass]
defaultSort TypeSig
t2) Bool -> Bool -> Bool
&&
Classrel -> Classrel -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (TypeSig -> Classrel
classrel TypeSig
t1) (TypeSig -> Classrel
classrel TypeSig
t2) Bool -> Bool -> Bool
&&
Locales -> Locales -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (TypeSig -> Locales
locales TypeSig
t1) (TypeSig -> Locales
locales TypeSig
t2) Bool -> Bool -> Bool
&&
Defs -> Defs -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (TypeSig -> Defs
defs TypeSig
t1) (TypeSig -> Defs
defs TypeSig
t2) Bool -> Bool -> Bool
&&
Funs -> Funs -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (TypeSig -> Funs
funs TypeSig
t1) (TypeSig -> Funs
funs TypeSig
t2) Bool -> Bool -> Bool
&&
[String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (TypeSig -> [String]
log_types TypeSig
t1 [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
\\ TypeSig -> [String]
log_types TypeSig
t2) Bool -> Bool -> Bool
&&
(case TypeSig -> Maybe (Typ, [IsaClass])
univ_witness TypeSig
t1 of
Nothing -> Bool
True
w1 :: Maybe (Typ, [IsaClass])
w1 -> Maybe (Typ, [IsaClass])
w1 Maybe (Typ, [IsaClass]) -> Maybe (Typ, [IsaClass]) -> Bool
forall a. Eq a => a -> a -> Bool
== TypeSig -> Maybe (Typ, [IsaClass])
univ_witness TypeSig
t2) Bool -> Bool -> Bool
&&
Abbrs -> Abbrs -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (TypeSig -> Abbrs
abbrs TypeSig
t1) (TypeSig -> Abbrs
abbrs TypeSig
t2) Bool -> Bool -> Bool
&&
Arities -> Arities -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (TypeSig -> Arities
arities TypeSig
t1) (TypeSig -> Arities
arities TypeSig
t2)
data BaseSig =
Main_thy
| Custom_thy
| MainHC_thy
| MainHCPairs_thy
| HOLCF_thy
| HsHOLCF_thy
| HsHOL_thy
| MHsHOL_thy
| MHsHOLCF_thy
| CspHOLComplex_thy
deriving (BaseSig -> BaseSig -> Bool
(BaseSig -> BaseSig -> Bool)
-> (BaseSig -> BaseSig -> Bool) -> Eq BaseSig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BaseSig -> BaseSig -> Bool
$c/= :: BaseSig -> BaseSig -> Bool
== :: BaseSig -> BaseSig -> Bool
$c== :: BaseSig -> BaseSig -> Bool
Eq, Eq BaseSig
Eq BaseSig =>
(BaseSig -> BaseSig -> Ordering)
-> (BaseSig -> BaseSig -> Bool)
-> (BaseSig -> BaseSig -> Bool)
-> (BaseSig -> BaseSig -> Bool)
-> (BaseSig -> BaseSig -> Bool)
-> (BaseSig -> BaseSig -> BaseSig)
-> (BaseSig -> BaseSig -> BaseSig)
-> Ord BaseSig
BaseSig -> BaseSig -> Bool
BaseSig -> BaseSig -> Ordering
BaseSig -> BaseSig -> BaseSig
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BaseSig -> BaseSig -> BaseSig
$cmin :: BaseSig -> BaseSig -> BaseSig
max :: BaseSig -> BaseSig -> BaseSig
$cmax :: BaseSig -> BaseSig -> BaseSig
>= :: BaseSig -> BaseSig -> Bool
$c>= :: BaseSig -> BaseSig -> Bool
> :: BaseSig -> BaseSig -> Bool
$c> :: BaseSig -> BaseSig -> Bool
<= :: BaseSig -> BaseSig -> Bool
$c<= :: BaseSig -> BaseSig -> Bool
< :: BaseSig -> BaseSig -> Bool
$c< :: BaseSig -> BaseSig -> Bool
compare :: BaseSig -> BaseSig -> Ordering
$ccompare :: BaseSig -> BaseSig -> Ordering
$cp1Ord :: Eq BaseSig
Ord, Int -> BaseSig -> ShowS
[BaseSig] -> ShowS
BaseSig -> String
(Int -> BaseSig -> ShowS)
-> (BaseSig -> String) -> ([BaseSig] -> ShowS) -> Show BaseSig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BaseSig] -> ShowS
$cshowList :: [BaseSig] -> ShowS
show :: BaseSig -> String
$cshow :: BaseSig -> String
showsPrec :: Int -> BaseSig -> ShowS
$cshowsPrec :: Int -> BaseSig -> ShowS
Show, Typeable)
data Sign = Sign
{ Sign -> String
theoryName :: String
, :: Maybe String
, Sign -> [String]
keywords :: [String]
, Sign -> [String]
uses :: [String]
, Sign -> BaseSig
baseSig :: BaseSig
, Sign -> [String]
imports :: [String]
, Sign -> TypeSig
tsig :: TypeSig
, Sign -> ConstTab
constTab :: ConstTab
, Sign -> DomainTab
domainTab :: DomainTab
, Sign -> Bool
showLemmas :: Bool
} deriving (Sign -> Sign -> Bool
(Sign -> Sign -> Bool) -> (Sign -> Sign -> Bool) -> Eq Sign
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sign -> Sign -> Bool
$c/= :: Sign -> Sign -> Bool
== :: Sign -> Sign -> Bool
$c== :: Sign -> Sign -> Bool
Eq, Eq Sign
Eq Sign =>
(Sign -> Sign -> Ordering)
-> (Sign -> Sign -> Bool)
-> (Sign -> Sign -> Bool)
-> (Sign -> Sign -> Bool)
-> (Sign -> Sign -> Bool)
-> (Sign -> Sign -> Sign)
-> (Sign -> Sign -> Sign)
-> Ord Sign
Sign -> Sign -> Bool
Sign -> Sign -> Ordering
Sign -> Sign -> Sign
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Sign -> Sign -> Sign
$cmin :: Sign -> Sign -> Sign
max :: Sign -> Sign -> Sign
$cmax :: Sign -> Sign -> Sign
>= :: Sign -> Sign -> Bool
$c>= :: Sign -> Sign -> Bool
> :: Sign -> Sign -> Bool
$c> :: Sign -> Sign -> Bool
<= :: Sign -> Sign -> Bool
$c<= :: Sign -> Sign -> Bool
< :: Sign -> Sign -> Bool
$c< :: Sign -> Sign -> Bool
compare :: Sign -> Sign -> Ordering
$ccompare :: Sign -> Sign -> Ordering
$cp1Ord :: Eq Sign
Ord, Int -> Sign -> ShowS
[Sign] -> ShowS
Sign -> String
(Int -> Sign -> ShowS)
-> (Sign -> String) -> ([Sign] -> ShowS) -> Show Sign
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Sign] -> ShowS
$cshowList :: [Sign] -> ShowS
show :: Sign -> String
$cshow :: Sign -> String
showsPrec :: Int -> Sign -> ShowS
$cshowsPrec :: Int -> Sign -> ShowS
Show, Typeable)
type ConstTab = Map.Map VName Typ
type DomainTab = [[DomainEntry]]
type DomainEntry = (Typ, [(VName, [Typ])])
emptySign :: Sign
emptySign :: Sign
emptySign = Sign :: String
-> Maybe String
-> [String]
-> [String]
-> BaseSig
-> [String]
-> TypeSig
-> ConstTab
-> DomainTab
-> Bool
-> Sign
Sign
{ theoryName :: String
theoryName = "thy"
, header :: Maybe String
header = Maybe String
forall a. Maybe a
Nothing
, keywords :: [String]
keywords = []
, uses :: [String]
uses = []
, baseSig :: BaseSig
baseSig = BaseSig
Main_thy
, imports :: [String]
imports = []
, tsig :: TypeSig
tsig = TypeSig
emptyTypeSig
, constTab :: ConstTab
constTab = ConstTab
forall k a. Map k a
Map.empty
, domainTab :: DomainTab
domainTab = []
, showLemmas :: Bool
showLemmas = Bool
False }
isSubSign :: Sign -> Sign -> Bool
isSubSign :: Sign -> Sign -> Bool
isSubSign s1 :: Sign
s1 s2 :: Sign
s2 =
TypeSig -> TypeSig -> Bool
isSubTypeSig (Sign -> TypeSig
tsig Sign
s1) (Sign -> TypeSig
tsig Sign
s2) Bool -> Bool -> Bool
&&
ConstTab -> ConstTab -> Bool
forall k a. (Ord k, Eq a) => Map k a -> Map k a -> Bool
Map.isSubmapOf (Sign -> ConstTab
constTab Sign
s1) (Sign -> ConstTab
constTab Sign
s2) Bool -> Bool -> Bool
&&
DomainTab -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Sign -> DomainTab
domainTab Sign
s1 DomainTab -> DomainTab -> DomainTab
forall a. Eq a => [a] -> [a] -> [a]
\\ Sign -> DomainTab
domainTab Sign
s2)
union_tsig :: TypeSig -> TypeSig -> TypeSig
union_tsig :: TypeSig -> TypeSig -> TypeSig
union_tsig t1 :: TypeSig
t1 t2 :: TypeSig
t2 = TypeSig
t1 {
classrel :: Classrel
classrel = Classrel -> Classrel -> Classrel
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (TypeSig -> Classrel
classrel TypeSig
t1) (TypeSig -> Classrel
classrel TypeSig
t2),
locales :: Locales
locales = Locales -> Locales -> Locales
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (TypeSig -> Locales
locales TypeSig
t1) (TypeSig -> Locales
locales TypeSig
t2),
defs :: Defs
defs = Defs -> Defs -> Defs
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (TypeSig -> Defs
defs TypeSig
t1) (TypeSig -> Defs
defs TypeSig
t2),
funs :: Funs
funs = Funs -> Funs -> Funs
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (TypeSig -> Funs
funs TypeSig
t1) (TypeSig -> Funs
funs TypeSig
t2),
log_types :: [String]
log_types = [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
Data.List.union (TypeSig -> [String]
log_types TypeSig
t1) (TypeSig -> [String]
log_types TypeSig
t2),
abbrs :: Abbrs
abbrs = Abbrs -> Abbrs -> Abbrs
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (TypeSig -> Abbrs
abbrs TypeSig
t1) (TypeSig -> Abbrs
abbrs TypeSig
t2),
arities :: Arities
arities = Arities -> Arities -> Arities
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (TypeSig -> Arities
arities TypeSig
t1) (TypeSig -> Arities
arities TypeSig
t2)
}
union_sig :: Sign -> Sign -> Sign
union_sig :: Sign -> Sign -> Sign
union_sig s1 :: Sign
s1 s2 :: Sign
s2 = Sign
s1 {
tsig :: TypeSig
tsig = TypeSig -> TypeSig -> TypeSig
union_tsig (Sign -> TypeSig
tsig Sign
s1) (Sign -> TypeSig
tsig Sign
s2),
constTab :: ConstTab
constTab = ConstTab -> ConstTab -> ConstTab
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (Sign -> ConstTab
constTab Sign
s1) (Sign -> ConstTab
constTab Sign
s2),
domainTab :: DomainTab
domainTab = DomainTab -> DomainTab -> DomainTab
forall a. Eq a => [a] -> [a] -> [a]
Data.List.union (Sign -> DomainTab
domainTab Sign
s1) (Sign -> DomainTab
domainTab Sign
s2)
}
data IsaProof = IsaProof
{ IsaProof -> [ProofCommand]
proof :: [ProofCommand],
IsaProof -> ProofEnd
end :: ProofEnd
} deriving (Int -> IsaProof -> ShowS
[IsaProof] -> ShowS
IsaProof -> String
(Int -> IsaProof -> ShowS)
-> (IsaProof -> String) -> ([IsaProof] -> ShowS) -> Show IsaProof
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsaProof] -> ShowS
$cshowList :: [IsaProof] -> ShowS
show :: IsaProof -> String
$cshow :: IsaProof -> String
showsPrec :: Int -> IsaProof -> ShowS
$cshowsPrec :: Int -> IsaProof -> ShowS
Show, IsaProof -> IsaProof -> Bool
(IsaProof -> IsaProof -> Bool)
-> (IsaProof -> IsaProof -> Bool) -> Eq IsaProof
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsaProof -> IsaProof -> Bool
$c/= :: IsaProof -> IsaProof -> Bool
== :: IsaProof -> IsaProof -> Bool
$c== :: IsaProof -> IsaProof -> Bool
Eq, Eq IsaProof
Eq IsaProof =>
(IsaProof -> IsaProof -> Ordering)
-> (IsaProof -> IsaProof -> Bool)
-> (IsaProof -> IsaProof -> Bool)
-> (IsaProof -> IsaProof -> Bool)
-> (IsaProof -> IsaProof -> Bool)
-> (IsaProof -> IsaProof -> IsaProof)
-> (IsaProof -> IsaProof -> IsaProof)
-> Ord IsaProof
IsaProof -> IsaProof -> Bool
IsaProof -> IsaProof -> Ordering
IsaProof -> IsaProof -> IsaProof
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IsaProof -> IsaProof -> IsaProof
$cmin :: IsaProof -> IsaProof -> IsaProof
max :: IsaProof -> IsaProof -> IsaProof
$cmax :: IsaProof -> IsaProof -> IsaProof
>= :: IsaProof -> IsaProof -> Bool
$c>= :: IsaProof -> IsaProof -> Bool
> :: IsaProof -> IsaProof -> Bool
$c> :: IsaProof -> IsaProof -> Bool
<= :: IsaProof -> IsaProof -> Bool
$c<= :: IsaProof -> IsaProof -> Bool
< :: IsaProof -> IsaProof -> Bool
$c< :: IsaProof -> IsaProof -> Bool
compare :: IsaProof -> IsaProof -> Ordering
$ccompare :: IsaProof -> IsaProof -> Ordering
$cp1Ord :: Eq IsaProof
Ord, Typeable, Typeable IsaProof
Constr
DataType
Typeable IsaProof =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaProof -> c IsaProof)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaProof)
-> (IsaProof -> Constr)
-> (IsaProof -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsaProof))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaProof))
-> ((forall b. Data b => b -> b) -> IsaProof -> IsaProof)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r)
-> (forall u. (forall d. Data d => d -> u) -> IsaProof -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> IsaProof -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof)
-> Data IsaProof
IsaProof -> Constr
IsaProof -> DataType
(forall b. Data b => b -> b) -> IsaProof -> IsaProof
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaProof -> c IsaProof
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaProof
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IsaProof -> u
forall u. (forall d. Data d => d -> u) -> IsaProof -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaProof
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaProof -> c IsaProof
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsaProof)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaProof)
$cIsaProof :: Constr
$tIsaProof :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
gmapMp :: (forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
gmapM :: (forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IsaProof -> m IsaProof
gmapQi :: Int -> (forall d. Data d => d -> u) -> IsaProof -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IsaProof -> u
gmapQ :: (forall d. Data d => d -> u) -> IsaProof -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IsaProof -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsaProof -> r
gmapT :: (forall b. Data b => b -> b) -> IsaProof -> IsaProof
$cgmapT :: (forall b. Data b => b -> b) -> IsaProof -> IsaProof
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaProof)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsaProof)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c IsaProof)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsaProof)
dataTypeOf :: IsaProof -> DataType
$cdataTypeOf :: IsaProof -> DataType
toConstr :: IsaProof -> Constr
$ctoConstr :: IsaProof -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaProof
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsaProof
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaProof -> c IsaProof
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsaProof -> c IsaProof
$cp1Data :: Typeable IsaProof
Data)
data ProofCommand
= Apply [ProofMethod] Bool
| Using [String]
| Back
| Defer Int
| Prefer Int
| Refute
deriving (Int -> ProofCommand -> ShowS
[ProofCommand] -> ShowS
ProofCommand -> String
(Int -> ProofCommand -> ShowS)
-> (ProofCommand -> String)
-> ([ProofCommand] -> ShowS)
-> Show ProofCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProofCommand] -> ShowS
$cshowList :: [ProofCommand] -> ShowS
show :: ProofCommand -> String
$cshow :: ProofCommand -> String
showsPrec :: Int -> ProofCommand -> ShowS
$cshowsPrec :: Int -> ProofCommand -> ShowS
Show, ProofCommand -> ProofCommand -> Bool
(ProofCommand -> ProofCommand -> Bool)
-> (ProofCommand -> ProofCommand -> Bool) -> Eq ProofCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProofCommand -> ProofCommand -> Bool
$c/= :: ProofCommand -> ProofCommand -> Bool
== :: ProofCommand -> ProofCommand -> Bool
$c== :: ProofCommand -> ProofCommand -> Bool
Eq, Eq ProofCommand
Eq ProofCommand =>
(ProofCommand -> ProofCommand -> Ordering)
-> (ProofCommand -> ProofCommand -> Bool)
-> (ProofCommand -> ProofCommand -> Bool)
-> (ProofCommand -> ProofCommand -> Bool)
-> (ProofCommand -> ProofCommand -> Bool)
-> (ProofCommand -> ProofCommand -> ProofCommand)
-> (ProofCommand -> ProofCommand -> ProofCommand)
-> Ord ProofCommand
ProofCommand -> ProofCommand -> Bool
ProofCommand -> ProofCommand -> Ordering
ProofCommand -> ProofCommand -> ProofCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ProofCommand -> ProofCommand -> ProofCommand
$cmin :: ProofCommand -> ProofCommand -> ProofCommand
max :: ProofCommand -> ProofCommand -> ProofCommand
$cmax :: ProofCommand -> ProofCommand -> ProofCommand
>= :: ProofCommand -> ProofCommand -> Bool
$c>= :: ProofCommand -> ProofCommand -> Bool
> :: ProofCommand -> ProofCommand -> Bool
$c> :: ProofCommand -> ProofCommand -> Bool
<= :: ProofCommand -> ProofCommand -> Bool
$c<= :: ProofCommand -> ProofCommand -> Bool
< :: ProofCommand -> ProofCommand -> Bool
$c< :: ProofCommand -> ProofCommand -> Bool
compare :: ProofCommand -> ProofCommand -> Ordering
$ccompare :: ProofCommand -> ProofCommand -> Ordering
$cp1Ord :: Eq ProofCommand
Ord, Typeable, Typeable ProofCommand
Constr
DataType
Typeable ProofCommand =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofCommand -> c ProofCommand)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofCommand)
-> (ProofCommand -> Constr)
-> (ProofCommand -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofCommand))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofCommand))
-> ((forall b. Data b => b -> b) -> ProofCommand -> ProofCommand)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r)
-> (forall u. (forall d. Data d => d -> u) -> ProofCommand -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ProofCommand -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand)
-> Data ProofCommand
ProofCommand -> Constr
ProofCommand -> DataType
(forall b. Data b => b -> b) -> ProofCommand -> ProofCommand
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofCommand -> c ProofCommand
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofCommand
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ProofCommand -> u
forall u. (forall d. Data d => d -> u) -> ProofCommand -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofCommand
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofCommand -> c ProofCommand
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofCommand)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofCommand)
$cRefute :: Constr
$cPrefer :: Constr
$cDefer :: Constr
$cBack :: Constr
$cUsing :: Constr
$cApply :: Constr
$tProofCommand :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
gmapMp :: (forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
gmapM :: (forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofCommand -> m ProofCommand
gmapQi :: Int -> (forall d. Data d => d -> u) -> ProofCommand -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ProofCommand -> u
gmapQ :: (forall d. Data d => d -> u) -> ProofCommand -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ProofCommand -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofCommand -> r
gmapT :: (forall b. Data b => b -> b) -> ProofCommand -> ProofCommand
$cgmapT :: (forall b. Data b => b -> b) -> ProofCommand -> ProofCommand
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofCommand)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofCommand)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ProofCommand)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofCommand)
dataTypeOf :: ProofCommand -> DataType
$cdataTypeOf :: ProofCommand -> DataType
toConstr :: ProofCommand -> Constr
$ctoConstr :: ProofCommand -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofCommand
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofCommand
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofCommand -> c ProofCommand
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofCommand -> c ProofCommand
$cp1Data :: Typeable ProofCommand
Data)
data ProofEnd
= By ProofMethod
| DotDot
| Done
| Oops
| Sorry
deriving (Int -> ProofEnd -> ShowS
[ProofEnd] -> ShowS
ProofEnd -> String
(Int -> ProofEnd -> ShowS)
-> (ProofEnd -> String) -> ([ProofEnd] -> ShowS) -> Show ProofEnd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProofEnd] -> ShowS
$cshowList :: [ProofEnd] -> ShowS
show :: ProofEnd -> String
$cshow :: ProofEnd -> String
showsPrec :: Int -> ProofEnd -> ShowS
$cshowsPrec :: Int -> ProofEnd -> ShowS
Show, ProofEnd -> ProofEnd -> Bool
(ProofEnd -> ProofEnd -> Bool)
-> (ProofEnd -> ProofEnd -> Bool) -> Eq ProofEnd
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProofEnd -> ProofEnd -> Bool
$c/= :: ProofEnd -> ProofEnd -> Bool
== :: ProofEnd -> ProofEnd -> Bool
$c== :: ProofEnd -> ProofEnd -> Bool
Eq, Eq ProofEnd
Eq ProofEnd =>
(ProofEnd -> ProofEnd -> Ordering)
-> (ProofEnd -> ProofEnd -> Bool)
-> (ProofEnd -> ProofEnd -> Bool)
-> (ProofEnd -> ProofEnd -> Bool)
-> (ProofEnd -> ProofEnd -> Bool)
-> (ProofEnd -> ProofEnd -> ProofEnd)
-> (ProofEnd -> ProofEnd -> ProofEnd)
-> Ord ProofEnd
ProofEnd -> ProofEnd -> Bool
ProofEnd -> ProofEnd -> Ordering
ProofEnd -> ProofEnd -> ProofEnd
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ProofEnd -> ProofEnd -> ProofEnd
$cmin :: ProofEnd -> ProofEnd -> ProofEnd
max :: ProofEnd -> ProofEnd -> ProofEnd
$cmax :: ProofEnd -> ProofEnd -> ProofEnd
>= :: ProofEnd -> ProofEnd -> Bool
$c>= :: ProofEnd -> ProofEnd -> Bool
> :: ProofEnd -> ProofEnd -> Bool
$c> :: ProofEnd -> ProofEnd -> Bool
<= :: ProofEnd -> ProofEnd -> Bool
$c<= :: ProofEnd -> ProofEnd -> Bool
< :: ProofEnd -> ProofEnd -> Bool
$c< :: ProofEnd -> ProofEnd -> Bool
compare :: ProofEnd -> ProofEnd -> Ordering
$ccompare :: ProofEnd -> ProofEnd -> Ordering
$cp1Ord :: Eq ProofEnd
Ord, Typeable, Typeable ProofEnd
Constr
DataType
Typeable ProofEnd =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofEnd -> c ProofEnd)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofEnd)
-> (ProofEnd -> Constr)
-> (ProofEnd -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofEnd))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProofEnd))
-> ((forall b. Data b => b -> b) -> ProofEnd -> ProofEnd)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r)
-> (forall u. (forall d. Data d => d -> u) -> ProofEnd -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ProofEnd -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd)
-> Data ProofEnd
ProofEnd -> Constr
ProofEnd -> DataType
(forall b. Data b => b -> b) -> ProofEnd -> ProofEnd
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofEnd -> c ProofEnd
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofEnd
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ProofEnd -> u
forall u. (forall d. Data d => d -> u) -> ProofEnd -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofEnd
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofEnd -> c ProofEnd
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofEnd)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProofEnd)
$cSorry :: Constr
$cOops :: Constr
$cDone :: Constr
$cDotDot :: Constr
$cBy :: Constr
$tProofEnd :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
gmapMp :: (forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
gmapM :: (forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofEnd -> m ProofEnd
gmapQi :: Int -> (forall d. Data d => d -> u) -> ProofEnd -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ProofEnd -> u
gmapQ :: (forall d. Data d => d -> u) -> ProofEnd -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ProofEnd -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofEnd -> r
gmapT :: (forall b. Data b => b -> b) -> ProofEnd -> ProofEnd
$cgmapT :: (forall b. Data b => b -> b) -> ProofEnd -> ProofEnd
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProofEnd)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProofEnd)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ProofEnd)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofEnd)
dataTypeOf :: ProofEnd -> DataType
$cdataTypeOf :: ProofEnd -> DataType
toConstr :: ProofEnd -> Constr
$ctoConstr :: ProofEnd -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofEnd
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofEnd
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofEnd -> c ProofEnd
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofEnd -> c ProofEnd
$cp1Data :: Typeable ProofEnd
Data)
data Modifier
= No_asm
| No_asm_simp
| No_asm_use
deriving (Int -> Modifier -> ShowS
[Modifier] -> ShowS
Modifier -> String
(Int -> Modifier -> ShowS)
-> (Modifier -> String) -> ([Modifier] -> ShowS) -> Show Modifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Modifier] -> ShowS
$cshowList :: [Modifier] -> ShowS
show :: Modifier -> String
$cshow :: Modifier -> String
showsPrec :: Int -> Modifier -> ShowS
$cshowsPrec :: Int -> Modifier -> ShowS
Show, Modifier -> Modifier -> Bool
(Modifier -> Modifier -> Bool)
-> (Modifier -> Modifier -> Bool) -> Eq Modifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Modifier -> Modifier -> Bool
$c/= :: Modifier -> Modifier -> Bool
== :: Modifier -> Modifier -> Bool
$c== :: Modifier -> Modifier -> Bool
Eq, Eq Modifier
Eq Modifier =>
(Modifier -> Modifier -> Ordering)
-> (Modifier -> Modifier -> Bool)
-> (Modifier -> Modifier -> Bool)
-> (Modifier -> Modifier -> Bool)
-> (Modifier -> Modifier -> Bool)
-> (Modifier -> Modifier -> Modifier)
-> (Modifier -> Modifier -> Modifier)
-> Ord Modifier
Modifier -> Modifier -> Bool
Modifier -> Modifier -> Ordering
Modifier -> Modifier -> Modifier
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Modifier -> Modifier -> Modifier
$cmin :: Modifier -> Modifier -> Modifier
max :: Modifier -> Modifier -> Modifier
$cmax :: Modifier -> Modifier -> Modifier
>= :: Modifier -> Modifier -> Bool
$c>= :: Modifier -> Modifier -> Bool
> :: Modifier -> Modifier -> Bool
$c> :: Modifier -> Modifier -> Bool
<= :: Modifier -> Modifier -> Bool
$c<= :: Modifier -> Modifier -> Bool
< :: Modifier -> Modifier -> Bool
$c< :: Modifier -> Modifier -> Bool
compare :: Modifier -> Modifier -> Ordering
$ccompare :: Modifier -> Modifier -> Ordering
$cp1Ord :: Eq Modifier
Ord, Typeable, Typeable Modifier
Constr
DataType
Typeable Modifier =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Modifier -> c Modifier)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Modifier)
-> (Modifier -> Constr)
-> (Modifier -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Modifier))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Modifier))
-> ((forall b. Data b => b -> b) -> Modifier -> Modifier)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r)
-> (forall u. (forall d. Data d => d -> u) -> Modifier -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Modifier -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier)
-> Data Modifier
Modifier -> Constr
Modifier -> DataType
(forall b. Data b => b -> b) -> Modifier -> Modifier
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Modifier -> c Modifier
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Modifier
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Modifier -> u
forall u. (forall d. Data d => d -> u) -> Modifier -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Modifier
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Modifier -> c Modifier
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Modifier)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Modifier)
$cNo_asm_use :: Constr
$cNo_asm_simp :: Constr
$cNo_asm :: Constr
$tModifier :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Modifier -> m Modifier
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier
gmapMp :: (forall d. Data d => d -> m d) -> Modifier -> m Modifier
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier
gmapM :: (forall d. Data d => d -> m d) -> Modifier -> m Modifier
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Modifier -> m Modifier
gmapQi :: Int -> (forall d. Data d => d -> u) -> Modifier -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Modifier -> u
gmapQ :: (forall d. Data d => d -> u) -> Modifier -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Modifier -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Modifier -> r
gmapT :: (forall b. Data b => b -> b) -> Modifier -> Modifier
$cgmapT :: (forall b. Data b => b -> b) -> Modifier -> Modifier
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Modifier)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Modifier)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Modifier)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Modifier)
dataTypeOf :: Modifier -> DataType
$cdataTypeOf :: Modifier -> DataType
toConstr :: Modifier -> Constr
$ctoConstr :: Modifier -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Modifier
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Modifier
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Modifier -> c Modifier
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Modifier -> c Modifier
$cp1Data :: Typeable Modifier
Data)
data ProofMethod
= Auto
| Simp
| AutoSimpAdd (Maybe Modifier) [String]
| SimpAdd (Maybe Modifier) [String]
| Induct Term
| CaseTac Term
| SubgoalTac Term
| Insert [String]
| Other String
deriving (Int -> ProofMethod -> ShowS
[ProofMethod] -> ShowS
ProofMethod -> String
(Int -> ProofMethod -> ShowS)
-> (ProofMethod -> String)
-> ([ProofMethod] -> ShowS)
-> Show ProofMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProofMethod] -> ShowS
$cshowList :: [ProofMethod] -> ShowS
show :: ProofMethod -> String
$cshow :: ProofMethod -> String
showsPrec :: Int -> ProofMethod -> ShowS
$cshowsPrec :: Int -> ProofMethod -> ShowS
Show, ProofMethod -> ProofMethod -> Bool
(ProofMethod -> ProofMethod -> Bool)
-> (ProofMethod -> ProofMethod -> Bool) -> Eq ProofMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProofMethod -> ProofMethod -> Bool
$c/= :: ProofMethod -> ProofMethod -> Bool
== :: ProofMethod -> ProofMethod -> Bool
$c== :: ProofMethod -> ProofMethod -> Bool
Eq, Eq ProofMethod
Eq ProofMethod =>
(ProofMethod -> ProofMethod -> Ordering)
-> (ProofMethod -> ProofMethod -> Bool)
-> (ProofMethod -> ProofMethod -> Bool)
-> (ProofMethod -> ProofMethod -> Bool)
-> (ProofMethod -> ProofMethod -> Bool)
-> (ProofMethod -> ProofMethod -> ProofMethod)
-> (ProofMethod -> ProofMethod -> ProofMethod)
-> Ord ProofMethod
ProofMethod -> ProofMethod -> Bool
ProofMethod -> ProofMethod -> Ordering
ProofMethod -> ProofMethod -> ProofMethod
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ProofMethod -> ProofMethod -> ProofMethod
$cmin :: ProofMethod -> ProofMethod -> ProofMethod
max :: ProofMethod -> ProofMethod -> ProofMethod
$cmax :: ProofMethod -> ProofMethod -> ProofMethod
>= :: ProofMethod -> ProofMethod -> Bool
$c>= :: ProofMethod -> ProofMethod -> Bool
> :: ProofMethod -> ProofMethod -> Bool
$c> :: ProofMethod -> ProofMethod -> Bool
<= :: ProofMethod -> ProofMethod -> Bool
$c<= :: ProofMethod -> ProofMethod -> Bool
< :: ProofMethod -> ProofMethod -> Bool
$c< :: ProofMethod -> ProofMethod -> Bool
compare :: ProofMethod -> ProofMethod -> Ordering
$ccompare :: ProofMethod -> ProofMethod -> Ordering
$cp1Ord :: Eq ProofMethod
Ord, Typeable, Typeable ProofMethod
Constr
DataType
Typeable ProofMethod =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofMethod -> c ProofMethod)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofMethod)
-> (ProofMethod -> Constr)
-> (ProofMethod -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofMethod))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofMethod))
-> ((forall b. Data b => b -> b) -> ProofMethod -> ProofMethod)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r)
-> (forall u. (forall d. Data d => d -> u) -> ProofMethod -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ProofMethod -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod)
-> Data ProofMethod
ProofMethod -> Constr
ProofMethod -> DataType
(forall b. Data b => b -> b) -> ProofMethod -> ProofMethod
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofMethod -> c ProofMethod
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofMethod
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ProofMethod -> u
forall u. (forall d. Data d => d -> u) -> ProofMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofMethod -> c ProofMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofMethod)
$cOther :: Constr
$cInsert :: Constr
$cSubgoalTac :: Constr
$cCaseTac :: Constr
$cInduct :: Constr
$cSimpAdd :: Constr
$cAutoSimpAdd :: Constr
$cSimp :: Constr
$cAuto :: Constr
$tProofMethod :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
gmapMp :: (forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
gmapM :: (forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ProofMethod -> m ProofMethod
gmapQi :: Int -> (forall d. Data d => d -> u) -> ProofMethod -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ProofMethod -> u
gmapQ :: (forall d. Data d => d -> u) -> ProofMethod -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ProofMethod -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ProofMethod -> r
gmapT :: (forall b. Data b => b -> b) -> ProofMethod -> ProofMethod
$cgmapT :: (forall b. Data b => b -> b) -> ProofMethod -> ProofMethod
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ProofMethod)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ProofMethod)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ProofMethod)
dataTypeOf :: ProofMethod -> DataType
$cdataTypeOf :: ProofMethod -> DataType
toConstr :: ProofMethod -> Constr
$ctoConstr :: ProofMethod -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ProofMethod
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofMethod -> c ProofMethod
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ProofMethod -> c ProofMethod
$cp1Data :: Typeable ProofMethod
Data)
toIsaProof :: ProofEnd -> IsaProof
toIsaProof :: ProofEnd -> IsaProof
toIsaProof = [ProofCommand] -> ProofEnd -> IsaProof
IsaProof []
mkOops :: IsaProof
mkOops :: IsaProof
mkOops = ProofEnd -> IsaProof
toIsaProof ProofEnd
Oops