Hets - the Heterogeneous Tool Set
Copyright(c) Klaus Luettich Christian Maeder and Uni Bremen 2002-2006
LicenseGPLv2 or higher, see LICENSE.txt
MaintainerChristian.Maeder@dfki.de
Stabilityprovisional
Portabilityportable
Safe HaskellSafe

Common.AS_Annotation

Description

Datastructures for annotations of (Het)CASL. There is also a paramterized data type for an Annoted item. See also chapter II.5 of the CASL Reference Manual.

Synopsis

Documentation

data Annote_word Source #

start of an annote with its WORD or a comment

Constructors

Annote_word String 
Comment_start 

Instances

Instances details
Eq Annote_word Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: Annote_word -> Annote_word -> Bool

(/=) :: Annote_word -> Annote_word -> Bool

Data Annote_word Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: Annote_word -> Constr

dataTypeOf :: Annote_word -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annote_word)

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

gmapT :: (forall b. Data b => b -> b) -> Annote_word -> Annote_word

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

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

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

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

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

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

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

Ord Annote_word Source # 
Instance details

Defined in Common.AS_Annotation

Show Annote_word Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Annote_word -> ShowS

show :: Annote_word -> String

showList :: [Annote_word] -> ShowS

Generic Annote_word 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep Annote_word :: Type -> Type

Methods

from :: Annote_word -> Rep Annote_word x

to :: Rep Annote_word x -> Annote_word

GetRange Annote_word Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON Annote_word 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser Annote_word

parseJSONList :: Value -> Parser [Annote_word]

ToJSON Annote_word 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Annote_word -> Value

toEncoding :: Annote_word -> Encoding

toJSONList :: [Annote_word] -> Value

toEncodingList :: [Annote_word] -> Encoding

ShATermConvertible Annote_word 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Annote_word -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Annote_word] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Annote_word)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Annote_word])

type Rep Annote_word 
Instance details

Defined in ATC.AS_Annotation

type Rep Annote_word = D1 ('MetaData "Annote_word" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "Annote_word" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Comment_start" 'PrefixI 'False) (U1 :: Type -> Type))

data Annote_text Source #

line or group for Unparsed_anno

Constructors

Line_anno String 
Group_anno [String] 

Instances

Instances details
Eq Annote_text Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: Annote_text -> Annote_text -> Bool

(/=) :: Annote_text -> Annote_text -> Bool

Data Annote_text Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: Annote_text -> Constr

dataTypeOf :: Annote_text -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annote_text)

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

gmapT :: (forall b. Data b => b -> b) -> Annote_text -> Annote_text

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

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

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

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

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

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

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

Ord Annote_text Source # 
Instance details

Defined in Common.AS_Annotation

Show Annote_text Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Annote_text -> ShowS

show :: Annote_text -> String

showList :: [Annote_text] -> ShowS

Generic Annote_text 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep Annote_text :: Type -> Type

Methods

from :: Annote_text -> Rep Annote_text x

to :: Rep Annote_text x -> Annote_text

GetRange Annote_text Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON Annote_text 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser Annote_text

parseJSONList :: Value -> Parser [Annote_text]

ToJSON Annote_text 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Annote_text -> Value

toEncoding :: Annote_text -> Encoding

toJSONList :: [Annote_text] -> Value

toEncodingList :: [Annote_text] -> Encoding

ShATermConvertible Annote_text 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Annote_text -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Annote_text] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Annote_text)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Annote_text])

type Rep Annote_text 
Instance details

Defined in ATC.AS_Annotation

type Rep Annote_text = D1 ('MetaData "Annote_text" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "Line_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Group_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))

data Display_format Source #

formats to be displayed (may be extended in the future). Drop 3 from the show result to get the string for parsing and printing

Constructors

DF_HTML 
DF_LATEX 
DF_RTF 

Instances

Instances details
Eq Display_format Source # 
Instance details

Defined in Common.AS_Annotation

Data Display_format Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: Display_format -> Constr

dataTypeOf :: Display_format -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Display_format)

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

gmapT :: (forall b. Data b => b -> b) -> Display_format -> Display_format

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

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

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

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

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

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

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

Ord Display_format Source # 
Instance details

Defined in Common.AS_Annotation

Show Display_format Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Display_format -> ShowS

show :: Display_format -> String

showList :: [Display_format] -> ShowS

Generic Display_format 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep Display_format :: Type -> Type

GetRange Display_format Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON Display_format 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser Display_format

parseJSONList :: Value -> Parser [Display_format]

ToJSON Display_format 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Display_format -> Value

toEncoding :: Display_format -> Encoding

toJSONList :: [Display_format] -> Value

toEncodingList :: [Display_format] -> Encoding

ShATermConvertible Display_format 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Display_format -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Display_format] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Display_format)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Display_format])

type Rep Display_format 
Instance details

Defined in ATC.AS_Annotation

type Rep Display_format = D1 ('MetaData "Display_format" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "DF_HTML" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DF_LATEX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DF_RTF" 'PrefixI 'False) (U1 :: Type -> Type)))

swapTable :: [(a, b)] -> [(b, a)] Source #

swap the entries of a lookup table

toTable :: Show a => [a] -> [(a, String)] Source #

drop the first 3 characters from the show result

display_format_table :: [(Display_format, String)] Source #

a lookup table for the textual representation of display formats

lookupDisplayFormat :: Display_format -> String Source #

lookup the textual representation of a display format in display_format_table

data PrecRel Source #

precedence Lower means less and BothDirections means less and greater. Higher means greater but this is syntactically not allowed in Prec_anno. NoDirection can also not be specified explicitly, but covers those ids that are not mentionend in precedences.

Instances

Instances details
Eq PrecRel Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: PrecRel -> PrecRel -> Bool

(/=) :: PrecRel -> PrecRel -> Bool

Data PrecRel Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: PrecRel -> Constr

dataTypeOf :: PrecRel -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrecRel)

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

gmapT :: (forall b. Data b => b -> b) -> PrecRel -> PrecRel

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

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

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

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

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

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

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

Ord PrecRel Source # 
Instance details

Defined in Common.AS_Annotation

Methods

compare :: PrecRel -> PrecRel -> Ordering

(<) :: PrecRel -> PrecRel -> Bool

(<=) :: PrecRel -> PrecRel -> Bool

(>) :: PrecRel -> PrecRel -> Bool

(>=) :: PrecRel -> PrecRel -> Bool

max :: PrecRel -> PrecRel -> PrecRel

min :: PrecRel -> PrecRel -> PrecRel

Show PrecRel Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> PrecRel -> ShowS

show :: PrecRel -> String

showList :: [PrecRel] -> ShowS

Generic PrecRel 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep PrecRel :: Type -> Type

Methods

from :: PrecRel -> Rep PrecRel x

to :: Rep PrecRel x -> PrecRel

GetRange PrecRel Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON PrecRel 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser PrecRel

parseJSONList :: Value -> Parser [PrecRel]

ToJSON PrecRel 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: PrecRel -> Value

toEncoding :: PrecRel -> Encoding

toJSONList :: [PrecRel] -> Value

toEncodingList :: [PrecRel] -> Encoding

ShATermConvertible PrecRel 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> PrecRel -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [PrecRel] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, PrecRel)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [PrecRel])

type Rep PrecRel 
Instance details

Defined in ATC.AS_Annotation

type Rep PrecRel = D1 ('MetaData "PrecRel" "Common.AS_Annotation" "main" 'False) ((C1 ('MetaCons "Higher" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lower" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BothDirections" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoDirection" 'PrefixI 'False) (U1 :: Type -> Type)))

data AssocEither Source #

either left or right associative

Constructors

ALeft 
ARight 

Instances

Instances details
Eq AssocEither Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: AssocEither -> AssocEither -> Bool

(/=) :: AssocEither -> AssocEither -> Bool

Data AssocEither Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: AssocEither -> Constr

dataTypeOf :: AssocEither -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AssocEither)

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

gmapT :: (forall b. Data b => b -> b) -> AssocEither -> AssocEither

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

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

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

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

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

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

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

Ord AssocEither Source # 
Instance details

Defined in Common.AS_Annotation

Show AssocEither Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> AssocEither -> ShowS

show :: AssocEither -> String

showList :: [AssocEither] -> ShowS

Generic AssocEither 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep AssocEither :: Type -> Type

Methods

from :: AssocEither -> Rep AssocEither x

to :: Rep AssocEither x -> AssocEither

GetRange AssocEither Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON AssocEither 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser AssocEither

parseJSONList :: Value -> Parser [AssocEither]

ToJSON AssocEither 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: AssocEither -> Value

toEncoding :: AssocEither -> Encoding

toJSONList :: [AssocEither] -> Value

toEncodingList :: [AssocEither] -> Encoding

ShATermConvertible AssocEither 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> AssocEither -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [AssocEither] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, AssocEither)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [AssocEither])

type Rep AssocEither 
Instance details

Defined in ATC.AS_Annotation

type Rep AssocEither = D1 ('MetaData "AssocEither" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "ALeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARight" 'PrefixI 'False) (U1 :: Type -> Type))

data Semantic_anno Source #

semantic (line) annotations without further information. Use the same drop-3-trick as for the Display_format.

Instances

Instances details
Bounded Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

Enum Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

Eq Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

Data Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: Semantic_anno -> Constr

dataTypeOf :: Semantic_anno -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Semantic_anno)

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

gmapT :: (forall b. Data b => b -> b) -> Semantic_anno -> Semantic_anno

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

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

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

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

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

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

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

Ord Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

Show Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Semantic_anno -> ShowS

show :: Semantic_anno -> String

showList :: [Semantic_anno] -> ShowS

Generic Semantic_anno 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep Semantic_anno :: Type -> Type

GetRange Semantic_anno Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON Semantic_anno 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser Semantic_anno

parseJSONList :: Value -> Parser [Semantic_anno]

ToJSON Semantic_anno 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Semantic_anno -> Value

toEncoding :: Semantic_anno -> Encoding

toJSONList :: [Semantic_anno] -> Value

toEncodingList :: [Semantic_anno] -> Encoding

ShATermConvertible Semantic_anno 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Semantic_anno -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Semantic_anno] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Semantic_anno)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Semantic_anno])

type Rep Semantic_anno 
Instance details

Defined in ATC.AS_Annotation

type Rep Semantic_anno = D1 ('MetaData "Semantic_anno" "Common.AS_Annotation" "main" 'False) (((C1 ('MetaCons "SA_cons" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SA_def" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SA_implies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SA_mono" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SA_implied" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SA_mcons" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SA_ccons" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SA_wdef" 'PrefixI 'False) (U1 :: Type -> Type))))

semantic_anno_table :: [(Semantic_anno, String)] Source #

a lookup table for the textual representation of semantic annos

lookupSemanticAnno :: Semantic_anno -> String Source #

lookup the textual representation of a semantic anno in semantic_anno_table

data Annotation Source #

all possible annotations (without comment-outs)

Instances

Instances details
Eq Annotation Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: Annotation -> Annotation -> Bool

(/=) :: Annotation -> Annotation -> Bool

Data Annotation Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: Annotation -> Constr

dataTypeOf :: Annotation -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation)

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

gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation

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

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

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

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

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

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

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

Ord Annotation Source # 
Instance details

Defined in Common.AS_Annotation

Show Annotation Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Annotation -> ShowS

show :: Annotation -> String

showList :: [Annotation] -> ShowS

Generic Annotation 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep Annotation :: Type -> Type

Methods

from :: Annotation -> Rep Annotation x

to :: Rep Annotation x -> Annotation

GetRange Annotation Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON Annotation 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser Annotation

parseJSONList :: Value -> Parser [Annotation]

ToJSON Annotation 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Annotation -> Value

toEncoding :: Annotation -> Encoding

toJSONList :: [Annotation] -> Value

toEncodingList :: [Annotation] -> Encoding

ShATermConvertible Annotation 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Annotation -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Annotation] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Annotation)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Annotation])

Pretty Annotation Source # 
Instance details

Defined in Common.DocUtils

ATermConvertibleSML Annotation Source # 
Instance details

Defined in ATC.Sml_cats

Methods

from_sml_ShATerm :: ATermTable -> Annotation

from_sml_ShATermList :: ATermTable -> [Annotation]

type Rep Annotation 
Instance details

Defined in ATC.AS_Annotation

type Rep Annotation = D1 ('MetaData "Annotation" "Common.AS_Annotation" "main" 'False) (((C1 ('MetaCons "Unparsed_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Annote_word) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Annote_text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: C1 ('MetaCons "Display_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Display_format, String)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)))) :+: (C1 ('MetaCons "List_anno" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: (C1 ('MetaCons "Number_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "Float_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)))))) :+: ((C1 ('MetaCons "String_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: (C1 ('MetaCons "Prec_anno" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrecRel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Id])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Id]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: C1 ('MetaCons "Assoc_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssocEither) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Id]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))) :+: (C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: (C1 ('MetaCons "Prefix_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, IRI)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "Semantic_anno" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Semantic_anno) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))))

isLabel :: Annotation -> Bool Source #

isLabel tests if the given Annotation is a label (a Label typically follows a formula)

isSemanticAnno :: Annotation -> Bool Source #

isSemanticAnno tests if the given Annotation is a semantic one

isComment :: Annotation -> Bool Source #

isComment tests if the given Annotation is a comment line or a comment group

isAnnote :: Annotation -> Bool Source #

isAnnote is the negation of isComment

partPrefixes :: [Annotation] -> (Map String IRI, [Annotation]) Source #

separate prefix annotations and put them into a map

data Annoted a Source #

an item wrapped in preceding (left l_annos) and following (right r_annos) annotations. opt_pos should carry the position of an optional semicolon following a formula (but is currently unused).

Constructors

Annoted 

Fields

Instances

Instances details
Functor Annoted Source # 
Instance details

Defined in Common.AS_Annotation

Methods

fmap :: (a -> b) -> Annoted a -> Annoted b

(<$) :: a -> Annoted b -> Annoted a

Eq a => Eq (Annoted a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: Annoted a -> Annoted a -> Bool

(/=) :: Annoted a -> Annoted a -> Bool

Data a => Data (Annoted a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annoted a -> c (Annoted a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Annoted a)

toConstr :: Annoted a -> Constr

dataTypeOf :: Annoted a -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Annoted a))

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Annoted a))

gmapT :: (forall b. Data b => b -> b) -> Annoted a -> Annoted a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annoted a -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annoted a -> r

gmapQ :: (forall d. Data d => d -> u) -> Annoted a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annoted a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)

Ord a => Ord (Annoted a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

compare :: Annoted a -> Annoted a -> Ordering

(<) :: Annoted a -> Annoted a -> Bool

(<=) :: Annoted a -> Annoted a -> Bool

(>) :: Annoted a -> Annoted a -> Bool

(>=) :: Annoted a -> Annoted a -> Bool

max :: Annoted a -> Annoted a -> Annoted a

min :: Annoted a -> Annoted a -> Annoted a

Show a => Show (Annoted a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Annoted a -> ShowS

show :: Annoted a -> String

showList :: [Annoted a] -> ShowS

Generic (Annoted a) 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep (Annoted a) :: Type -> Type

Methods

from :: Annoted a -> Rep (Annoted a) x

to :: Rep (Annoted a) x -> Annoted a

GetRange a => GetRange (Annoted a) Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON a => FromJSON (Annoted a) 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser (Annoted a)

parseJSONList :: Value -> Parser [Annoted a]

ToJSON a => ToJSON (Annoted a) 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Annoted a -> Value

toEncoding :: Annoted a -> Encoding

toJSONList :: [Annoted a] -> Value

toEncodingList :: [Annoted a] -> Encoding

ShATermConvertible a => ShATermConvertible (Annoted a) 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Annoted a -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Annoted a] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Annoted a)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Annoted a])

Pretty a => Pretty (Annoted a) Source # 
Instance details

Defined in Common.DocUtils

Methods

pretty :: Annoted a -> Doc Source #

pretties :: [Annoted a] -> Doc Source #

ListCheck a => ListCheck (Annoted a) Source #

an instance of ListCheck for Annoted stuff

Instance details

Defined in CASL.ToDoc

Methods

innerList :: Annoted a -> [()] Source #

PrettyLG a => PrettyLG (Annoted a) Source # 
Instance details

Defined in Syntax.Print_AS_Structured

ShATermLG a => ShATermLG (Annoted a) Source # 
Instance details

Defined in ATC.Grothendieck

Methods

toShATermLG :: ATermTable -> Annoted a -> IO (ATermTable, Int) Source #

fromShATermLG :: LogicGraph -> Int -> ATermTable -> (ATermTable, Annoted a) Source #

ATermConvertibleSML a => ATermConvertibleSML (Annoted a) Source # 
Instance details

Defined in ATC.Sml_cats

Methods

from_sml_ShATerm :: ATermTable -> Annoted a

from_sml_ShATermList :: ATermTable -> [Annoted a]

type Rep (Annoted a) 
Instance details

Defined in ATC.AS_Annotation

type Rep (Annoted a) = D1 ('MetaData "Annoted" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "Annoted" 'PrefixI 'True) ((S1 ('MetaSel ('Just "item") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "opt_pos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :*: (S1 ('MetaSel ('Just "l_annos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Annotation]) :*: S1 ('MetaSel ('Just "r_annos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Annotation]))))

annoRange :: (a -> [Pos]) -> Annoted a -> [Pos] Source #

notImplied :: Annoted a -> Bool Source #

data SenOrigin Source #

origin of sentences

Constructors

SenOrigin 

Fields

Instances

Instances details
Eq SenOrigin Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: SenOrigin -> SenOrigin -> Bool

(/=) :: SenOrigin -> SenOrigin -> Bool

Data SenOrigin Source # 
Instance details

Defined in Common.AS_Annotation

Methods

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

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

toConstr :: SenOrigin -> Constr

dataTypeOf :: SenOrigin -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SenOrigin)

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

gmapT :: (forall b. Data b => b -> b) -> SenOrigin -> SenOrigin

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

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

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

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

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

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

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

Ord SenOrigin Source # 
Instance details

Defined in Common.AS_Annotation

Methods

compare :: SenOrigin -> SenOrigin -> Ordering

(<) :: SenOrigin -> SenOrigin -> Bool

(<=) :: SenOrigin -> SenOrigin -> Bool

(>) :: SenOrigin -> SenOrigin -> Bool

(>=) :: SenOrigin -> SenOrigin -> Bool

max :: SenOrigin -> SenOrigin -> SenOrigin

min :: SenOrigin -> SenOrigin -> SenOrigin

Show SenOrigin Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> SenOrigin -> ShowS

show :: SenOrigin -> String

showList :: [SenOrigin] -> ShowS

Generic SenOrigin 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep SenOrigin :: Type -> Type

Methods

from :: SenOrigin -> Rep SenOrigin x

to :: Rep SenOrigin x -> SenOrigin

GetRange SenOrigin Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON SenOrigin 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser SenOrigin

parseJSONList :: Value -> Parser [SenOrigin]

ToJSON SenOrigin 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: SenOrigin -> Value

toEncoding :: SenOrigin -> Encoding

toJSONList :: [SenOrigin] -> Value

toEncodingList :: [SenOrigin] -> Encoding

ShATermConvertible SenOrigin 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> SenOrigin -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [SenOrigin] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, SenOrigin)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [SenOrigin])

type Rep SenOrigin 
Instance details

Defined in ATC.AS_Annotation

type Rep SenOrigin = D1 ('MetaData "SenOrigin" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "SenOrigin" 'PrefixI 'True) (S1 ('MetaSel ('Just "dGraphName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI) :*: (S1 ('MetaSel ('Just "originNodeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Node) :*: S1 ('MetaSel ('Just "senName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

data SenAttr s a Source #

naming or labelling sentences

Constructors

SenAttr 

Fields

Instances

Instances details
(Eq a, Eq s) => Eq (SenAttr s a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

(==) :: SenAttr s a -> SenAttr s a -> Bool

(/=) :: SenAttr s a -> SenAttr s a -> Bool

(Data s, Data a) => Data (SenAttr s a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SenAttr s a)

toConstr :: SenAttr s a -> Constr

dataTypeOf :: SenAttr s a -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SenAttr s a))

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SenAttr s a))

gmapT :: (forall b. Data b => b -> b) -> SenAttr s a -> SenAttr s a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r

gmapQ :: (forall d. Data d => d -> u) -> SenAttr s a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SenAttr s a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)

(Ord a, Ord s) => Ord (SenAttr s a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

compare :: SenAttr s a -> SenAttr s a -> Ordering

(<) :: SenAttr s a -> SenAttr s a -> Bool

(<=) :: SenAttr s a -> SenAttr s a -> Bool

(>) :: SenAttr s a -> SenAttr s a -> Bool

(>=) :: SenAttr s a -> SenAttr s a -> Bool

max :: SenAttr s a -> SenAttr s a -> SenAttr s a

min :: SenAttr s a -> SenAttr s a -> SenAttr s a

(Show a, Show s) => Show (SenAttr s a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> SenAttr s a -> ShowS

show :: SenAttr s a -> String

showList :: [SenAttr s a] -> ShowS

Generic (SenAttr s a) 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep (SenAttr s a) :: Type -> Type

Methods

from :: SenAttr s a -> Rep (SenAttr s a) x

to :: Rep (SenAttr s a) x -> SenAttr s a

(GetRange s, GetRange a) => GetRange (SenAttr s a) Source # 
Instance details

Defined in Common.AS_Annotation

Methods

getRange :: SenAttr s a -> Range Source #

rangeSpan :: SenAttr s a -> [Pos] Source #

(FromJSON s, FromJSON a) => FromJSON (SenAttr s a) 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser (SenAttr s a)

parseJSONList :: Value -> Parser [SenAttr s a]

(ToJSON s, ToJSON a) => ToJSON (SenAttr s a) 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: SenAttr s a -> Value

toEncoding :: SenAttr s a -> Encoding

toJSONList :: [SenAttr s a] -> Value

toEncodingList :: [SenAttr s a] -> Encoding

(ShATermConvertible s, ShATermConvertible a) => ShATermConvertible (SenAttr s a) 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> SenAttr s a -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [SenAttr s a] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, SenAttr s a)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [SenAttr s a])

(ShATermLG s, ShATermLG a) => ShATermLG (SenAttr s a) Source # 
Instance details

Defined in ATC.Grothendieck

Methods

toShATermLG :: ATermTable -> SenAttr s a -> IO (ATermTable, Int) Source #

fromShATermLG :: LogicGraph -> Int -> ATermTable -> (ATermTable, SenAttr s a) Source #

type Rep (SenAttr s a) 
Instance details

Defined in ATC.AS_Annotation

type Rep (SenAttr s a) = D1 ('MetaData "SenAttr" "Common.AS_Annotation" "main" 'False) (C1 ('MetaCons "SenAttr" 'PrefixI 'True) (((S1 ('MetaSel ('Just "senAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "priority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "isAxiom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "isDef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "wasTheorem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "simpAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "attrOrigin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Id))) :*: (S1 ('MetaSel ('Just "senMark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "senOrigin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SenOrigin)) :*: S1 ('MetaSel ('Just "sentence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s))))))

makeNamed :: a -> s -> SenAttr s a Source #

equip a sentence with a name

setOrigin :: IRI -> Node -> String -> SenAttr s a -> SenAttr s a Source #

set the origin of a named sentence

setOriginIfLocal :: IRI -> Node -> String -> SenAttr s a -> SenAttr s a Source #

set the origin of a named sentence, if the sentence does not already have an origin, owise leave unchanged

type Named s = SenAttr s String Source #

markSen :: String -> Named s -> Named s Source #

reName :: (a -> b) -> SenAttr s a -> SenAttr s b Source #

mapNamed :: (s -> t) -> SenAttr s a -> SenAttr t a Source #

extending sentence maps to maps on labelled sentences

mapNamedM :: Monad m => (s -> m t) -> Named s -> m (Named t) Source #

extending sentence maybe-maps to maps on labelled sentences

mapAnM :: Monad m => (a -> m b) -> [Annoted a] -> m [Annoted b] Source #

process all items and wrap matching annotations around the results

replaceAnnoted :: b -> Annoted a -> Annoted b Source #

replace the item

appendAnno :: Annoted a -> [Annotation] -> Annoted a Source #

add further following annotations

addLeftAnno :: [Annotation] -> a -> Annoted a Source #

put together preceding annotations and an item

emptyAnno :: a -> Annoted a Source #

decorate with no annotations

getRLabel :: Annoted a -> String Source #

get the label following (or to the right of) an item

identAnno :: String -> Annotation -> Bool Source #

check for an annotation starting with % and the input str (does not work for known annotation words)

hasIdentAnno :: String -> Annoted a -> Bool Source #

test all anntotions for an item

getPriority :: [Annotation] -> Maybe String Source #

newtype Name Source #

Constructors

Name String 

Instances

Instances details
Show Name Source # 
Instance details

Defined in Common.AS_Annotation

Methods

showsPrec :: Int -> Name -> ShowS

show :: Name -> String

showList :: [Name] -> ShowS

Generic Name 
Instance details

Defined in ATC.AS_Annotation

Associated Types

type Rep Name :: Type -> Type

Methods

from :: Name -> Rep Name x

to :: Rep Name x -> Name

GetRange Name Source # 
Instance details

Defined in Common.AS_Annotation

FromJSON Name 
Instance details

Defined in ATC.AS_Annotation

Methods

parseJSON :: Value -> Parser Name

parseJSONList :: Value -> Parser [Name]

ToJSON Name 
Instance details

Defined in ATC.AS_Annotation

Methods

toJSON :: Name -> Value

toEncoding :: Name -> Encoding

toJSONList :: [Name] -> Value

toEncodingList :: [Name] -> Encoding

ShATermConvertible Name 
Instance details

Defined in ATC.AS_Annotation

Methods

toShATermAux :: ATermTable -> Name -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Name] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Name)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Name])

type Rep Name 
Instance details

Defined in ATC.AS_Annotation

type Rep Name = D1 ('MetaData "Name" "Common.AS_Annotation" "main" 'True) (C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))