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
Stabilityexperimental
Portabilityportable
Safe HaskellSafe

Common.GlobalAnnotations

Description

Data structures for global annotations

Synopsis

Documentation

data GlobalAnnos Source #

all global annotations and a field for pretty printing stuff

Constructors

GA 

Fields

Instances

Instances details
Eq GlobalAnnos Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

(==) :: GlobalAnnos -> GlobalAnnos -> Bool

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

Data GlobalAnnos Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

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

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

toConstr :: GlobalAnnos -> Constr

dataTypeOf :: GlobalAnnos -> DataType

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

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

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

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

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

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

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

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

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

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

Show GlobalAnnos Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

showsPrec :: Int -> GlobalAnnos -> ShowS

show :: GlobalAnnos -> String

showList :: [GlobalAnnos] -> ShowS

Generic GlobalAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Associated Types

type Rep GlobalAnnos :: Type -> Type

Methods

from :: GlobalAnnos -> Rep GlobalAnnos x

to :: Rep GlobalAnnos x -> GlobalAnnos

FromJSON GlobalAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Methods

parseJSON :: Value -> Parser GlobalAnnos

parseJSONList :: Value -> Parser [GlobalAnnos]

ToJSON GlobalAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Methods

toJSON :: GlobalAnnos -> Value

toEncoding :: GlobalAnnos -> Encoding

toJSONList :: [GlobalAnnos] -> Value

toEncodingList :: [GlobalAnnos] -> Encoding

ShATermConvertible GlobalAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Methods

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

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

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

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

Pretty GlobalAnnos Source # 
Instance details

Defined in Common.ConvertGlobalAnnos

ShATermLG GlobalAnnos Source # 
Instance details

Defined in ATC.Grothendieck

Methods

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

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

type Rep GlobalAnnos 
Instance details

Defined in ATC.GlobalAnnotations

type Rep GlobalAnnos = D1 ('MetaData "GlobalAnnos" "Common.GlobalAnnotations" "main" 'False) (C1 ('MetaCons "GA" 'PrefixI 'True) ((S1 ('MetaSel ('Just "prec_annos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrecedenceGraph) :*: (S1 ('MetaSel ('Just "assoc_annos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssocMap) :*: S1 ('MetaSel ('Just "display_annos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisplayMap))) :*: (S1 ('MetaSel ('Just "literal_annos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LiteralAnnos) :*: (S1 ('MetaSel ('Just "literal_map") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LiteralMap) :*: S1 ('MetaSel ('Just "prefix_map") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixMap)))))

emptyGlobalAnnos :: GlobalAnnos Source #

empty (or initial) global annotations

data LiteralAnnos Source #

literal annotations for string, lists, number and floating

Constructors

LA 

Fields

Instances

Instances details
Eq LiteralAnnos Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

(==) :: LiteralAnnos -> LiteralAnnos -> Bool

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

Data LiteralAnnos Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

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

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

toConstr :: LiteralAnnos -> Constr

dataTypeOf :: LiteralAnnos -> DataType

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

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

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

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

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

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

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

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

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

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

Show LiteralAnnos Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

showsPrec :: Int -> LiteralAnnos -> ShowS

show :: LiteralAnnos -> String

showList :: [LiteralAnnos] -> ShowS

Generic LiteralAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Associated Types

type Rep LiteralAnnos :: Type -> Type

FromJSON LiteralAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Methods

parseJSON :: Value -> Parser LiteralAnnos

parseJSONList :: Value -> Parser [LiteralAnnos]

ToJSON LiteralAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Methods

toJSON :: LiteralAnnos -> Value

toEncoding :: LiteralAnnos -> Encoding

toJSONList :: [LiteralAnnos] -> Value

toEncodingList :: [LiteralAnnos] -> Encoding

ShATermConvertible LiteralAnnos 
Instance details

Defined in ATC.GlobalAnnotations

Methods

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

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

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

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

type Rep LiteralAnnos 
Instance details

Defined in ATC.GlobalAnnotations

type Rep LiteralAnnos = D1 ('MetaData "LiteralAnnos" "Common.GlobalAnnotations" "main" 'False) (C1 ('MetaCons "LA" 'PrefixI 'True) ((S1 ('MetaSel ('Just "string_lit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Id, Id))) :*: S1 ('MetaSel ('Just "list_lit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Id (Id, Id)))) :*: (S1 ('MetaSel ('Just "number_lit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Id)) :*: S1 ('MetaSel ('Just "float_lit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Id, Id))))))

emptyLiteralAnnos :: LiteralAnnos Source #

empty literal annotations

type DisplayMap = Map Id (Map Display_format [Token]) Source #

ids to be displayed according to a format

type LiteralMap = Map Id LiteralType Source #

a redundant map for LiteralAnnos

type PrefixMap = Map String IRI Source #

a map for expansion of abbreviated/simple IRI to full IRI

data LiteralType Source #

description of the type of a literal for a given Id in LiteralMap

Constructors

StringCons Id

refer to the Id of the null string

StringNull 
ListCons Id Id

brackets (as Id) and Id of matching empty list

ListNull Id

brackets (as Id) for the empty list

Number 
Fraction 
Floating 
NoLiteral

and error value for a getLiteralType

Instances

Instances details
Eq LiteralType Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

(==) :: LiteralType -> LiteralType -> Bool

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

Data LiteralType Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

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

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

toConstr :: LiteralType -> Constr

dataTypeOf :: LiteralType -> DataType

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

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

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

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

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

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

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

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

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

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

Show LiteralType Source # 
Instance details

Defined in Common.GlobalAnnotations

Methods

showsPrec :: Int -> LiteralType -> ShowS

show :: LiteralType -> String

showList :: [LiteralType] -> ShowS

Generic LiteralType 
Instance details

Defined in ATC.GlobalAnnotations

Associated Types

type Rep LiteralType :: Type -> Type

Methods

from :: LiteralType -> Rep LiteralType x

to :: Rep LiteralType x -> LiteralType

FromJSON LiteralType 
Instance details

Defined in ATC.GlobalAnnotations

Methods

parseJSON :: Value -> Parser LiteralType

parseJSONList :: Value -> Parser [LiteralType]

ToJSON LiteralType 
Instance details

Defined in ATC.GlobalAnnotations

Methods

toJSON :: LiteralType -> Value

toEncoding :: LiteralType -> Encoding

toJSONList :: [LiteralType] -> Value

toEncodingList :: [LiteralType] -> Encoding

ShATermConvertible LiteralType 
Instance details

Defined in ATC.GlobalAnnotations

Methods

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

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

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

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

type Rep LiteralType 
Instance details

Defined in ATC.GlobalAnnotations

type Rep LiteralType = D1 ('MetaData "LiteralType" "Common.GlobalAnnotations" "main" 'False) (((C1 ('MetaCons "StringCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id)) :+: C1 ('MetaCons "StringNull" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id)) :+: C1 ('MetaCons "ListNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id)))) :+: ((C1 ('MetaCons "Number" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fraction" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Floating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoLiteral" 'PrefixI 'False) (U1 :: Type -> Type))))

type AssocMap = Map Id AssocEither Source #

a map of associative ids

isAssoc :: AssocEither -> AssocMap -> Id -> Bool Source #

check if Id has a given associativity

type PrecedenceGraph = Rel Id Source #

a binary relation over ids as precedence graph

precRel Source #

Arguments

:: PrecedenceGraph

Graph describing the precedences

-> Id

x oID (y iid z) -- outer id

-> Id

x oid (y iID z) -- inner id

-> PrecRel 

return precedence relation of two ids

lookupDisplay :: GlobalAnnos -> Display_format -> Id -> Maybe [Token] Source #

lookup of an display [string] in the GlobalAnnos record