Copyright | (c) Klaus Luettich Christian Maeder and Uni Bremen 2002-2006 |
---|---|
License | GPLv2 or higher, see LICENSE.txt |
Maintainer | Christian.Maeder@dfki.de |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Synopsis
- data Annote_word
- = Annote_word String
- | Comment_start
- data Annote_text
- = Line_anno String
- | Group_anno [String]
- data Display_format
- swapTable :: [(a, b)] -> [(b, a)]
- toTable :: Show a => [a] -> [(a, String)]
- display_format_table :: [(Display_format, String)]
- lookupDisplayFormat :: Display_format -> String
- data PrecRel
- data AssocEither
- data Semantic_anno
- = SA_cons
- | SA_def
- | SA_implies
- | SA_mono
- | SA_implied
- | SA_mcons
- | SA_ccons
- | SA_wdef
- semantic_anno_table :: [(Semantic_anno, String)]
- lookupSemanticAnno :: Semantic_anno -> String
- data Annotation
- = Unparsed_anno Annote_word Annote_text Range
- | Display_anno Id [(Display_format, String)] Range
- | List_anno Id Id Id Range
- | Number_anno Id Range
- | Float_anno Id Id Range
- | String_anno Id Id Range
- | Prec_anno PrecRel [Id] [Id] Range
- | Assoc_anno AssocEither [Id] Range
- | Label [String] Range
- | Prefix_anno [(String, IRI)] Range
- | Semantic_anno Semantic_anno Range
- isLabel :: Annotation -> Bool
- isImplies :: Annotation -> Bool
- isImplied :: Annotation -> Bool
- isSemanticAnno :: Annotation -> Bool
- isComment :: Annotation -> Bool
- isAnnote :: Annotation -> Bool
- partPrefixes :: [Annotation] -> (Map String IRI, [Annotation])
- data Annoted a = Annoted {
- item :: a
- opt_pos :: Range
- l_annos :: [Annotation]
- r_annos :: [Annotation]
- annoRange :: (a -> [Pos]) -> Annoted a -> [Pos]
- notImplied :: Annoted a -> Bool
- data SenOrigin = SenOrigin {
- dGraphName :: IRI
- originNodeId :: Node
- senName :: String
- data SenAttr s a = SenAttr {}
- makeNamed :: a -> s -> SenAttr s a
- setOrigin :: IRI -> Node -> String -> SenAttr s a -> SenAttr s a
- setOriginIfLocal :: IRI -> Node -> String -> SenAttr s a -> SenAttr s a
- type Named s = SenAttr s String
- markSen :: String -> Named s -> Named s
- unmark :: Named s -> Named s
- reName :: (a -> b) -> SenAttr s a -> SenAttr s b
- mapNamed :: (s -> t) -> SenAttr s a -> SenAttr t a
- mapNamedM :: Monad m => (s -> m t) -> Named s -> m (Named t)
- mapAnM :: Monad m => (a -> m b) -> [Annoted a] -> m [Annoted b]
- replaceAnnoted :: b -> Annoted a -> Annoted b
- appendAnno :: Annoted a -> [Annotation] -> Annoted a
- addLeftAnno :: [Annotation] -> a -> Annoted a
- emptyAnno :: a -> Annoted a
- getRLabel :: Annoted a -> String
- identAnno :: String -> Annotation -> Bool
- hasIdentAnno :: String -> Annoted a -> Bool
- getPriority :: [Annotation] -> Maybe String
- makeNamedSen :: Annoted a -> Named a
- annoArg :: Annote_text -> String
- newtype Name = Name String
- getAnnoName :: Annoted a -> Name
Documentation
data Annote_word Source #
start of an annote with its WORD or a comment
Annote_word String | |
Comment_start |
Instances
Eq Annote_word Source # | |
Defined in Common.AS_Annotation (==) :: Annote_word -> Annote_word -> Bool (/=) :: Annote_word -> Annote_word -> Bool | |
Data Annote_word Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation compare :: Annote_word -> Annote_word -> Ordering (<) :: Annote_word -> Annote_word -> Bool (<=) :: Annote_word -> Annote_word -> Bool (>) :: Annote_word -> Annote_word -> Bool (>=) :: Annote_word -> Annote_word -> Bool max :: Annote_word -> Annote_word -> Annote_word min :: Annote_word -> Annote_word -> Annote_word | |
Show Annote_word Source # | |
Defined in Common.AS_Annotation showsPrec :: Int -> Annote_word -> ShowS show :: Annote_word -> String showList :: [Annote_word] -> ShowS | |
Generic Annote_word | |
Defined in ATC.AS_Annotation type Rep Annote_word :: Type -> Type from :: Annote_word -> Rep Annote_word x to :: Rep Annote_word x -> Annote_word | |
GetRange Annote_word Source # | |
Defined in Common.AS_Annotation getRange :: Annote_word -> Range Source # rangeSpan :: Annote_word -> [Pos] Source # | |
FromJSON Annote_word | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser Annote_word parseJSONList :: Value -> Parser [Annote_word] | |
ToJSON Annote_word | |
Defined in ATC.AS_Annotation toJSON :: Annote_word -> Value toEncoding :: Annote_word -> Encoding toJSONList :: [Annote_word] -> Value toEncodingList :: [Annote_word] -> Encoding | |
ShATermConvertible Annote_word | |
Defined in ATC.AS_Annotation 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 | |
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
Line_anno String | |
Group_anno [String] |
Instances
Eq Annote_text Source # | |
Defined in Common.AS_Annotation (==) :: Annote_text -> Annote_text -> Bool (/=) :: Annote_text -> Annote_text -> Bool | |
Data Annote_text Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation compare :: Annote_text -> Annote_text -> Ordering (<) :: Annote_text -> Annote_text -> Bool (<=) :: Annote_text -> Annote_text -> Bool (>) :: Annote_text -> Annote_text -> Bool (>=) :: Annote_text -> Annote_text -> Bool max :: Annote_text -> Annote_text -> Annote_text min :: Annote_text -> Annote_text -> Annote_text | |
Show Annote_text Source # | |
Defined in Common.AS_Annotation showsPrec :: Int -> Annote_text -> ShowS show :: Annote_text -> String showList :: [Annote_text] -> ShowS | |
Generic Annote_text | |
Defined in ATC.AS_Annotation type Rep Annote_text :: Type -> Type from :: Annote_text -> Rep Annote_text x to :: Rep Annote_text x -> Annote_text | |
GetRange Annote_text Source # | |
Defined in Common.AS_Annotation getRange :: Annote_text -> Range Source # rangeSpan :: Annote_text -> [Pos] Source # | |
FromJSON Annote_text | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser Annote_text parseJSONList :: Value -> Parser [Annote_text] | |
ToJSON Annote_text | |
Defined in ATC.AS_Annotation toJSON :: Annote_text -> Value toEncoding :: Annote_text -> Encoding toJSONList :: [Annote_text] -> Value toEncodingList :: [Annote_text] -> Encoding | |
ShATermConvertible Annote_text | |
Defined in ATC.AS_Annotation 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 | |
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
Instances
Eq Display_format Source # | |
Defined in Common.AS_Annotation (==) :: Display_format -> Display_format -> Bool (/=) :: Display_format -> Display_format -> Bool | |
Data Display_format Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation compare :: Display_format -> Display_format -> Ordering (<) :: Display_format -> Display_format -> Bool (<=) :: Display_format -> Display_format -> Bool (>) :: Display_format -> Display_format -> Bool (>=) :: Display_format -> Display_format -> Bool max :: Display_format -> Display_format -> Display_format min :: Display_format -> Display_format -> Display_format | |
Show Display_format Source # | |
Defined in Common.AS_Annotation showsPrec :: Int -> Display_format -> ShowS show :: Display_format -> String showList :: [Display_format] -> ShowS | |
Generic Display_format | |
Defined in ATC.AS_Annotation type Rep Display_format :: Type -> Type from :: Display_format -> Rep Display_format x to :: Rep Display_format x -> Display_format | |
GetRange Display_format Source # | |
Defined in Common.AS_Annotation getRange :: Display_format -> Range Source # rangeSpan :: Display_format -> [Pos] Source # | |
FromJSON Display_format | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser Display_format parseJSONList :: Value -> Parser [Display_format] | |
ToJSON Display_format | |
Defined in ATC.AS_Annotation toJSON :: Display_format -> Value toEncoding :: Display_format -> Encoding toJSONList :: [Display_format] -> Value toEncodingList :: [Display_format] -> Encoding | |
ShATermConvertible Display_format | |
Defined in ATC.AS_Annotation 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 | |
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))) |
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
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
Eq PrecRel Source # | |
Data PrecRel Source # | |
Defined in Common.AS_Annotation 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 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 # | |
Show PrecRel Source # | |
Generic PrecRel | |
GetRange PrecRel Source # | |
FromJSON PrecRel | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser PrecRel parseJSONList :: Value -> Parser [PrecRel] | |
ToJSON PrecRel | |
Defined in ATC.AS_Annotation toEncoding :: PrecRel -> Encoding toJSONList :: [PrecRel] -> Value toEncodingList :: [PrecRel] -> Encoding | |
ShATermConvertible PrecRel | |
Defined in ATC.AS_Annotation 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 | |
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
Instances
Eq AssocEither Source # | |
Defined in Common.AS_Annotation (==) :: AssocEither -> AssocEither -> Bool (/=) :: AssocEither -> AssocEither -> Bool | |
Data AssocEither Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation compare :: AssocEither -> AssocEither -> Ordering (<) :: AssocEither -> AssocEither -> Bool (<=) :: AssocEither -> AssocEither -> Bool (>) :: AssocEither -> AssocEither -> Bool (>=) :: AssocEither -> AssocEither -> Bool max :: AssocEither -> AssocEither -> AssocEither min :: AssocEither -> AssocEither -> AssocEither | |
Show AssocEither Source # | |
Defined in Common.AS_Annotation showsPrec :: Int -> AssocEither -> ShowS show :: AssocEither -> String showList :: [AssocEither] -> ShowS | |
Generic AssocEither | |
Defined in ATC.AS_Annotation type Rep AssocEither :: Type -> Type from :: AssocEither -> Rep AssocEither x to :: Rep AssocEither x -> AssocEither | |
GetRange AssocEither Source # | |
Defined in Common.AS_Annotation getRange :: AssocEither -> Range Source # rangeSpan :: AssocEither -> [Pos] Source # | |
FromJSON AssocEither | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser AssocEither parseJSONList :: Value -> Parser [AssocEither] | |
ToJSON AssocEither | |
Defined in ATC.AS_Annotation toJSON :: AssocEither -> Value toEncoding :: AssocEither -> Encoding toJSONList :: [AssocEither] -> Value toEncodingList :: [AssocEither] -> Encoding | |
ShATermConvertible AssocEither | |
Defined in ATC.AS_Annotation 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 | |
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
Bounded Semantic_anno Source # | |
Defined in Common.AS_Annotation | |
Enum Semantic_anno Source # | |
Defined in Common.AS_Annotation succ :: Semantic_anno -> Semantic_anno pred :: Semantic_anno -> Semantic_anno toEnum :: Int -> Semantic_anno fromEnum :: Semantic_anno -> Int enumFrom :: Semantic_anno -> [Semantic_anno] enumFromThen :: Semantic_anno -> Semantic_anno -> [Semantic_anno] enumFromTo :: Semantic_anno -> Semantic_anno -> [Semantic_anno] enumFromThenTo :: Semantic_anno -> Semantic_anno -> Semantic_anno -> [Semantic_anno] | |
Eq Semantic_anno Source # | |
Defined in Common.AS_Annotation (==) :: Semantic_anno -> Semantic_anno -> Bool (/=) :: Semantic_anno -> Semantic_anno -> Bool | |
Data Semantic_anno Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation compare :: Semantic_anno -> Semantic_anno -> Ordering (<) :: Semantic_anno -> Semantic_anno -> Bool (<=) :: Semantic_anno -> Semantic_anno -> Bool (>) :: Semantic_anno -> Semantic_anno -> Bool (>=) :: Semantic_anno -> Semantic_anno -> Bool max :: Semantic_anno -> Semantic_anno -> Semantic_anno min :: Semantic_anno -> Semantic_anno -> Semantic_anno | |
Show Semantic_anno Source # | |
Defined in Common.AS_Annotation showsPrec :: Int -> Semantic_anno -> ShowS show :: Semantic_anno -> String showList :: [Semantic_anno] -> ShowS | |
Generic Semantic_anno | |
Defined in ATC.AS_Annotation type Rep Semantic_anno :: Type -> Type from :: Semantic_anno -> Rep Semantic_anno x to :: Rep Semantic_anno x -> Semantic_anno | |
GetRange Semantic_anno Source # | |
Defined in Common.AS_Annotation getRange :: Semantic_anno -> Range Source # rangeSpan :: Semantic_anno -> [Pos] Source # | |
FromJSON Semantic_anno | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser Semantic_anno parseJSONList :: Value -> Parser [Semantic_anno] | |
ToJSON Semantic_anno | |
Defined in ATC.AS_Annotation toJSON :: Semantic_anno -> Value toEncoding :: Semantic_anno -> Encoding toJSONList :: [Semantic_anno] -> Value toEncodingList :: [Semantic_anno] -> Encoding | |
ShATermConvertible Semantic_anno | |
Defined in ATC.AS_Annotation 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 | |
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)
Unparsed_anno Annote_word Annote_text Range | constructor for comments or unparsed annotes |
Display_anno Id [(Display_format, String)] Range | known annotes |
List_anno Id Id Id Range | |
Number_anno Id Range | |
Float_anno Id Id Range | |
String_anno Id Id Range | |
Prec_anno PrecRel [Id] [Id] Range | |
Assoc_anno AssocEither [Id] Range | |
Label [String] Range | |
Prefix_anno [(String, IRI)] Range | |
Semantic_anno Semantic_anno Range |
Instances
Eq Annotation Source # | |
Defined in Common.AS_Annotation (==) :: Annotation -> Annotation -> Bool (/=) :: Annotation -> Annotation -> Bool | |
Data Annotation Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation compare :: Annotation -> Annotation -> Ordering (<) :: Annotation -> Annotation -> Bool (<=) :: Annotation -> Annotation -> Bool (>) :: Annotation -> Annotation -> Bool (>=) :: Annotation -> Annotation -> Bool max :: Annotation -> Annotation -> Annotation min :: Annotation -> Annotation -> Annotation | |
Show Annotation Source # | |
Defined in Common.AS_Annotation showsPrec :: Int -> Annotation -> ShowS show :: Annotation -> String showList :: [Annotation] -> ShowS | |
Generic Annotation | |
Defined in ATC.AS_Annotation type Rep Annotation :: Type -> Type from :: Annotation -> Rep Annotation x to :: Rep Annotation x -> Annotation | |
GetRange Annotation Source # | |
Defined in Common.AS_Annotation getRange :: Annotation -> Range Source # rangeSpan :: Annotation -> [Pos] Source # | |
FromJSON Annotation | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser Annotation parseJSONList :: Value -> Parser [Annotation] | |
ToJSON Annotation | |
Defined in ATC.AS_Annotation toJSON :: Annotation -> Value toEncoding :: Annotation -> Encoding toJSONList :: [Annotation] -> Value toEncodingList :: [Annotation] -> Encoding | |
ShATermConvertible Annotation | |
Defined in ATC.AS_Annotation 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 # | |
Defined in Common.DocUtils pretty :: Annotation -> Doc Source # pretties :: [Annotation] -> Doc Source # | |
ATermConvertibleSML Annotation Source # | |
Defined in ATC.Sml_cats from_sml_ShATerm :: ATermTable -> Annotation from_sml_ShATermList :: ATermTable -> [Annotation] | |
type Rep Annotation | |
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)
isImplies :: Annotation -> Bool Source #
isImplied :: Annotation -> Bool Source #
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
partPrefixes :: [Annotation] -> (Map String IRI, [Annotation]) Source #
separate prefix annotations and put them into a map
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).
Annoted | |
|
Instances
Functor Annoted Source # | |
Eq a => Eq (Annoted a) Source # | |
Data a => Data (Annoted a) Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation | |
Show a => Show (Annoted a) Source # | |
Generic (Annoted a) | |
GetRange a => GetRange (Annoted a) Source # | |
FromJSON a => FromJSON (Annoted a) | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser (Annoted a) parseJSONList :: Value -> Parser [Annoted a] | |
ToJSON a => ToJSON (Annoted a) | |
Defined in ATC.AS_Annotation toEncoding :: Annoted a -> Encoding toJSONList :: [Annoted a] -> Value toEncodingList :: [Annoted a] -> Encoding | |
ShATermConvertible a => ShATermConvertible (Annoted a) | |
Defined in ATC.AS_Annotation 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 # | |
ListCheck a => ListCheck (Annoted a) Source # | an instance of ListCheck for Annoted stuff |
Defined in CASL.ToDoc | |
PrettyLG a => PrettyLG (Annoted a) Source # | |
Defined in Syntax.Print_AS_Structured | |
ShATermLG a => ShATermLG (Annoted a) Source # | |
Defined in ATC.Grothendieck toShATermLG :: ATermTable -> Annoted a -> IO (ATermTable, Int) Source # fromShATermLG :: LogicGraph -> Int -> ATermTable -> (ATermTable, Annoted a) Source # | |
ATermConvertibleSML a => ATermConvertibleSML (Annoted a) Source # | |
Defined in ATC.Sml_cats from_sml_ShATerm :: ATermTable -> Annoted a from_sml_ShATermList :: ATermTable -> [Annoted a] | |
type Rep (Annoted a) | |
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])))) |
notImplied :: Annoted a -> Bool Source #
origin of sentences
SenOrigin | |
|
Instances
Eq SenOrigin Source # | |
Data SenOrigin Source # | |
Defined in Common.AS_Annotation 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 # | |
Defined in Common.AS_Annotation | |
Show SenOrigin Source # | |
Generic SenOrigin | |
GetRange SenOrigin Source # | |
FromJSON SenOrigin | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser SenOrigin parseJSONList :: Value -> Parser [SenOrigin] | |
ToJSON SenOrigin | |
Defined in ATC.AS_Annotation toEncoding :: SenOrigin -> Encoding toJSONList :: [SenOrigin] -> Value toEncodingList :: [SenOrigin] -> Encoding | |
ShATermConvertible SenOrigin | |
Defined in ATC.AS_Annotation 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 | |
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)))) |
naming or labelling sentences
Instances
(Eq a, Eq s) => Eq (SenAttr s a) Source # | |
(Data s, Data a) => Data (SenAttr s a) Source # | |
Defined in Common.AS_Annotation 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 # | |
(Show a, Show s) => Show (SenAttr s a) Source # | |
Generic (SenAttr s a) | |
(GetRange s, GetRange a) => GetRange (SenAttr s a) Source # | |
(FromJSON s, FromJSON a) => FromJSON (SenAttr s a) | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser (SenAttr s a) parseJSONList :: Value -> Parser [SenAttr s a] | |
(ToJSON s, ToJSON a) => ToJSON (SenAttr s a) | |
Defined in ATC.AS_Annotation 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) | |
Defined in ATC.AS_Annotation 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 # | |
Defined in ATC.Grothendieck toShATermLG :: ATermTable -> SenAttr s a -> IO (ATermTable, Int) Source # fromShATermLG :: LogicGraph -> Int -> ATermTable -> (ATermTable, SenAttr s a) Source # | |
type Rep (SenAttr s a) | |
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)))))) |
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
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
appendAnno :: Annoted a -> [Annotation] -> Annoted a Source #
add further following annotations
addLeftAnno :: [Annotation] -> a -> Annoted a Source #
put together preceding annotations and 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 #
makeNamedSen :: Annoted a -> Named a Source #
annoArg :: Annote_text -> String Source #
Name String |
Instances
Show Name Source # | |
Generic Name | |
GetRange Name Source # | |
FromJSON Name | |
Defined in ATC.AS_Annotation parseJSON :: Value -> Parser Name parseJSONList :: Value -> Parser [Name] | |
ToJSON Name | |
Defined in ATC.AS_Annotation | |
ShATermConvertible Name | |
Defined in ATC.AS_Annotation 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 | |
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))) |
getAnnoName :: Annoted a -> Name Source #