clafer-0.4.4: Compiles Clafer models to other formats: Alloy, JavaScript, JSON, HTML, Dot.

Safe HaskellSafe
LanguageHaskell2010

Language.Clafer.Front.AbsClafer

Documentation

data Pos Source #

Constructors

Pos Integer Integer 

Instances

Eq Pos Source # 

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Data Pos Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pos -> c Pos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pos #

toConstr :: Pos -> Constr #

dataTypeOf :: Pos -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Pos) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos) #

gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

Ord Pos Source # 

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Read Pos Source # 
Show Pos Source # 

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 

Associated Types

type Rep Pos :: * -> * #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

type Rep Pos Source # 

data Span Source #

Constructors

Span Pos Pos 

Instances

Eq Span Source # 

Methods

(==) :: Span -> Span -> Bool #

(/=) :: Span -> Span -> Bool #

Data Span Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Span -> c Span #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Span #

toConstr :: Span -> Constr #

dataTypeOf :: Span -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Span) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span) #

gmapT :: (forall b. Data b => b -> b) -> Span -> Span #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r #

gmapQ :: (forall d. Data d => d -> u) -> Span -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Span -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #

Ord Span Source # 

Methods

compare :: Span -> Span -> Ordering #

(<) :: Span -> Span -> Bool #

(<=) :: Span -> Span -> Bool #

(>) :: Span -> Span -> Bool #

(>=) :: Span -> Span -> Bool #

max :: Span -> Span -> Span #

min :: Span -> Span -> Span #

Read Span Source # 
Show Span Source # 

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Generic Span Source # 

Associated Types

type Rep Span :: * -> * #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

type Rep Span Source # 
type Rep Span = D1 (MetaData "Span" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "Span" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pos)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pos))))

class Spannable n where Source #

Minimal complete definition

getSpan

Methods

getSpan :: n -> Span Source #

Instances

Spannable LocId Source # 

Methods

getSpan :: LocId -> Span Source #

Spannable ModId Source # 

Methods

getSpan :: ModId -> Span Source #

Spannable EnumId Source # 

Methods

getSpan :: EnumId -> Span Source #

Spannable Quant Source # 

Methods

getSpan :: Quant -> Span Source #

Spannable Decl Source # 

Methods

getSpan :: Decl -> Span Source #

Spannable Exp Source # 

Methods

getSpan :: Exp -> Span Source #

Spannable Name Source # 

Methods

getSpan :: Name -> Span Source #

Spannable ExInteger Source # 
Spannable NCard Source # 

Methods

getSpan :: NCard -> Span Source #

Spannable Card Source # 

Methods

getSpan :: Card -> Span Source #

Spannable GCard Source # 

Methods

getSpan :: GCard -> Span Source #

Spannable InitHow Source # 

Methods

getSpan :: InitHow -> Span Source #

Spannable Init Source # 

Methods

getSpan :: Init -> Span Source #

Spannable Reference Source # 
Spannable Super Source # 

Methods

getSpan :: Super -> Span Source #

Spannable Element Source # 

Methods

getSpan :: Element -> Span Source #

Spannable Elements Source # 
Spannable Abstract Source # 
Spannable Goal Source # 

Methods

getSpan :: Goal -> Span Source #

Spannable Assertion Source # 
Spannable Constraint Source # 
Spannable Clafer Source # 

Methods

getSpan :: Clafer -> Span Source #

Spannable Declaration Source # 
Spannable Module Source # 

Methods

getSpan :: Module -> Span Source #

Spannable PosChoco Source # 
Spannable PosAlloy Source # 
Spannable PosBlockComment Source # 
Spannable PosLineComment Source # 
Spannable PosIdent Source # 
Spannable PosString Source # 
Spannable PosReal Source # 

Methods

getSpan :: PosReal -> Span Source #

Spannable PosDouble Source # 
Spannable PosInteger Source # 
Spannable n => Spannable [n] Source # 

Methods

getSpan :: [n] -> Span Source #

len :: [a] -> Integer Source #

newtype PosInteger Source #

Constructors

PosInteger ((Int, Int), String) 

Instances

Eq PosInteger Source # 
Data PosInteger Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosInteger -> c PosInteger #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosInteger #

toConstr :: PosInteger -> Constr #

dataTypeOf :: PosInteger -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosInteger) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosInteger) #

gmapT :: (forall b. Data b => b -> b) -> PosInteger -> PosInteger #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosInteger -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosInteger -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosInteger -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosInteger -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosInteger -> m PosInteger #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosInteger -> m PosInteger #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosInteger -> m PosInteger #

Ord PosInteger Source # 
Read PosInteger Source # 
Show PosInteger Source # 
Generic PosInteger Source # 

Associated Types

type Rep PosInteger :: * -> * #

Spannable PosInteger Source # 
Print PosInteger Source # 
type Rep PosInteger Source # 
type Rep PosInteger = D1 (MetaData "PosInteger" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosInteger" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosDouble Source #

Constructors

PosDouble ((Int, Int), String) 

Instances

Eq PosDouble Source # 
Data PosDouble Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosDouble -> c PosDouble #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosDouble #

toConstr :: PosDouble -> Constr #

dataTypeOf :: PosDouble -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosDouble) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosDouble) #

gmapT :: (forall b. Data b => b -> b) -> PosDouble -> PosDouble #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosDouble -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosDouble -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosDouble -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosDouble -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosDouble -> m PosDouble #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosDouble -> m PosDouble #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosDouble -> m PosDouble #

Ord PosDouble Source # 
Read PosDouble Source # 
Show PosDouble Source # 
Generic PosDouble Source # 

Associated Types

type Rep PosDouble :: * -> * #

Spannable PosDouble Source # 
Print PosDouble Source # 

Methods

prt :: Int -> PosDouble -> Doc Source #

prtList :: Int -> [PosDouble] -> Doc Source #

type Rep PosDouble Source # 
type Rep PosDouble = D1 (MetaData "PosDouble" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosDouble" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosReal Source #

Constructors

PosReal ((Int, Int), String) 

Instances

Eq PosReal Source # 

Methods

(==) :: PosReal -> PosReal -> Bool #

(/=) :: PosReal -> PosReal -> Bool #

Data PosReal Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosReal -> c PosReal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosReal #

toConstr :: PosReal -> Constr #

dataTypeOf :: PosReal -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosReal) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosReal) #

gmapT :: (forall b. Data b => b -> b) -> PosReal -> PosReal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosReal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosReal -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosReal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosReal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosReal -> m PosReal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosReal -> m PosReal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosReal -> m PosReal #

Ord PosReal Source # 
Read PosReal Source # 
Show PosReal Source # 
Generic PosReal Source # 

Associated Types

type Rep PosReal :: * -> * #

Methods

from :: PosReal -> Rep PosReal x #

to :: Rep PosReal x -> PosReal #

Spannable PosReal Source # 

Methods

getSpan :: PosReal -> Span Source #

Print PosReal Source # 

Methods

prt :: Int -> PosReal -> Doc Source #

prtList :: Int -> [PosReal] -> Doc Source #

type Rep PosReal Source # 
type Rep PosReal = D1 (MetaData "PosReal" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosReal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosString Source #

Constructors

PosString ((Int, Int), String) 

Instances

Eq PosString Source # 
Data PosString Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosString -> c PosString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosString #

toConstr :: PosString -> Constr #

dataTypeOf :: PosString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosString) #

gmapT :: (forall b. Data b => b -> b) -> PosString -> PosString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosString -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosString -> m PosString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosString -> m PosString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosString -> m PosString #

Ord PosString Source # 
Read PosString Source # 
Show PosString Source # 
Generic PosString Source # 

Associated Types

type Rep PosString :: * -> * #

Spannable PosString Source # 
Print PosString Source # 

Methods

prt :: Int -> PosString -> Doc Source #

prtList :: Int -> [PosString] -> Doc Source #

type Rep PosString Source # 
type Rep PosString = D1 (MetaData "PosString" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosString" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosIdent Source #

Constructors

PosIdent ((Int, Int), String) 

Instances

Eq PosIdent Source # 
Data PosIdent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosIdent -> c PosIdent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosIdent #

toConstr :: PosIdent -> Constr #

dataTypeOf :: PosIdent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosIdent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosIdent) #

gmapT :: (forall b. Data b => b -> b) -> PosIdent -> PosIdent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosIdent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosIdent -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosIdent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosIdent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosIdent -> m PosIdent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosIdent -> m PosIdent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosIdent -> m PosIdent #

Ord PosIdent Source # 
Read PosIdent Source # 
Show PosIdent Source # 
Generic PosIdent Source # 

Associated Types

type Rep PosIdent :: * -> * #

Methods

from :: PosIdent -> Rep PosIdent x #

to :: Rep PosIdent x -> PosIdent #

Spannable PosIdent Source # 
Print PosIdent Source # 

Methods

prt :: Int -> PosIdent -> Doc Source #

prtList :: Int -> [PosIdent] -> Doc Source #

type Rep PosIdent Source # 
type Rep PosIdent = D1 (MetaData "PosIdent" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosIdent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosLineComment Source #

Constructors

PosLineComment ((Int, Int), String) 

Instances

Eq PosLineComment Source # 
Data PosLineComment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosLineComment -> c PosLineComment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosLineComment #

toConstr :: PosLineComment -> Constr #

dataTypeOf :: PosLineComment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosLineComment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosLineComment) #

gmapT :: (forall b. Data b => b -> b) -> PosLineComment -> PosLineComment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosLineComment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosLineComment -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosLineComment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosLineComment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosLineComment -> m PosLineComment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosLineComment -> m PosLineComment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosLineComment -> m PosLineComment #

Ord PosLineComment Source # 
Read PosLineComment Source # 
Show PosLineComment Source # 
Generic PosLineComment Source # 

Associated Types

type Rep PosLineComment :: * -> * #

Spannable PosLineComment Source # 
Print PosLineComment Source # 
type Rep PosLineComment Source # 
type Rep PosLineComment = D1 (MetaData "PosLineComment" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosLineComment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosBlockComment Source #

Constructors

PosBlockComment ((Int, Int), String) 

Instances

Eq PosBlockComment Source # 
Data PosBlockComment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosBlockComment -> c PosBlockComment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosBlockComment #

toConstr :: PosBlockComment -> Constr #

dataTypeOf :: PosBlockComment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosBlockComment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosBlockComment) #

gmapT :: (forall b. Data b => b -> b) -> PosBlockComment -> PosBlockComment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosBlockComment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosBlockComment -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosBlockComment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosBlockComment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosBlockComment -> m PosBlockComment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosBlockComment -> m PosBlockComment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosBlockComment -> m PosBlockComment #

Ord PosBlockComment Source # 
Read PosBlockComment Source # 
Show PosBlockComment Source # 
Generic PosBlockComment Source # 
Spannable PosBlockComment Source # 
Print PosBlockComment Source # 
type Rep PosBlockComment Source # 
type Rep PosBlockComment = D1 (MetaData "PosBlockComment" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosBlockComment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosAlloy Source #

Constructors

PosAlloy ((Int, Int), String) 

Instances

Eq PosAlloy Source # 
Data PosAlloy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosAlloy -> c PosAlloy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosAlloy #

toConstr :: PosAlloy -> Constr #

dataTypeOf :: PosAlloy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosAlloy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosAlloy) #

gmapT :: (forall b. Data b => b -> b) -> PosAlloy -> PosAlloy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosAlloy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosAlloy -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosAlloy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosAlloy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosAlloy -> m PosAlloy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosAlloy -> m PosAlloy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosAlloy -> m PosAlloy #

Ord PosAlloy Source # 
Read PosAlloy Source # 
Show PosAlloy Source # 
Generic PosAlloy Source # 

Associated Types

type Rep PosAlloy :: * -> * #

Methods

from :: PosAlloy -> Rep PosAlloy x #

to :: Rep PosAlloy x -> PosAlloy #

Spannable PosAlloy Source # 
Print PosAlloy Source # 

Methods

prt :: Int -> PosAlloy -> Doc Source #

prtList :: Int -> [PosAlloy] -> Doc Source #

type Rep PosAlloy Source # 
type Rep PosAlloy = D1 (MetaData "PosAlloy" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosAlloy" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype PosChoco Source #

Constructors

PosChoco ((Int, Int), String) 

Instances

Eq PosChoco Source # 
Data PosChoco Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosChoco -> c PosChoco #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosChoco #

toConstr :: PosChoco -> Constr #

dataTypeOf :: PosChoco -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PosChoco) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosChoco) #

gmapT :: (forall b. Data b => b -> b) -> PosChoco -> PosChoco #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosChoco -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosChoco -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosChoco -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosChoco -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosChoco -> m PosChoco #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosChoco -> m PosChoco #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosChoco -> m PosChoco #

Ord PosChoco Source # 
Read PosChoco Source # 
Show PosChoco Source # 
Generic PosChoco Source # 

Associated Types

type Rep PosChoco :: * -> * #

Methods

from :: PosChoco -> Rep PosChoco x #

to :: Rep PosChoco x -> PosChoco #

Spannable PosChoco Source # 
Print PosChoco Source # 

Methods

prt :: Int -> PosChoco -> Doc Source #

prtList :: Int -> [PosChoco] -> Doc Source #

type Rep PosChoco Source # 
type Rep PosChoco = D1 (MetaData "PosChoco" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" True) (C1 (MetaCons "PosChoco" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

data Module Source #

Constructors

Module Span [Declaration] 

Instances

Eq Module Source # 

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Data Module Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module #

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Module) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) #

gmapT :: (forall b. Data b => b -> b) -> Module -> Module #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

Ord Module Source # 
Read Module Source # 
Show Module Source # 
Generic Module Source # 

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Spannable Module Source # 

Methods

getSpan :: Module -> Span Source #

Print Module Source # 

Methods

prt :: Int -> Module -> Doc Source #

prtList :: Int -> [Module] -> Doc Source #

type Rep Module Source # 
type Rep Module = D1 (MetaData "Module" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "Module" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Declaration]))))

data Declaration Source #

Instances

Eq Declaration Source # 
Data Declaration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Declaration -> c Declaration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Declaration #

toConstr :: Declaration -> Constr #

dataTypeOf :: Declaration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Declaration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Declaration) #

gmapT :: (forall b. Data b => b -> b) -> Declaration -> Declaration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Declaration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Declaration -> r #

gmapQ :: (forall d. Data d => d -> u) -> Declaration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Declaration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Declaration -> m Declaration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Declaration -> m Declaration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Declaration -> m Declaration #

Ord Declaration Source # 
Read Declaration Source # 
Show Declaration Source # 
Generic Declaration Source # 

Associated Types

type Rep Declaration :: * -> * #

Spannable Declaration Source # 
Print Declaration Source # 
type Rep Declaration Source # 

data Clafer Source #

Instances

Eq Clafer Source # 

Methods

(==) :: Clafer -> Clafer -> Bool #

(/=) :: Clafer -> Clafer -> Bool #

Data Clafer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Clafer -> c Clafer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Clafer #

toConstr :: Clafer -> Constr #

dataTypeOf :: Clafer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Clafer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Clafer) #

gmapT :: (forall b. Data b => b -> b) -> Clafer -> Clafer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Clafer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Clafer -> r #

gmapQ :: (forall d. Data d => d -> u) -> Clafer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Clafer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Clafer -> m Clafer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Clafer -> m Clafer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Clafer -> m Clafer #

Ord Clafer Source # 
Read Clafer Source # 
Show Clafer Source # 
Generic Clafer Source # 

Associated Types

type Rep Clafer :: * -> * #

Methods

from :: Clafer -> Rep Clafer x #

to :: Rep Clafer x -> Clafer #

Spannable Clafer Source # 

Methods

getSpan :: Clafer -> Span Source #

Print Clafer Source # 

Methods

prt :: Int -> Clafer -> Doc Source #

prtList :: Int -> [Clafer] -> Doc Source #

type Rep Clafer Source # 

data Constraint Source #

Constructors

Constraint Span [Exp] 

Instances

Eq Constraint Source # 
Data Constraint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Constraint -> c Constraint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Constraint #

toConstr :: Constraint -> Constr #

dataTypeOf :: Constraint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Constraint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Constraint) #

gmapT :: (forall b. Data b => b -> b) -> Constraint -> Constraint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Constraint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Constraint -> r #

gmapQ :: (forall d. Data d => d -> u) -> Constraint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Constraint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Constraint -> m Constraint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Constraint -> m Constraint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Constraint -> m Constraint #

Ord Constraint Source # 
Read Constraint Source # 
Show Constraint Source # 
Generic Constraint Source # 

Associated Types

type Rep Constraint :: * -> * #

Spannable Constraint Source # 
Print Constraint Source # 
type Rep Constraint Source # 
type Rep Constraint = D1 (MetaData "Constraint" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "Constraint" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Exp]))))

data Assertion Source #

Constructors

Assertion Span [Exp] 

Instances

Eq Assertion Source # 
Data Assertion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Assertion -> c Assertion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Assertion #

toConstr :: Assertion -> Constr #

dataTypeOf :: Assertion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Assertion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Assertion) #

gmapT :: (forall b. Data b => b -> b) -> Assertion -> Assertion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Assertion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Assertion -> r #

gmapQ :: (forall d. Data d => d -> u) -> Assertion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Assertion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Assertion -> m Assertion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Assertion -> m Assertion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Assertion -> m Assertion #

Ord Assertion Source # 
Read Assertion Source # 
Show Assertion Source # 
Generic Assertion Source # 

Associated Types

type Rep Assertion :: * -> * #

Spannable Assertion Source # 
Print Assertion Source # 

Methods

prt :: Int -> Assertion -> Doc Source #

prtList :: Int -> [Assertion] -> Doc Source #

type Rep Assertion Source # 
type Rep Assertion = D1 (MetaData "Assertion" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "Assertion" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Exp]))))

data Goal Source #

Instances

Eq Goal Source # 

Methods

(==) :: Goal -> Goal -> Bool #

(/=) :: Goal -> Goal -> Bool #

Data Goal Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Goal -> c Goal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Goal #

toConstr :: Goal -> Constr #

dataTypeOf :: Goal -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Goal) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Goal) #

gmapT :: (forall b. Data b => b -> b) -> Goal -> Goal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Goal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Goal -> r #

gmapQ :: (forall d. Data d => d -> u) -> Goal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Goal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Goal -> m Goal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Goal -> m Goal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Goal -> m Goal #

Ord Goal Source # 

Methods

compare :: Goal -> Goal -> Ordering #

(<) :: Goal -> Goal -> Bool #

(<=) :: Goal -> Goal -> Bool #

(>) :: Goal -> Goal -> Bool #

(>=) :: Goal -> Goal -> Bool #

max :: Goal -> Goal -> Goal #

min :: Goal -> Goal -> Goal #

Read Goal Source # 
Show Goal Source # 

Methods

showsPrec :: Int -> Goal -> ShowS #

show :: Goal -> String #

showList :: [Goal] -> ShowS #

Generic Goal Source # 

Associated Types

type Rep Goal :: * -> * #

Methods

from :: Goal -> Rep Goal x #

to :: Rep Goal x -> Goal #

Spannable Goal Source # 

Methods

getSpan :: Goal -> Span Source #

Print Goal Source # 

Methods

prt :: Int -> Goal -> Doc Source #

prtList :: Int -> [Goal] -> Doc Source #

type Rep Goal Source # 

data Abstract Source #

Instances

Eq Abstract Source # 
Data Abstract Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Abstract -> c Abstract #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Abstract #

toConstr :: Abstract -> Constr #

dataTypeOf :: Abstract -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Abstract) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Abstract) #

gmapT :: (forall b. Data b => b -> b) -> Abstract -> Abstract #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Abstract -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Abstract -> r #

gmapQ :: (forall d. Data d => d -> u) -> Abstract -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Abstract -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Abstract -> m Abstract #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Abstract -> m Abstract #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Abstract -> m Abstract #

Ord Abstract Source # 
Read Abstract Source # 
Show Abstract Source # 
Generic Abstract Source # 

Associated Types

type Rep Abstract :: * -> * #

Methods

from :: Abstract -> Rep Abstract x #

to :: Rep Abstract x -> Abstract #

Spannable Abstract Source # 
Print Abstract Source # 

Methods

prt :: Int -> Abstract -> Doc Source #

prtList :: Int -> [Abstract] -> Doc Source #

type Rep Abstract Source # 
type Rep Abstract = D1 (MetaData "Abstract" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) ((:+:) (C1 (MetaCons "AbstractEmpty" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span))) (C1 (MetaCons "Abstract" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span))))

data Elements Source #

Instances

Eq Elements Source # 
Data Elements Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Elements -> c Elements #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Elements #

toConstr :: Elements -> Constr #

dataTypeOf :: Elements -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Elements) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Elements) #

gmapT :: (forall b. Data b => b -> b) -> Elements -> Elements #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Elements -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Elements -> r #

gmapQ :: (forall d. Data d => d -> u) -> Elements -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Elements -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Elements -> m Elements #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Elements -> m Elements #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Elements -> m Elements #

Ord Elements Source # 
Read Elements Source # 
Show Elements Source # 
Generic Elements Source # 

Associated Types

type Rep Elements :: * -> * #

Methods

from :: Elements -> Rep Elements x #

to :: Rep Elements x -> Elements #

Spannable Elements Source # 
Print Elements Source # 

Methods

prt :: Int -> Elements -> Doc Source #

prtList :: Int -> [Elements] -> Doc Source #

type Rep Elements Source # 

data Element Source #

Instances

Eq Element Source # 

Methods

(==) :: Element -> Element -> Bool #

(/=) :: Element -> Element -> Bool #

Data Element Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element #

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Element) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) #

gmapT :: (forall b. Data b => b -> b) -> Element -> Element #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

Ord Element Source # 
Read Element Source # 
Show Element Source # 
Generic Element Source # 

Associated Types

type Rep Element :: * -> * #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

Spannable Element Source # 

Methods

getSpan :: Element -> Span Source #

Print Element Source # 

Methods

prt :: Int -> Element -> Doc Source #

prtList :: Int -> [Element] -> Doc Source #

type Rep Element Source # 
type Rep Element = D1 (MetaData "Element" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) ((:+:) ((:+:) (C1 (MetaCons "Subclafer" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Clafer)))) (C1 (MetaCons "ClaferUse" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Card)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Elements)))))) ((:+:) (C1 (MetaCons "Subconstraint" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Constraint)))) ((:+:) (C1 (MetaCons "Subgoal" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Goal)))) (C1 (MetaCons "SubAssertion" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Assertion)))))))

data Super Source #

Instances

Eq Super Source # 

Methods

(==) :: Super -> Super -> Bool #

(/=) :: Super -> Super -> Bool #

Data Super Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Super -> c Super #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Super #

toConstr :: Super -> Constr #

dataTypeOf :: Super -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Super) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Super) #

gmapT :: (forall b. Data b => b -> b) -> Super -> Super #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Super -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Super -> r #

gmapQ :: (forall d. Data d => d -> u) -> Super -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Super -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Super -> m Super #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Super -> m Super #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Super -> m Super #

Ord Super Source # 

Methods

compare :: Super -> Super -> Ordering #

(<) :: Super -> Super -> Bool #

(<=) :: Super -> Super -> Bool #

(>) :: Super -> Super -> Bool #

(>=) :: Super -> Super -> Bool #

max :: Super -> Super -> Super #

min :: Super -> Super -> Super #

Read Super Source # 
Show Super Source # 

Methods

showsPrec :: Int -> Super -> ShowS #

show :: Super -> String #

showList :: [Super] -> ShowS #

Generic Super Source # 

Associated Types

type Rep Super :: * -> * #

Methods

from :: Super -> Rep Super x #

to :: Rep Super x -> Super #

Spannable Super Source # 

Methods

getSpan :: Super -> Span Source #

Print Super Source # 

Methods

prt :: Int -> Super -> Doc Source #

prtList :: Int -> [Super] -> Doc Source #

type Rep Super Source # 

data Reference Source #

Instances

Eq Reference Source # 
Data Reference Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Reference -> c Reference #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Reference #

toConstr :: Reference -> Constr #

dataTypeOf :: Reference -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Reference) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference) #

gmapT :: (forall b. Data b => b -> b) -> Reference -> Reference #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Reference -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Reference -> r #

gmapQ :: (forall d. Data d => d -> u) -> Reference -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Reference -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Reference -> m Reference #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Reference -> m Reference #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Reference -> m Reference #

Ord Reference Source # 
Read Reference Source # 
Show Reference Source # 
Generic Reference Source # 

Associated Types

type Rep Reference :: * -> * #

Spannable Reference Source # 
Print Reference Source # 

Methods

prt :: Int -> Reference -> Doc Source #

prtList :: Int -> [Reference] -> Doc Source #

type Rep Reference Source # 

data Init Source #

Instances

Eq Init Source # 

Methods

(==) :: Init -> Init -> Bool #

(/=) :: Init -> Init -> Bool #

Data Init Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Init -> c Init #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Init #

toConstr :: Init -> Constr #

dataTypeOf :: Init -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Init) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Init) #

gmapT :: (forall b. Data b => b -> b) -> Init -> Init #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Init -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Init -> r #

gmapQ :: (forall d. Data d => d -> u) -> Init -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Init -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Init -> m Init #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Init -> m Init #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Init -> m Init #

Ord Init Source # 

Methods

compare :: Init -> Init -> Ordering #

(<) :: Init -> Init -> Bool #

(<=) :: Init -> Init -> Bool #

(>) :: Init -> Init -> Bool #

(>=) :: Init -> Init -> Bool #

max :: Init -> Init -> Init #

min :: Init -> Init -> Init #

Read Init Source # 
Show Init Source # 

Methods

showsPrec :: Int -> Init -> ShowS #

show :: Init -> String #

showList :: [Init] -> ShowS #

Generic Init Source # 

Associated Types

type Rep Init :: * -> * #

Methods

from :: Init -> Rep Init x #

to :: Rep Init x -> Init #

Spannable Init Source # 

Methods

getSpan :: Init -> Span Source #

Print Init Source # 

Methods

prt :: Int -> Init -> Doc Source #

prtList :: Int -> [Init] -> Doc Source #

type Rep Init Source # 

data InitHow Source #

Instances

Eq InitHow Source # 

Methods

(==) :: InitHow -> InitHow -> Bool #

(/=) :: InitHow -> InitHow -> Bool #

Data InitHow Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitHow -> c InitHow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitHow #

toConstr :: InitHow -> Constr #

dataTypeOf :: InitHow -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InitHow) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitHow) #

gmapT :: (forall b. Data b => b -> b) -> InitHow -> InitHow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitHow -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitHow -> r #

gmapQ :: (forall d. Data d => d -> u) -> InitHow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InitHow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitHow -> m InitHow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitHow -> m InitHow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitHow -> m InitHow #

Ord InitHow Source # 
Read InitHow Source # 
Show InitHow Source # 
Generic InitHow Source # 

Associated Types

type Rep InitHow :: * -> * #

Methods

from :: InitHow -> Rep InitHow x #

to :: Rep InitHow x -> InitHow #

Spannable InitHow Source # 

Methods

getSpan :: InitHow -> Span Source #

Print InitHow Source # 

Methods

prt :: Int -> InitHow -> Doc Source #

prtList :: Int -> [InitHow] -> Doc Source #

type Rep InitHow Source # 
type Rep InitHow = D1 (MetaData "InitHow" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) ((:+:) (C1 (MetaCons "InitConstant" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span))) (C1 (MetaCons "InitDefault" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span))))

data GCard Source #

Instances

Eq GCard Source # 

Methods

(==) :: GCard -> GCard -> Bool #

(/=) :: GCard -> GCard -> Bool #

Data GCard Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GCard -> c GCard #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GCard #

toConstr :: GCard -> Constr #

dataTypeOf :: GCard -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GCard) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCard) #

gmapT :: (forall b. Data b => b -> b) -> GCard -> GCard #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GCard -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GCard -> r #

gmapQ :: (forall d. Data d => d -> u) -> GCard -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GCard -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GCard -> m GCard #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GCard -> m GCard #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GCard -> m GCard #

Ord GCard Source # 

Methods

compare :: GCard -> GCard -> Ordering #

(<) :: GCard -> GCard -> Bool #

(<=) :: GCard -> GCard -> Bool #

(>) :: GCard -> GCard -> Bool #

(>=) :: GCard -> GCard -> Bool #

max :: GCard -> GCard -> GCard #

min :: GCard -> GCard -> GCard #

Read GCard Source # 
Show GCard Source # 

Methods

showsPrec :: Int -> GCard -> ShowS #

show :: GCard -> String #

showList :: [GCard] -> ShowS #

Generic GCard Source # 

Associated Types

type Rep GCard :: * -> * #

Methods

from :: GCard -> Rep GCard x #

to :: Rep GCard x -> GCard #

Spannable GCard Source # 

Methods

getSpan :: GCard -> Span Source #

Print GCard Source # 

Methods

prt :: Int -> GCard -> Doc Source #

prtList :: Int -> [GCard] -> Doc Source #

type Rep GCard Source # 

data Card Source #

Instances

Eq Card Source # 

Methods

(==) :: Card -> Card -> Bool #

(/=) :: Card -> Card -> Bool #

Data Card Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Card -> c Card #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Card #

toConstr :: Card -> Constr #

dataTypeOf :: Card -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Card) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Card) #

gmapT :: (forall b. Data b => b -> b) -> Card -> Card #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Card -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Card -> r #

gmapQ :: (forall d. Data d => d -> u) -> Card -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Card -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Card -> m Card #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Card -> m Card #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Card -> m Card #

Ord Card Source # 

Methods

compare :: Card -> Card -> Ordering #

(<) :: Card -> Card -> Bool #

(<=) :: Card -> Card -> Bool #

(>) :: Card -> Card -> Bool #

(>=) :: Card -> Card -> Bool #

max :: Card -> Card -> Card #

min :: Card -> Card -> Card #

Read Card Source # 
Show Card Source # 

Methods

showsPrec :: Int -> Card -> ShowS #

show :: Card -> String #

showList :: [Card] -> ShowS #

Generic Card Source # 

Associated Types

type Rep Card :: * -> * #

Methods

from :: Card -> Rep Card x #

to :: Rep Card x -> Card #

Spannable Card Source # 

Methods

getSpan :: Card -> Span Source #

Print Card Source # 

Methods

prt :: Int -> Card -> Doc Source #

prtList :: Int -> [Card] -> Doc Source #

type Rep Card Source # 

data NCard Source #

Instances

Eq NCard Source # 

Methods

(==) :: NCard -> NCard -> Bool #

(/=) :: NCard -> NCard -> Bool #

Data NCard Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NCard -> c NCard #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NCard #

toConstr :: NCard -> Constr #

dataTypeOf :: NCard -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NCard) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NCard) #

gmapT :: (forall b. Data b => b -> b) -> NCard -> NCard #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NCard -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NCard -> r #

gmapQ :: (forall d. Data d => d -> u) -> NCard -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NCard -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NCard -> m NCard #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NCard -> m NCard #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NCard -> m NCard #

Ord NCard Source # 

Methods

compare :: NCard -> NCard -> Ordering #

(<) :: NCard -> NCard -> Bool #

(<=) :: NCard -> NCard -> Bool #

(>) :: NCard -> NCard -> Bool #

(>=) :: NCard -> NCard -> Bool #

max :: NCard -> NCard -> NCard #

min :: NCard -> NCard -> NCard #

Read NCard Source # 
Show NCard Source # 

Methods

showsPrec :: Int -> NCard -> ShowS #

show :: NCard -> String #

showList :: [NCard] -> ShowS #

Generic NCard Source # 

Associated Types

type Rep NCard :: * -> * #

Methods

from :: NCard -> Rep NCard x #

to :: Rep NCard x -> NCard #

Spannable NCard Source # 

Methods

getSpan :: NCard -> Span Source #

Print NCard Source # 

Methods

prt :: Int -> NCard -> Doc Source #

prtList :: Int -> [NCard] -> Doc Source #

type Rep NCard Source # 

data ExInteger Source #

Instances

Eq ExInteger Source # 
Data ExInteger Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExInteger -> c ExInteger #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExInteger #

toConstr :: ExInteger -> Constr #

dataTypeOf :: ExInteger -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExInteger) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExInteger) #

gmapT :: (forall b. Data b => b -> b) -> ExInteger -> ExInteger #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExInteger -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExInteger -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExInteger -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExInteger -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExInteger -> m ExInteger #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExInteger -> m ExInteger #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExInteger -> m ExInteger #

Ord ExInteger Source # 
Read ExInteger Source # 
Show ExInteger Source # 
Generic ExInteger Source # 

Associated Types

type Rep ExInteger :: * -> * #

Spannable ExInteger Source # 
Print ExInteger Source # 

Methods

prt :: Int -> ExInteger -> Doc Source #

prtList :: Int -> [ExInteger] -> Doc Source #

type Rep ExInteger Source # 

data Name Source #

Constructors

Path Span [ModId] 

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Data Name Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Read Name Source # 
Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Spannable Name Source # 

Methods

getSpan :: Name -> Span Source #

Print Name Source # 

Methods

prt :: Int -> Name -> Doc Source #

prtList :: Int -> [Name] -> Doc Source #

type Rep Name Source # 
type Rep Name = D1 (MetaData "Name" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "Path" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModId]))))

data Exp Source #

Instances

Eq Exp Source # 

Methods

(==) :: Exp -> Exp -> Bool #

(/=) :: Exp -> Exp -> Bool #

Data Exp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp #

toConstr :: Exp -> Constr #

dataTypeOf :: Exp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Exp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) #

gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r #

gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp #

Ord Exp Source # 

Methods

compare :: Exp -> Exp -> Ordering #

(<) :: Exp -> Exp -> Bool #

(<=) :: Exp -> Exp -> Bool #

(>) :: Exp -> Exp -> Bool #

(>=) :: Exp -> Exp -> Bool #

max :: Exp -> Exp -> Exp #

min :: Exp -> Exp -> Exp #

Read Exp Source # 
Show Exp Source # 

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Generic Exp Source # 

Associated Types

type Rep Exp :: * -> * #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Spannable Exp Source # 

Methods

getSpan :: Exp -> Span Source #

Print Exp Source # 

Methods

prt :: Int -> Exp -> Doc Source #

prtList :: Int -> [Exp] -> Doc Source #

type Rep Exp Source # 
type Rep Exp = D1 (MetaData "Exp" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EDeclAllDisj" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decl)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EDeclAll" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decl)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))) ((:+:) (C1 (MetaCons "EDeclQuantDisj" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quant))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decl)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EDeclQuant" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quant))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decl)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EImpliesElse" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))))) ((:+:) ((:+:) (C1 (MetaCons "EIff" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EImplies" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EOr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))) ((:+:) (C1 (MetaCons "EXor" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EAnd" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "ENeg" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ELt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EGt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))) ((:+:) (C1 (MetaCons "EEq" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "ELte" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EGte" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))))) ((:+:) ((:+:) (C1 (MetaCons "ENeq" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EIn" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "ENin" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))) ((:+:) (C1 (MetaCons "EQuantExp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quant)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EAdd" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "ESub" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EMul" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EDiv" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))) ((:+:) (C1 (MetaCons "ERem" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EGMax" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "EGMin" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))) ((:+:) ((:+:) (C1 (MetaCons "ESum" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) ((:+:) (C1 (MetaCons "EProd" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "ECard" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))) ((:+:) (C1 (MetaCons "EMinExp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) ((:+:) (C1 (MetaCons "EDomain" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "ERange" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EUnion" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EUnionCom" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))) ((:+:) (C1 (MetaCons "EDifference" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "EIntersection" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "EIntersectionDeprecated" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))))) ((:+:) ((:+:) (C1 (MetaCons "EJoin" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "ClaferId" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))) (C1 (MetaCons "EInt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosInteger)))))) ((:+:) (C1 (MetaCons "EDouble" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosDouble)))) ((:+:) (C1 (MetaCons "EReal" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosReal)))) (C1 (MetaCons "EStr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosString))))))))))

data Decl Source #

Constructors

Decl Span [LocId] Exp 

Instances

Eq Decl Source # 

Methods

(==) :: Decl -> Decl -> Bool #

(/=) :: Decl -> Decl -> Bool #

Data Decl Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Decl -> c Decl #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Decl #

toConstr :: Decl -> Constr #

dataTypeOf :: Decl -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Decl) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Decl) #

gmapT :: (forall b. Data b => b -> b) -> Decl -> Decl #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r #

gmapQ :: (forall d. Data d => d -> u) -> Decl -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Decl -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Decl -> m Decl #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl #

Ord Decl Source # 

Methods

compare :: Decl -> Decl -> Ordering #

(<) :: Decl -> Decl -> Bool #

(<=) :: Decl -> Decl -> Bool #

(>) :: Decl -> Decl -> Bool #

(>=) :: Decl -> Decl -> Bool #

max :: Decl -> Decl -> Decl #

min :: Decl -> Decl -> Decl #

Read Decl Source # 
Show Decl Source # 

Methods

showsPrec :: Int -> Decl -> ShowS #

show :: Decl -> String #

showList :: [Decl] -> ShowS #

Generic Decl Source # 

Associated Types

type Rep Decl :: * -> * #

Methods

from :: Decl -> Rep Decl x #

to :: Rep Decl x -> Decl #

Spannable Decl Source # 

Methods

getSpan :: Decl -> Span Source #

Print Decl Source # 

Methods

prt :: Int -> Decl -> Doc Source #

prtList :: Int -> [Decl] -> Doc Source #

type Rep Decl Source # 

data Quant Source #

Instances

Eq Quant Source # 

Methods

(==) :: Quant -> Quant -> Bool #

(/=) :: Quant -> Quant -> Bool #

Data Quant Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quant -> c Quant #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Quant #

toConstr :: Quant -> Constr #

dataTypeOf :: Quant -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Quant) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quant) #

gmapT :: (forall b. Data b => b -> b) -> Quant -> Quant #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quant -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quant -> r #

gmapQ :: (forall d. Data d => d -> u) -> Quant -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quant -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quant -> m Quant #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quant -> m Quant #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quant -> m Quant #

Ord Quant Source # 

Methods

compare :: Quant -> Quant -> Ordering #

(<) :: Quant -> Quant -> Bool #

(<=) :: Quant -> Quant -> Bool #

(>) :: Quant -> Quant -> Bool #

(>=) :: Quant -> Quant -> Bool #

max :: Quant -> Quant -> Quant #

min :: Quant -> Quant -> Quant #

Read Quant Source # 
Show Quant Source # 

Methods

showsPrec :: Int -> Quant -> ShowS #

show :: Quant -> String #

showList :: [Quant] -> ShowS #

Generic Quant Source # 

Associated Types

type Rep Quant :: * -> * #

Methods

from :: Quant -> Rep Quant x #

to :: Rep Quant x -> Quant #

Spannable Quant Source # 

Methods

getSpan :: Quant -> Span Source #

Print Quant Source # 

Methods

prt :: Int -> Quant -> Doc Source #

prtList :: Int -> [Quant] -> Doc Source #

type Rep Quant Source # 

data EnumId Source #

Constructors

EnumIdIdent Span PosIdent 

Instances

Eq EnumId Source # 

Methods

(==) :: EnumId -> EnumId -> Bool #

(/=) :: EnumId -> EnumId -> Bool #

Data EnumId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumId -> c EnumId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumId #

toConstr :: EnumId -> Constr #

dataTypeOf :: EnumId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EnumId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumId) #

gmapT :: (forall b. Data b => b -> b) -> EnumId -> EnumId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumId -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumId -> m EnumId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumId -> m EnumId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumId -> m EnumId #

Ord EnumId Source # 
Read EnumId Source # 
Show EnumId Source # 
Generic EnumId Source # 

Associated Types

type Rep EnumId :: * -> * #

Methods

from :: EnumId -> Rep EnumId x #

to :: Rep EnumId x -> EnumId #

Spannable EnumId Source # 

Methods

getSpan :: EnumId -> Span Source #

Print EnumId Source # 

Methods

prt :: Int -> EnumId -> Doc Source #

prtList :: Int -> [EnumId] -> Doc Source #

type Rep EnumId Source # 
type Rep EnumId = D1 (MetaData "EnumId" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "EnumIdIdent" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosIdent))))

data ModId Source #

Constructors

ModIdIdent Span PosIdent 

Instances

Eq ModId Source # 

Methods

(==) :: ModId -> ModId -> Bool #

(/=) :: ModId -> ModId -> Bool #

Data ModId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModId -> c ModId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModId #

toConstr :: ModId -> Constr #

dataTypeOf :: ModId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModId) #

gmapT :: (forall b. Data b => b -> b) -> ModId -> ModId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModId -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModId -> m ModId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModId -> m ModId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModId -> m ModId #

Ord ModId Source # 

Methods

compare :: ModId -> ModId -> Ordering #

(<) :: ModId -> ModId -> Bool #

(<=) :: ModId -> ModId -> Bool #

(>) :: ModId -> ModId -> Bool #

(>=) :: ModId -> ModId -> Bool #

max :: ModId -> ModId -> ModId #

min :: ModId -> ModId -> ModId #

Read ModId Source # 
Show ModId Source # 

Methods

showsPrec :: Int -> ModId -> ShowS #

show :: ModId -> String #

showList :: [ModId] -> ShowS #

Generic ModId Source # 

Associated Types

type Rep ModId :: * -> * #

Methods

from :: ModId -> Rep ModId x #

to :: Rep ModId x -> ModId #

Spannable ModId Source # 

Methods

getSpan :: ModId -> Span Source #

Print ModId Source # 

Methods

prt :: Int -> ModId -> Doc Source #

prtList :: Int -> [ModId] -> Doc Source #

type Rep ModId Source # 
type Rep ModId = D1 (MetaData "ModId" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "ModIdIdent" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosIdent))))

data LocId Source #

Constructors

LocIdIdent Span PosIdent 

Instances

Eq LocId Source # 

Methods

(==) :: LocId -> LocId -> Bool #

(/=) :: LocId -> LocId -> Bool #

Data LocId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocId -> c LocId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocId #

toConstr :: LocId -> Constr #

dataTypeOf :: LocId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocId) #

gmapT :: (forall b. Data b => b -> b) -> LocId -> LocId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocId -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocId -> m LocId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocId -> m LocId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocId -> m LocId #

Ord LocId Source # 

Methods

compare :: LocId -> LocId -> Ordering #

(<) :: LocId -> LocId -> Bool #

(<=) :: LocId -> LocId -> Bool #

(>) :: LocId -> LocId -> Bool #

(>=) :: LocId -> LocId -> Bool #

max :: LocId -> LocId -> LocId #

min :: LocId -> LocId -> LocId #

Read LocId Source # 
Show LocId Source # 

Methods

showsPrec :: Int -> LocId -> ShowS #

show :: LocId -> String #

showList :: [LocId] -> ShowS #

Generic LocId Source # 

Associated Types

type Rep LocId :: * -> * #

Methods

from :: LocId -> Rep LocId x #

to :: Rep LocId x -> LocId #

Spannable LocId Source # 

Methods

getSpan :: LocId -> Span Source #

Print LocId Source # 

Methods

prt :: Int -> LocId -> Doc Source #

prtList :: Int -> [LocId] -> Doc Source #

type Rep LocId Source # 
type Rep LocId = D1 (MetaData "LocId" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "LocIdIdent" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PosIdent))))