{-# LANGUAGE DeriveDataTypeable #-}
module Common.AS_Annotation where
import Common.Id
import Common.IRI (IRI)
import Data.Data
import Data.Maybe
import qualified Data.Map as Map
import Data.Graph.Inductive.Graph as Graph
data Annote_word = Annote_word String |
deriving (Int -> Annote_word -> ShowS
[Annote_word] -> ShowS
Annote_word -> String
(Int -> Annote_word -> ShowS)
-> (Annote_word -> String)
-> ([Annote_word] -> ShowS)
-> Show Annote_word
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Annote_word] -> ShowS
$cshowList :: [Annote_word] -> ShowS
show :: Annote_word -> String
$cshow :: Annote_word -> String
showsPrec :: Int -> Annote_word -> ShowS
$cshowsPrec :: Int -> Annote_word -> ShowS
Show, Annote_word -> Annote_word -> Bool
(Annote_word -> Annote_word -> Bool)
-> (Annote_word -> Annote_word -> Bool) -> Eq Annote_word
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annote_word -> Annote_word -> Bool
$c/= :: Annote_word -> Annote_word -> Bool
== :: Annote_word -> Annote_word -> Bool
$c== :: Annote_word -> Annote_word -> Bool
Eq, Eq Annote_word
Eq Annote_word =>
(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)
-> (Annote_word -> Annote_word -> Annote_word)
-> (Annote_word -> Annote_word -> Annote_word)
-> Ord Annote_word
Annote_word -> Annote_word -> Bool
Annote_word -> Annote_word -> Ordering
Annote_word -> Annote_word -> Annote_word
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Annote_word -> Annote_word -> Annote_word
$cmin :: Annote_word -> Annote_word -> Annote_word
max :: Annote_word -> Annote_word -> Annote_word
$cmax :: Annote_word -> Annote_word -> Annote_word
>= :: Annote_word -> Annote_word -> Bool
$c>= :: Annote_word -> Annote_word -> Bool
> :: Annote_word -> Annote_word -> Bool
$c> :: Annote_word -> Annote_word -> Bool
<= :: Annote_word -> Annote_word -> Bool
$c<= :: Annote_word -> Annote_word -> Bool
< :: Annote_word -> Annote_word -> Bool
$c< :: Annote_word -> Annote_word -> Bool
compare :: Annote_word -> Annote_word -> Ordering
$ccompare :: Annote_word -> Annote_word -> Ordering
$cp1Ord :: Eq Annote_word
Ord, Typeable, )
data Annote_text = Line_anno String | Group_anno [String]
deriving (Int -> Annote_text -> ShowS
[Annote_text] -> ShowS
Annote_text -> String
(Int -> Annote_text -> ShowS)
-> (Annote_text -> String)
-> ([Annote_text] -> ShowS)
-> Show Annote_text
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Annote_text] -> ShowS
$cshowList :: [Annote_text] -> ShowS
show :: Annote_text -> String
$cshow :: Annote_text -> String
showsPrec :: Int -> Annote_text -> ShowS
$cshowsPrec :: Int -> Annote_text -> ShowS
Show, Annote_text -> Annote_text -> Bool
(Annote_text -> Annote_text -> Bool)
-> (Annote_text -> Annote_text -> Bool) -> Eq Annote_text
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annote_text -> Annote_text -> Bool
$c/= :: Annote_text -> Annote_text -> Bool
== :: Annote_text -> Annote_text -> Bool
$c== :: Annote_text -> Annote_text -> Bool
Eq, Eq Annote_text
Eq Annote_text =>
(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)
-> (Annote_text -> Annote_text -> Annote_text)
-> (Annote_text -> Annote_text -> Annote_text)
-> Ord Annote_text
Annote_text -> Annote_text -> Bool
Annote_text -> Annote_text -> Ordering
Annote_text -> Annote_text -> Annote_text
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Annote_text -> Annote_text -> Annote_text
$cmin :: Annote_text -> Annote_text -> Annote_text
max :: Annote_text -> Annote_text -> Annote_text
$cmax :: Annote_text -> Annote_text -> Annote_text
>= :: Annote_text -> Annote_text -> Bool
$c>= :: Annote_text -> Annote_text -> Bool
> :: Annote_text -> Annote_text -> Bool
$c> :: Annote_text -> Annote_text -> Bool
<= :: Annote_text -> Annote_text -> Bool
$c<= :: Annote_text -> Annote_text -> Bool
< :: Annote_text -> Annote_text -> Bool
$c< :: Annote_text -> Annote_text -> Bool
compare :: Annote_text -> Annote_text -> Ordering
$ccompare :: Annote_text -> Annote_text -> Ordering
$cp1Ord :: Eq Annote_text
Ord, Typeable, Typeable Annote_text
Constr
DataType
Typeable Annote_text =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annote_text -> c Annote_text)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annote_text)
-> (Annote_text -> Constr)
-> (Annote_text -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Annote_text))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Annote_text))
-> ((forall b. Data b => b -> b) -> Annote_text -> Annote_text)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r)
-> (forall u. (forall d. Data d => d -> u) -> Annote_text -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Annote_text -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text)
-> Data Annote_text
Annote_text -> Constr
Annote_text -> DataType
(forall b. Data b => b -> b) -> Annote_text -> Annote_text
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annote_text -> c Annote_text
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annote_text
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Annote_text -> u
forall u. (forall d. Data d => d -> u) -> Annote_text -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annote_text
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annote_text -> c Annote_text
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Annote_text)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Annote_text)
$cGroup_anno :: Constr
$cLine_anno :: Constr
$tAnnote_text :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
gmapMp :: (forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
gmapM :: (forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annote_text -> m Annote_text
gmapQi :: Int -> (forall d. Data d => d -> u) -> Annote_text -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Annote_text -> u
gmapQ :: (forall d. Data d => d -> u) -> Annote_text -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Annote_text -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annote_text -> r
gmapT :: (forall b. Data b => b -> b) -> Annote_text -> Annote_text
$cgmapT :: (forall b. Data b => b -> b) -> Annote_text -> Annote_text
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Annote_text)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Annote_text)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Annote_text)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Annote_text)
dataTypeOf :: Annote_text -> DataType
$cdataTypeOf :: Annote_text -> DataType
toConstr :: Annote_text -> Constr
$ctoConstr :: Annote_text -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annote_text
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annote_text
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annote_text -> c Annote_text
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annote_text -> c Annote_text
$cp1Data :: Typeable Annote_text
Data)
data Display_format = DF_HTML | DF_LATEX | DF_RTF
deriving (Int -> Display_format -> ShowS
[Display_format] -> ShowS
Display_format -> String
(Int -> Display_format -> ShowS)
-> (Display_format -> String)
-> ([Display_format] -> ShowS)
-> Show Display_format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Display_format] -> ShowS
$cshowList :: [Display_format] -> ShowS
show :: Display_format -> String
$cshow :: Display_format -> String
showsPrec :: Int -> Display_format -> ShowS
$cshowsPrec :: Int -> Display_format -> ShowS
Show, Display_format -> Display_format -> Bool
(Display_format -> Display_format -> Bool)
-> (Display_format -> Display_format -> Bool) -> Eq Display_format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Display_format -> Display_format -> Bool
$c/= :: Display_format -> Display_format -> Bool
== :: Display_format -> Display_format -> Bool
$c== :: Display_format -> Display_format -> Bool
Eq, Eq Display_format
Eq Display_format =>
(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)
-> (Display_format -> Display_format -> Display_format)
-> (Display_format -> Display_format -> Display_format)
-> Ord Display_format
Display_format -> Display_format -> Bool
Display_format -> Display_format -> Ordering
Display_format -> Display_format -> Display_format
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Display_format -> Display_format -> Display_format
$cmin :: Display_format -> Display_format -> Display_format
max :: Display_format -> Display_format -> Display_format
$cmax :: Display_format -> Display_format -> Display_format
>= :: Display_format -> Display_format -> Bool
$c>= :: Display_format -> Display_format -> Bool
> :: Display_format -> Display_format -> Bool
$c> :: Display_format -> Display_format -> Bool
<= :: Display_format -> Display_format -> Bool
$c<= :: Display_format -> Display_format -> Bool
< :: Display_format -> Display_format -> Bool
$c< :: Display_format -> Display_format -> Bool
compare :: Display_format -> Display_format -> Ordering
$ccompare :: Display_format -> Display_format -> Ordering
$cp1Ord :: Eq Display_format
Ord, Typeable, Typeable Display_format
Constr
DataType
Typeable Display_format =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display_format -> c Display_format)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display_format)
-> (Display_format -> Constr)
-> (Display_format -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Display_format))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Display_format))
-> ((forall b. Data b => b -> b)
-> Display_format -> Display_format)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r)
-> (forall u.
(forall d. Data d => d -> u) -> Display_format -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Display_format -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format)
-> Data Display_format
Display_format -> Constr
Display_format -> DataType
(forall b. Data b => b -> b) -> Display_format -> Display_format
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display_format -> c Display_format
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display_format
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> Display_format -> u
forall u. (forall d. Data d => d -> u) -> Display_format -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display_format
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display_format -> c Display_format
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Display_format)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Display_format)
$cDF_RTF :: Constr
$cDF_LATEX :: Constr
$cDF_HTML :: Constr
$tDisplay_format :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> Display_format -> m Display_format
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format
gmapMp :: (forall d. Data d => d -> m d)
-> Display_format -> m Display_format
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format
gmapM :: (forall d. Data d => d -> m d)
-> Display_format -> m Display_format
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Display_format -> m Display_format
gmapQi :: Int -> (forall d. Data d => d -> u) -> Display_format -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> Display_format -> u
gmapQ :: (forall d. Data d => d -> u) -> Display_format -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Display_format -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display_format -> r
gmapT :: (forall b. Data b => b -> b) -> Display_format -> Display_format
$cgmapT :: (forall b. Data b => b -> b) -> Display_format -> Display_format
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Display_format)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Display_format)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Display_format)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Display_format)
dataTypeOf :: Display_format -> DataType
$cdataTypeOf :: Display_format -> DataType
toConstr :: Display_format -> Constr
$ctoConstr :: Display_format -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display_format
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display_format
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display_format -> c Display_format
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display_format -> c Display_format
$cp1Data :: Typeable Display_format
Data)
swapTable :: [(a, b)] -> [(b, a)]
swapTable :: [(a, b)] -> [(b, a)]
swapTable = ((a, b) -> (b, a)) -> [(a, b)] -> [(b, a)]
forall a b. (a -> b) -> [a] -> [b]
map (((a, b) -> (b, a)) -> [(a, b)] -> [(b, a)])
-> ((a, b) -> (b, a)) -> [(a, b)] -> [(b, a)]
forall a b. (a -> b) -> a -> b
$ \ (a :: a
a, b :: b
b) -> (b
b, a
a)
toTable :: (Show a) => [a] -> [(a, String)]
toTable :: [a] -> [(a, String)]
toTable = (a -> (a, String)) -> [a] -> [(a, String)]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> (a, String)) -> [a] -> [(a, String)])
-> (a -> (a, String)) -> [a] -> [(a, String)]
forall a b. (a -> b) -> a -> b
$ \ a :: a
a -> (a
a, Int -> ShowS
forall a. Int -> [a] -> [a]
drop 3 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ a -> String
forall a. Show a => a -> String
show a
a)
display_format_table :: [(Display_format, String)]
display_format_table :: [(Display_format, String)]
display_format_table = [Display_format] -> [(Display_format, String)]
forall a. Show a => [a] -> [(a, String)]
toTable [ Display_format
DF_HTML, Display_format
DF_LATEX, Display_format
DF_RTF ]
lookupDisplayFormat :: Display_format -> String
lookupDisplayFormat :: Display_format -> String
lookupDisplayFormat df :: Display_format
df =
String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (ShowS
forall a. HasCallStack => String -> a
error "lookupDisplayFormat: unknown display format")
(Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ Display_format -> [(Display_format, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Display_format
df [(Display_format, String)]
display_format_table
data PrecRel = Higher | Lower | BothDirections | NoDirection
deriving (Int -> PrecRel -> ShowS
[PrecRel] -> ShowS
PrecRel -> String
(Int -> PrecRel -> ShowS)
-> (PrecRel -> String) -> ([PrecRel] -> ShowS) -> Show PrecRel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrecRel] -> ShowS
$cshowList :: [PrecRel] -> ShowS
show :: PrecRel -> String
$cshow :: PrecRel -> String
showsPrec :: Int -> PrecRel -> ShowS
$cshowsPrec :: Int -> PrecRel -> ShowS
Show, PrecRel -> PrecRel -> Bool
(PrecRel -> PrecRel -> Bool)
-> (PrecRel -> PrecRel -> Bool) -> Eq PrecRel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrecRel -> PrecRel -> Bool
$c/= :: PrecRel -> PrecRel -> Bool
== :: PrecRel -> PrecRel -> Bool
$c== :: PrecRel -> PrecRel -> Bool
Eq, Eq PrecRel
Eq PrecRel =>
(PrecRel -> PrecRel -> Ordering)
-> (PrecRel -> PrecRel -> Bool)
-> (PrecRel -> PrecRel -> Bool)
-> (PrecRel -> PrecRel -> Bool)
-> (PrecRel -> PrecRel -> Bool)
-> (PrecRel -> PrecRel -> PrecRel)
-> (PrecRel -> PrecRel -> PrecRel)
-> Ord PrecRel
PrecRel -> PrecRel -> Bool
PrecRel -> PrecRel -> Ordering
PrecRel -> PrecRel -> PrecRel
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PrecRel -> PrecRel -> PrecRel
$cmin :: PrecRel -> PrecRel -> PrecRel
max :: PrecRel -> PrecRel -> PrecRel
$cmax :: PrecRel -> PrecRel -> PrecRel
>= :: PrecRel -> PrecRel -> Bool
$c>= :: PrecRel -> PrecRel -> Bool
> :: PrecRel -> PrecRel -> Bool
$c> :: PrecRel -> PrecRel -> Bool
<= :: PrecRel -> PrecRel -> Bool
$c<= :: PrecRel -> PrecRel -> Bool
< :: PrecRel -> PrecRel -> Bool
$c< :: PrecRel -> PrecRel -> Bool
compare :: PrecRel -> PrecRel -> Ordering
$ccompare :: PrecRel -> PrecRel -> Ordering
$cp1Ord :: Eq PrecRel
Ord, Typeable, Typeable PrecRel
Constr
DataType
Typeable PrecRel =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrecRel -> c PrecRel)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrecRel)
-> (PrecRel -> Constr)
-> (PrecRel -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrecRel))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrecRel))
-> ((forall b. Data b => b -> b) -> PrecRel -> PrecRel)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r)
-> (forall u. (forall d. Data d => d -> u) -> PrecRel -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> PrecRel -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel)
-> Data PrecRel
PrecRel -> Constr
PrecRel -> DataType
(forall b. Data b => b -> b) -> PrecRel -> PrecRel
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrecRel -> c PrecRel
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrecRel
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PrecRel -> u
forall u. (forall d. Data d => d -> u) -> PrecRel -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrecRel
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrecRel -> c PrecRel
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrecRel)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrecRel)
$cNoDirection :: Constr
$cBothDirections :: Constr
$cLower :: Constr
$cHigher :: Constr
$tPrecRel :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
gmapMp :: (forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
gmapM :: (forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrecRel -> m PrecRel
gmapQi :: Int -> (forall d. Data d => d -> u) -> PrecRel -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PrecRel -> u
gmapQ :: (forall d. Data d => d -> u) -> PrecRel -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PrecRel -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrecRel -> r
gmapT :: (forall b. Data b => b -> b) -> PrecRel -> PrecRel
$cgmapT :: (forall b. Data b => b -> b) -> PrecRel -> PrecRel
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrecRel)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrecRel)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PrecRel)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrecRel)
dataTypeOf :: PrecRel -> DataType
$cdataTypeOf :: PrecRel -> DataType
toConstr :: PrecRel -> Constr
$ctoConstr :: PrecRel -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrecRel
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrecRel
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrecRel -> c PrecRel
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrecRel -> c PrecRel
$cp1Data :: Typeable PrecRel
Data)
data AssocEither = ALeft | ARight deriving (Int -> AssocEither -> ShowS
[AssocEither] -> ShowS
AssocEither -> String
(Int -> AssocEither -> ShowS)
-> (AssocEither -> String)
-> ([AssocEither] -> ShowS)
-> Show AssocEither
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssocEither] -> ShowS
$cshowList :: [AssocEither] -> ShowS
show :: AssocEither -> String
$cshow :: AssocEither -> String
showsPrec :: Int -> AssocEither -> ShowS
$cshowsPrec :: Int -> AssocEither -> ShowS
Show, AssocEither -> AssocEither -> Bool
(AssocEither -> AssocEither -> Bool)
-> (AssocEither -> AssocEither -> Bool) -> Eq AssocEither
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssocEither -> AssocEither -> Bool
$c/= :: AssocEither -> AssocEither -> Bool
== :: AssocEither -> AssocEither -> Bool
$c== :: AssocEither -> AssocEither -> Bool
Eq, Eq AssocEither
Eq AssocEither =>
(AssocEither -> AssocEither -> Ordering)
-> (AssocEither -> AssocEither -> Bool)
-> (AssocEither -> AssocEither -> Bool)
-> (AssocEither -> AssocEither -> Bool)
-> (AssocEither -> AssocEither -> Bool)
-> (AssocEither -> AssocEither -> AssocEither)
-> (AssocEither -> AssocEither -> AssocEither)
-> Ord AssocEither
AssocEither -> AssocEither -> Bool
AssocEither -> AssocEither -> Ordering
AssocEither -> AssocEither -> AssocEither
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AssocEither -> AssocEither -> AssocEither
$cmin :: AssocEither -> AssocEither -> AssocEither
max :: AssocEither -> AssocEither -> AssocEither
$cmax :: AssocEither -> AssocEither -> AssocEither
>= :: AssocEither -> AssocEither -> Bool
$c>= :: AssocEither -> AssocEither -> Bool
> :: AssocEither -> AssocEither -> Bool
$c> :: AssocEither -> AssocEither -> Bool
<= :: AssocEither -> AssocEither -> Bool
$c<= :: AssocEither -> AssocEither -> Bool
< :: AssocEither -> AssocEither -> Bool
$c< :: AssocEither -> AssocEither -> Bool
compare :: AssocEither -> AssocEither -> Ordering
$ccompare :: AssocEither -> AssocEither -> Ordering
$cp1Ord :: Eq AssocEither
Ord, Typeable, Typeable AssocEither
Constr
DataType
Typeable AssocEither =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssocEither -> c AssocEither)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssocEither)
-> (AssocEither -> Constr)
-> (AssocEither -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AssocEither))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AssocEither))
-> ((forall b. Data b => b -> b) -> AssocEither -> AssocEither)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r)
-> (forall u. (forall d. Data d => d -> u) -> AssocEither -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AssocEither -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither)
-> Data AssocEither
AssocEither -> Constr
AssocEither -> DataType
(forall b. Data b => b -> b) -> AssocEither -> AssocEither
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssocEither -> c AssocEither
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssocEither
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AssocEither -> u
forall u. (forall d. Data d => d -> u) -> AssocEither -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssocEither
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssocEither -> c AssocEither
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AssocEither)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AssocEither)
$cARight :: Constr
$cALeft :: Constr
$tAssocEither :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
gmapMp :: (forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
gmapM :: (forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AssocEither -> m AssocEither
gmapQi :: Int -> (forall d. Data d => d -> u) -> AssocEither -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AssocEither -> u
gmapQ :: (forall d. Data d => d -> u) -> AssocEither -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AssocEither -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AssocEither -> r
gmapT :: (forall b. Data b => b -> b) -> AssocEither -> AssocEither
$cgmapT :: (forall b. Data b => b -> b) -> AssocEither -> AssocEither
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AssocEither)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AssocEither)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c AssocEither)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AssocEither)
dataTypeOf :: AssocEither -> DataType
$cdataTypeOf :: AssocEither -> DataType
toConstr :: AssocEither -> Constr
$ctoConstr :: AssocEither -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssocEither
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AssocEither
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssocEither -> c AssocEither
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AssocEither -> c AssocEither
$cp1Data :: Typeable AssocEither
Data)
data Semantic_anno = SA_cons | SA_def | SA_implies | SA_mono | SA_implied
| SA_mcons | SA_ccons | SA_wdef
deriving (Int -> Semantic_anno -> ShowS
[Semantic_anno] -> ShowS
Semantic_anno -> String
(Int -> Semantic_anno -> ShowS)
-> (Semantic_anno -> String)
-> ([Semantic_anno] -> ShowS)
-> Show Semantic_anno
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Semantic_anno] -> ShowS
$cshowList :: [Semantic_anno] -> ShowS
show :: Semantic_anno -> String
$cshow :: Semantic_anno -> String
showsPrec :: Int -> Semantic_anno -> ShowS
$cshowsPrec :: Int -> Semantic_anno -> ShowS
Show, Semantic_anno -> Semantic_anno -> Bool
(Semantic_anno -> Semantic_anno -> Bool)
-> (Semantic_anno -> Semantic_anno -> Bool) -> Eq Semantic_anno
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Semantic_anno -> Semantic_anno -> Bool
$c/= :: Semantic_anno -> Semantic_anno -> Bool
== :: Semantic_anno -> Semantic_anno -> Bool
$c== :: Semantic_anno -> Semantic_anno -> Bool
Eq, Eq Semantic_anno
Eq Semantic_anno =>
(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)
-> (Semantic_anno -> Semantic_anno -> Semantic_anno)
-> (Semantic_anno -> Semantic_anno -> Semantic_anno)
-> Ord Semantic_anno
Semantic_anno -> Semantic_anno -> Bool
Semantic_anno -> Semantic_anno -> Ordering
Semantic_anno -> Semantic_anno -> Semantic_anno
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Semantic_anno -> Semantic_anno -> Semantic_anno
$cmin :: Semantic_anno -> Semantic_anno -> Semantic_anno
max :: Semantic_anno -> Semantic_anno -> Semantic_anno
$cmax :: Semantic_anno -> Semantic_anno -> Semantic_anno
>= :: Semantic_anno -> Semantic_anno -> Bool
$c>= :: Semantic_anno -> Semantic_anno -> Bool
> :: Semantic_anno -> Semantic_anno -> Bool
$c> :: Semantic_anno -> Semantic_anno -> Bool
<= :: Semantic_anno -> Semantic_anno -> Bool
$c<= :: Semantic_anno -> Semantic_anno -> Bool
< :: Semantic_anno -> Semantic_anno -> Bool
$c< :: Semantic_anno -> Semantic_anno -> Bool
compare :: Semantic_anno -> Semantic_anno -> Ordering
$ccompare :: Semantic_anno -> Semantic_anno -> Ordering
$cp1Ord :: Eq Semantic_anno
Ord, Typeable, Typeable Semantic_anno
Constr
DataType
Typeable Semantic_anno =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Semantic_anno -> c Semantic_anno)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Semantic_anno)
-> (Semantic_anno -> Constr)
-> (Semantic_anno -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Semantic_anno))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Semantic_anno))
-> ((forall b. Data b => b -> b) -> Semantic_anno -> Semantic_anno)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r)
-> (forall u. (forall d. Data d => d -> u) -> Semantic_anno -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Semantic_anno -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno)
-> Data Semantic_anno
Semantic_anno -> Constr
Semantic_anno -> DataType
(forall b. Data b => b -> b) -> Semantic_anno -> Semantic_anno
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Semantic_anno -> c Semantic_anno
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Semantic_anno
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Semantic_anno -> u
forall u. (forall d. Data d => d -> u) -> Semantic_anno -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Semantic_anno
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Semantic_anno -> c Semantic_anno
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Semantic_anno)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Semantic_anno)
$cSA_wdef :: Constr
$cSA_ccons :: Constr
$cSA_mcons :: Constr
$cSA_implied :: Constr
$cSA_mono :: Constr
$cSA_implies :: Constr
$cSA_def :: Constr
$cSA_cons :: Constr
$tSemantic_anno :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
gmapMp :: (forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
gmapM :: (forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Semantic_anno -> m Semantic_anno
gmapQi :: Int -> (forall d. Data d => d -> u) -> Semantic_anno -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Semantic_anno -> u
gmapQ :: (forall d. Data d => d -> u) -> Semantic_anno -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Semantic_anno -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Semantic_anno -> r
gmapT :: (forall b. Data b => b -> b) -> Semantic_anno -> Semantic_anno
$cgmapT :: (forall b. Data b => b -> b) -> Semantic_anno -> Semantic_anno
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Semantic_anno)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Semantic_anno)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Semantic_anno)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Semantic_anno)
dataTypeOf :: Semantic_anno -> DataType
$cdataTypeOf :: Semantic_anno -> DataType
toConstr :: Semantic_anno -> Constr
$ctoConstr :: Semantic_anno -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Semantic_anno
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Semantic_anno
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Semantic_anno -> c Semantic_anno
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Semantic_anno -> c Semantic_anno
$cp1Data :: Typeable Semantic_anno
Data, Int -> Semantic_anno
Semantic_anno -> Int
Semantic_anno -> [Semantic_anno]
Semantic_anno -> Semantic_anno
Semantic_anno -> Semantic_anno -> [Semantic_anno]
Semantic_anno -> Semantic_anno -> Semantic_anno -> [Semantic_anno]
(Semantic_anno -> Semantic_anno)
-> (Semantic_anno -> Semantic_anno)
-> (Int -> Semantic_anno)
-> (Semantic_anno -> Int)
-> (Semantic_anno -> [Semantic_anno])
-> (Semantic_anno -> Semantic_anno -> [Semantic_anno])
-> (Semantic_anno -> Semantic_anno -> [Semantic_anno])
-> (Semantic_anno
-> Semantic_anno -> Semantic_anno -> [Semantic_anno])
-> Enum Semantic_anno
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Semantic_anno -> Semantic_anno -> Semantic_anno -> [Semantic_anno]
$cenumFromThenTo :: Semantic_anno -> Semantic_anno -> Semantic_anno -> [Semantic_anno]
enumFromTo :: Semantic_anno -> Semantic_anno -> [Semantic_anno]
$cenumFromTo :: Semantic_anno -> Semantic_anno -> [Semantic_anno]
enumFromThen :: Semantic_anno -> Semantic_anno -> [Semantic_anno]
$cenumFromThen :: Semantic_anno -> Semantic_anno -> [Semantic_anno]
enumFrom :: Semantic_anno -> [Semantic_anno]
$cenumFrom :: Semantic_anno -> [Semantic_anno]
fromEnum :: Semantic_anno -> Int
$cfromEnum :: Semantic_anno -> Int
toEnum :: Int -> Semantic_anno
$ctoEnum :: Int -> Semantic_anno
pred :: Semantic_anno -> Semantic_anno
$cpred :: Semantic_anno -> Semantic_anno
succ :: Semantic_anno -> Semantic_anno
$csucc :: Semantic_anno -> Semantic_anno
Enum, Semantic_anno
Semantic_anno -> Semantic_anno -> Bounded Semantic_anno
forall a. a -> a -> Bounded a
maxBound :: Semantic_anno
$cmaxBound :: Semantic_anno
minBound :: Semantic_anno
$cminBound :: Semantic_anno
Bounded)
semantic_anno_table :: [(Semantic_anno, String)]
semantic_anno_table :: [(Semantic_anno, String)]
semantic_anno_table =
[Semantic_anno] -> [(Semantic_anno, String)]
forall a. Show a => [a] -> [(a, String)]
toTable [Semantic_anno
forall a. Bounded a => a
minBound .. Semantic_anno
forall a. Bounded a => a
maxBound]
lookupSemanticAnno :: Semantic_anno -> String
lookupSemanticAnno :: Semantic_anno -> String
lookupSemanticAnno sa :: Semantic_anno
sa =
String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (ShowS
forall a. HasCallStack => String -> a
error "lookupSemanticAnno: no semantic anno")
(Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ Semantic_anno -> [(Semantic_anno, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Semantic_anno
sa [(Semantic_anno, String)]
semantic_anno_table
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
deriving (Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Annotation] -> ShowS
$cshowList :: [Annotation] -> ShowS
show :: Annotation -> String
$cshow :: Annotation -> String
showsPrec :: Int -> Annotation -> ShowS
$cshowsPrec :: Int -> Annotation -> ShowS
Show, Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c== :: Annotation -> Annotation -> Bool
Eq, Eq Annotation
Eq Annotation =>
(Annotation -> Annotation -> Ordering)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Annotation)
-> (Annotation -> Annotation -> Annotation)
-> Ord Annotation
Annotation -> Annotation -> Bool
Annotation -> Annotation -> Ordering
Annotation -> Annotation -> Annotation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Annotation -> Annotation -> Annotation
$cmin :: Annotation -> Annotation -> Annotation
max :: Annotation -> Annotation -> Annotation
$cmax :: Annotation -> Annotation -> Annotation
>= :: Annotation -> Annotation -> Bool
$c>= :: Annotation -> Annotation -> Bool
> :: Annotation -> Annotation -> Bool
$c> :: Annotation -> Annotation -> Bool
<= :: Annotation -> Annotation -> Bool
$c<= :: Annotation -> Annotation -> Bool
< :: Annotation -> Annotation -> Bool
$c< :: Annotation -> Annotation -> Bool
compare :: Annotation -> Annotation -> Ordering
$ccompare :: Annotation -> Annotation -> Ordering
$cp1Ord :: Eq Annotation
Ord, Typeable, Typeable Annotation
Constr
DataType
Typeable Annotation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annotation -> c Annotation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annotation)
-> (Annotation -> Constr)
-> (Annotation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Annotation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Annotation))
-> ((forall b. Data b => b -> b) -> Annotation -> Annotation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r)
-> (forall u. (forall d. Data d => d -> u) -> Annotation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Annotation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation)
-> Data Annotation
Annotation -> Constr
Annotation -> DataType
(forall b. Data b => b -> b) -> Annotation -> Annotation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annotation -> c Annotation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annotation
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Annotation -> u
forall u. (forall d. Data d => d -> u) -> Annotation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annotation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annotation -> c Annotation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Annotation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation)
$cSemantic_anno :: Constr
$cPrefix_anno :: Constr
$cLabel :: Constr
$cAssoc_anno :: Constr
$cPrec_anno :: Constr
$cString_anno :: Constr
$cFloat_anno :: Constr
$cNumber_anno :: Constr
$cList_anno :: Constr
$cDisplay_anno :: Constr
$cUnparsed_anno :: Constr
$tAnnotation :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Annotation -> m Annotation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation
gmapMp :: (forall d. Data d => d -> m d) -> Annotation -> m Annotation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation
gmapM :: (forall d. Data d => d -> m d) -> Annotation -> m Annotation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annotation -> m Annotation
gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Annotation -> u
gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Annotation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annotation -> r
gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation
$cgmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Annotation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Annotation)
dataTypeOf :: Annotation -> DataType
$cdataTypeOf :: Annotation -> DataType
toConstr :: Annotation -> Constr
$ctoConstr :: Annotation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annotation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Annotation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annotation -> c Annotation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annotation -> c Annotation
$cp1Data :: Typeable Annotation
Data)
isLabel :: Annotation -> Bool
isLabel :: Annotation -> Bool
isLabel a :: Annotation
a = case Annotation
a of
Label _ _ -> Bool
True
_ -> Bool
False
isImplies :: Annotation -> Bool
isImplies :: Annotation -> Bool
isImplies a :: Annotation
a = case Annotation
a of
Semantic_anno SA_implies _ -> Bool
True
_ -> Bool
False
isImplied :: Annotation -> Bool
isImplied :: Annotation -> Bool
isImplied a :: Annotation
a = case Annotation
a of
Semantic_anno SA_implied _ -> Bool
True
_ -> Bool
False
isSemanticAnno :: Annotation -> Bool
isSemanticAnno :: Annotation -> Bool
isSemanticAnno a :: Annotation
a = case Annotation
a of
Semantic_anno _ _ -> Bool
True
_ -> Bool
False
isComment :: Annotation -> Bool
c :: Annotation
c = case Annotation
c of
Unparsed_anno Comment_start _ _ -> Bool
True
_ -> Bool
False
isAnnote :: Annotation -> Bool
isAnnote :: Annotation -> Bool
isAnnote = Bool -> Bool
not (Bool -> Bool) -> (Annotation -> Bool) -> Annotation -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annotation -> Bool
isComment
partPrefixes :: [Annotation] -> (Map.Map String IRI, [Annotation])
partPrefixes :: [Annotation] -> (Map String IRI, [Annotation])
partPrefixes = (Annotation
-> (Map String IRI, [Annotation])
-> (Map String IRI, [Annotation]))
-> (Map String IRI, [Annotation])
-> [Annotation]
-> (Map String IRI, [Annotation])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ a :: Annotation
a (m :: Map String IRI
m, l :: [Annotation]
l) -> case Annotation
a of
Prefix_anno p :: [(String, IRI)]
p _ -> (Map String IRI -> Map String IRI -> Map String IRI
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map String IRI
m (Map String IRI -> Map String IRI)
-> Map String IRI -> Map String IRI
forall a b. (a -> b) -> a -> b
$ [(String, IRI)] -> Map String IRI
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(String, IRI)]
p, [Annotation]
l)
_ -> (Map String IRI
m, Annotation
a Annotation -> [Annotation] -> [Annotation]
forall a. a -> [a] -> [a]
: [Annotation]
l)) (Map String IRI
forall k a. Map k a
Map.empty, [])
data Annoted a = Annoted
{ Annoted a -> a
item :: a
, Annoted a -> Range
opt_pos :: Range
, Annoted a -> [Annotation]
l_annos :: [Annotation]
, Annoted a -> [Annotation]
r_annos :: [Annotation] } deriving (Int -> Annoted a -> ShowS
[Annoted a] -> ShowS
Annoted a -> String
(Int -> Annoted a -> ShowS)
-> (Annoted a -> String)
-> ([Annoted a] -> ShowS)
-> Show (Annoted a)
forall a. Show a => Int -> Annoted a -> ShowS
forall a. Show a => [Annoted a] -> ShowS
forall a. Show a => Annoted a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Annoted a] -> ShowS
$cshowList :: forall a. Show a => [Annoted a] -> ShowS
show :: Annoted a -> String
$cshow :: forall a. Show a => Annoted a -> String
showsPrec :: Int -> Annoted a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Annoted a -> ShowS
Show, Eq (Annoted a)
Eq (Annoted a) =>
(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)
-> (Annoted a -> Annoted a -> Annoted a)
-> (Annoted a -> Annoted a -> Annoted a)
-> Ord (Annoted a)
Annoted a -> Annoted a -> Bool
Annoted a -> Annoted a -> Ordering
Annoted a -> Annoted a -> Annoted a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Annoted a)
forall a. Ord a => Annoted a -> Annoted a -> Bool
forall a. Ord a => Annoted a -> Annoted a -> Ordering
forall a. Ord a => Annoted a -> Annoted a -> Annoted a
min :: Annoted a -> Annoted a -> Annoted a
$cmin :: forall a. Ord a => Annoted a -> Annoted a -> Annoted a
max :: Annoted a -> Annoted a -> Annoted a
$cmax :: forall a. Ord a => Annoted a -> Annoted a -> Annoted a
>= :: Annoted a -> Annoted a -> Bool
$c>= :: forall a. Ord a => Annoted a -> Annoted a -> Bool
> :: Annoted a -> Annoted a -> Bool
$c> :: forall a. Ord a => Annoted a -> Annoted a -> Bool
<= :: Annoted a -> Annoted a -> Bool
$c<= :: forall a. Ord a => Annoted a -> Annoted a -> Bool
< :: Annoted a -> Annoted a -> Bool
$c< :: forall a. Ord a => Annoted a -> Annoted a -> Bool
compare :: Annoted a -> Annoted a -> Ordering
$ccompare :: forall a. Ord a => Annoted a -> Annoted a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Annoted a)
Ord, Annoted a -> Annoted a -> Bool
(Annoted a -> Annoted a -> Bool)
-> (Annoted a -> Annoted a -> Bool) -> Eq (Annoted a)
forall a. Eq a => Annoted a -> Annoted a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annoted a -> Annoted a -> Bool
$c/= :: forall a. Eq a => Annoted a -> Annoted a -> Bool
== :: Annoted a -> Annoted a -> Bool
$c== :: forall a. Eq a => Annoted a -> Annoted a -> Bool
Eq, Typeable, Typeable (Annoted a)
Constr
DataType
Typeable (Annoted a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annoted a -> c (Annoted a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Annoted a))
-> (Annoted a -> Constr)
-> (Annoted a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Annoted a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Annoted a)))
-> ((forall b. Data b => b -> b) -> Annoted a -> Annoted a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Annoted a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Annoted a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a))
-> Data (Annoted a)
Annoted a -> Constr
Annoted a -> DataType
(forall d. Data d => c (t d)) -> Maybe (c (Annoted a))
(forall b. Data b => b -> b) -> Annoted a -> Annoted a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annoted a -> c (Annoted a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Annoted a)
forall a. Data a => Typeable (Annoted a)
forall a. Data a => Annoted a -> Constr
forall a. Data a => Annoted a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> Annoted a -> Annoted a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Annoted a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Annoted a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Annoted a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annoted a -> c (Annoted a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Annoted a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Annoted a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Annoted a -> u
forall u. (forall d. Data d => d -> u) -> Annoted a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Annoted a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annoted a -> c (Annoted a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Annoted a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Annoted a))
$cAnnoted :: Constr
$tAnnoted :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
gmapMp :: (forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
gmapM :: (forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Annoted a -> m (Annoted a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Annoted a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Annoted a -> u
gmapQ :: (forall d. Data d => d -> u) -> Annoted a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Annoted a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Annoted a -> r
gmapT :: (forall b. Data b => b -> b) -> Annoted a -> Annoted a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Annoted a -> Annoted a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Annoted a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Annoted a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Annoted a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Annoted a))
dataTypeOf :: Annoted a -> DataType
$cdataTypeOf :: forall a. Data a => Annoted a -> DataType
toConstr :: Annoted a -> Constr
$ctoConstr :: forall a. Data a => Annoted a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Annoted a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Annoted a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annoted a -> c (Annoted a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Annoted a -> c (Annoted a)
$cp1Data :: forall a. Data a => Typeable (Annoted a)
Data)
annoRange :: (a -> [Pos]) -> Annoted a -> [Pos]
annoRange :: (a -> [Pos]) -> Annoted a -> [Pos]
annoRange f :: a -> [Pos]
f a :: Annoted a
a =
[[Pos]] -> [Pos]
joinRanges ([[Pos]] -> [Pos]) -> [[Pos]] -> [Pos]
forall a b. (a -> b) -> a -> b
$ (Annotation -> [Pos]) -> [Annotation] -> [[Pos]]
forall a b. (a -> b) -> [a] -> [b]
map (Range -> [Pos]
rangeToList (Range -> [Pos]) -> (Annotation -> Range) -> Annotation -> [Pos]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annotation -> Range
forall a. GetRange a => a -> Range
getRange) (Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
l_annos Annoted a
a) [[Pos]] -> [[Pos]] -> [[Pos]]
forall a. [a] -> [a] -> [a]
++ [a -> [Pos]
f (a -> [Pos]) -> a -> [Pos]
forall a b. (a -> b) -> a -> b
$ Annoted a -> a
forall a. Annoted a -> a
item Annoted a
a]
[[Pos]] -> [[Pos]] -> [[Pos]]
forall a. [a] -> [a] -> [a]
++ [Range -> [Pos]
rangeToList (Annoted a -> Range
forall a. Annoted a -> Range
opt_pos Annoted a
a)] [[Pos]] -> [[Pos]] -> [[Pos]]
forall a. [a] -> [a] -> [a]
++ (Annotation -> [Pos]) -> [Annotation] -> [[Pos]]
forall a b. (a -> b) -> [a] -> [b]
map (Range -> [Pos]
rangeToList (Range -> [Pos]) -> (Annotation -> Range) -> Annotation -> [Pos]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annotation -> Range
forall a. GetRange a => a -> Range
getRange) (Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
r_annos Annoted a
a)
notImplied :: Annoted a -> Bool
notImplied :: Annoted a -> Bool
notImplied = Bool -> Bool
not (Bool -> Bool) -> (Annoted a -> Bool) -> Annoted a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Annotation -> Bool) -> [Annotation] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Annotation -> Bool
isImplied ([Annotation] -> Bool)
-> (Annoted a -> [Annotation]) -> Annoted a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
r_annos
data SenOrigin = SenOrigin
{ SenOrigin -> IRI
dGraphName :: IRI
, SenOrigin -> Int
originNodeId :: Node
, SenOrigin -> String
senName :: String } deriving (SenOrigin -> SenOrigin -> Bool
(SenOrigin -> SenOrigin -> Bool)
-> (SenOrigin -> SenOrigin -> Bool) -> Eq SenOrigin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SenOrigin -> SenOrigin -> Bool
$c/= :: SenOrigin -> SenOrigin -> Bool
== :: SenOrigin -> SenOrigin -> Bool
$c== :: SenOrigin -> SenOrigin -> Bool
Eq, Eq SenOrigin
Eq SenOrigin =>
(SenOrigin -> SenOrigin -> Ordering)
-> (SenOrigin -> SenOrigin -> Bool)
-> (SenOrigin -> SenOrigin -> Bool)
-> (SenOrigin -> SenOrigin -> Bool)
-> (SenOrigin -> SenOrigin -> Bool)
-> (SenOrigin -> SenOrigin -> SenOrigin)
-> (SenOrigin -> SenOrigin -> SenOrigin)
-> Ord SenOrigin
SenOrigin -> SenOrigin -> Bool
SenOrigin -> SenOrigin -> Ordering
SenOrigin -> SenOrigin -> SenOrigin
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SenOrigin -> SenOrigin -> SenOrigin
$cmin :: SenOrigin -> SenOrigin -> SenOrigin
max :: SenOrigin -> SenOrigin -> SenOrigin
$cmax :: SenOrigin -> SenOrigin -> SenOrigin
>= :: SenOrigin -> SenOrigin -> Bool
$c>= :: SenOrigin -> SenOrigin -> Bool
> :: SenOrigin -> SenOrigin -> Bool
$c> :: SenOrigin -> SenOrigin -> Bool
<= :: SenOrigin -> SenOrigin -> Bool
$c<= :: SenOrigin -> SenOrigin -> Bool
< :: SenOrigin -> SenOrigin -> Bool
$c< :: SenOrigin -> SenOrigin -> Bool
compare :: SenOrigin -> SenOrigin -> Ordering
$ccompare :: SenOrigin -> SenOrigin -> Ordering
$cp1Ord :: Eq SenOrigin
Ord, Int -> SenOrigin -> ShowS
[SenOrigin] -> ShowS
SenOrigin -> String
(Int -> SenOrigin -> ShowS)
-> (SenOrigin -> String)
-> ([SenOrigin] -> ShowS)
-> Show SenOrigin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SenOrigin] -> ShowS
$cshowList :: [SenOrigin] -> ShowS
show :: SenOrigin -> String
$cshow :: SenOrigin -> String
showsPrec :: Int -> SenOrigin -> ShowS
$cshowsPrec :: Int -> SenOrigin -> ShowS
Show, Typeable, Typeable SenOrigin
Constr
DataType
Typeable SenOrigin =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenOrigin -> c SenOrigin)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SenOrigin)
-> (SenOrigin -> Constr)
-> (SenOrigin -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SenOrigin))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SenOrigin))
-> ((forall b. Data b => b -> b) -> SenOrigin -> SenOrigin)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r)
-> (forall u. (forall d. Data d => d -> u) -> SenOrigin -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SenOrigin -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin)
-> Data SenOrigin
SenOrigin -> Constr
SenOrigin -> DataType
(forall b. Data b => b -> b) -> SenOrigin -> SenOrigin
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenOrigin -> c SenOrigin
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SenOrigin
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SenOrigin -> u
forall u. (forall d. Data d => d -> u) -> SenOrigin -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SenOrigin
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenOrigin -> c SenOrigin
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SenOrigin)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SenOrigin)
$cSenOrigin :: Constr
$tSenOrigin :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
gmapMp :: (forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
gmapM :: (forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SenOrigin -> m SenOrigin
gmapQi :: Int -> (forall d. Data d => d -> u) -> SenOrigin -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SenOrigin -> u
gmapQ :: (forall d. Data d => d -> u) -> SenOrigin -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SenOrigin -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenOrigin -> r
gmapT :: (forall b. Data b => b -> b) -> SenOrigin -> SenOrigin
$cgmapT :: (forall b. Data b => b -> b) -> SenOrigin -> SenOrigin
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SenOrigin)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SenOrigin)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SenOrigin)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SenOrigin)
dataTypeOf :: SenOrigin -> DataType
$cdataTypeOf :: SenOrigin -> DataType
toConstr :: SenOrigin -> Constr
$ctoConstr :: SenOrigin -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SenOrigin
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SenOrigin
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenOrigin -> c SenOrigin
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenOrigin -> c SenOrigin
$cp1Data :: Typeable SenOrigin
Data)
data SenAttr s a = SenAttr
{ SenAttr s a -> a
senAttr :: a
, SenAttr s a -> Maybe String
priority :: Maybe String
, SenAttr s a -> Bool
isAxiom :: Bool
, SenAttr s a -> Bool
isDef :: Bool
, SenAttr s a -> Bool
wasTheorem :: Bool
, SenAttr s a -> Maybe Bool
simpAnno :: Maybe Bool
, SenAttr s a -> Maybe Id
attrOrigin :: Maybe Id
, SenAttr s a -> String
senMark :: String
, SenAttr s a -> Maybe SenOrigin
senOrigin :: Maybe SenOrigin
, SenAttr s a -> s
sentence :: s } deriving (SenAttr s a -> SenAttr s a -> Bool
(SenAttr s a -> SenAttr s a -> Bool)
-> (SenAttr s a -> SenAttr s a -> Bool) -> Eq (SenAttr s a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall s a. (Eq a, Eq s) => SenAttr s a -> SenAttr s a -> Bool
/= :: SenAttr s a -> SenAttr s a -> Bool
$c/= :: forall s a. (Eq a, Eq s) => SenAttr s a -> SenAttr s a -> Bool
== :: SenAttr s a -> SenAttr s a -> Bool
$c== :: forall s a. (Eq a, Eq s) => SenAttr s a -> SenAttr s a -> Bool
Eq, Eq (SenAttr s a)
Eq (SenAttr s a) =>
(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)
-> (SenAttr s a -> SenAttr s a -> SenAttr s a)
-> (SenAttr s a -> SenAttr s a -> SenAttr s a)
-> Ord (SenAttr s a)
SenAttr s a -> SenAttr s a -> Bool
SenAttr s a -> SenAttr s a -> Ordering
SenAttr s a -> SenAttr s a -> SenAttr s a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall s a. (Ord a, Ord s) => Eq (SenAttr s a)
forall s a. (Ord a, Ord s) => SenAttr s a -> SenAttr s a -> Bool
forall s a.
(Ord a, Ord s) =>
SenAttr s a -> SenAttr s a -> Ordering
forall s a.
(Ord a, Ord s) =>
SenAttr s a -> SenAttr s a -> SenAttr s a
min :: SenAttr s a -> SenAttr s a -> SenAttr s a
$cmin :: forall s a.
(Ord a, Ord s) =>
SenAttr s a -> SenAttr s a -> SenAttr s a
max :: SenAttr s a -> SenAttr s a -> SenAttr s a
$cmax :: forall s a.
(Ord a, Ord s) =>
SenAttr s a -> SenAttr s a -> SenAttr s a
>= :: SenAttr s a -> SenAttr s a -> Bool
$c>= :: forall s a. (Ord a, Ord s) => SenAttr s a -> SenAttr s a -> Bool
> :: SenAttr s a -> SenAttr s a -> Bool
$c> :: forall s a. (Ord a, Ord s) => SenAttr s a -> SenAttr s a -> Bool
<= :: SenAttr s a -> SenAttr s a -> Bool
$c<= :: forall s a. (Ord a, Ord s) => SenAttr s a -> SenAttr s a -> Bool
< :: SenAttr s a -> SenAttr s a -> Bool
$c< :: forall s a. (Ord a, Ord s) => SenAttr s a -> SenAttr s a -> Bool
compare :: SenAttr s a -> SenAttr s a -> Ordering
$ccompare :: forall s a.
(Ord a, Ord s) =>
SenAttr s a -> SenAttr s a -> Ordering
$cp1Ord :: forall s a. (Ord a, Ord s) => Eq (SenAttr s a)
Ord, Int -> SenAttr s a -> ShowS
[SenAttr s a] -> ShowS
SenAttr s a -> String
(Int -> SenAttr s a -> ShowS)
-> (SenAttr s a -> String)
-> ([SenAttr s a] -> ShowS)
-> Show (SenAttr s a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall s a. (Show a, Show s) => Int -> SenAttr s a -> ShowS
forall s a. (Show a, Show s) => [SenAttr s a] -> ShowS
forall s a. (Show a, Show s) => SenAttr s a -> String
showList :: [SenAttr s a] -> ShowS
$cshowList :: forall s a. (Show a, Show s) => [SenAttr s a] -> ShowS
show :: SenAttr s a -> String
$cshow :: forall s a. (Show a, Show s) => SenAttr s a -> String
showsPrec :: Int -> SenAttr s a -> ShowS
$cshowsPrec :: forall s a. (Show a, Show s) => Int -> SenAttr s a -> ShowS
Show, Typeable, Typeable (SenAttr s a)
Constr
DataType
Typeable (SenAttr s a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SenAttr s a))
-> (SenAttr s a -> Constr)
-> (SenAttr s a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (SenAttr s a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SenAttr s a)))
-> ((forall b. Data b => b -> b) -> SenAttr s a -> SenAttr s a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r)
-> (forall u. (forall d. Data d => d -> u) -> SenAttr s a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SenAttr s a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a))
-> Data (SenAttr s a)
SenAttr s a -> Constr
SenAttr s a -> DataType
(forall b. Data b => b -> b) -> SenAttr s a -> SenAttr s a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SenAttr s a)
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SenAttr s a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SenAttr s a -> u
forall u. (forall d. Data d => d -> u) -> SenAttr s a -> [u]
forall s a. (Data s, Data a) => Typeable (SenAttr s a)
forall s a. (Data s, Data a) => SenAttr s a -> Constr
forall s a. (Data s, Data a) => SenAttr s a -> DataType
forall s a.
(Data s, Data a) =>
(forall b. Data b => b -> b) -> SenAttr s a -> SenAttr s a
forall s a u.
(Data s, Data a) =>
Int -> (forall d. Data d => d -> u) -> SenAttr s a -> u
forall s a u.
(Data s, Data a) =>
(forall d. Data d => d -> u) -> SenAttr s a -> [u]
forall s a r r'.
(Data s, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
forall s a r r'.
(Data s, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
forall s a (m :: * -> *).
(Data s, Data a, Monad m) =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
forall s a (m :: * -> *).
(Data s, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
forall s a (c :: * -> *).
(Data s, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SenAttr s a)
forall s a (c :: * -> *).
(Data s, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a)
forall s a (t :: * -> *) (c :: * -> *).
(Data s, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (SenAttr s a))
forall s a (t :: * -> * -> *) (c :: * -> *).
(Data s, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SenAttr s a))
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SenAttr s a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (SenAttr s a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SenAttr s a))
$cSenAttr :: Constr
$tSenAttr :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
$cgmapMo :: forall s a (m :: * -> *).
(Data s, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
gmapMp :: (forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
$cgmapMp :: forall s a (m :: * -> *).
(Data s, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
gmapM :: (forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
$cgmapM :: forall s a (m :: * -> *).
(Data s, Data a, Monad m) =>
(forall d. Data d => d -> m d) -> SenAttr s a -> m (SenAttr s a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> SenAttr s a -> u
$cgmapQi :: forall s a u.
(Data s, Data a) =>
Int -> (forall d. Data d => d -> u) -> SenAttr s a -> u
gmapQ :: (forall d. Data d => d -> u) -> SenAttr s a -> [u]
$cgmapQ :: forall s a u.
(Data s, Data a) =>
(forall d. Data d => d -> u) -> SenAttr s a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
$cgmapQr :: forall s a r r'.
(Data s, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
$cgmapQl :: forall s a r r'.
(Data s, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SenAttr s a -> r
gmapT :: (forall b. Data b => b -> b) -> SenAttr s a -> SenAttr s a
$cgmapT :: forall s a.
(Data s, Data a) =>
(forall b. Data b => b -> b) -> SenAttr s a -> SenAttr s a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SenAttr s a))
$cdataCast2 :: forall s a (t :: * -> * -> *) (c :: * -> *).
(Data s, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (SenAttr s a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (SenAttr s a))
$cdataCast1 :: forall s a (t :: * -> *) (c :: * -> *).
(Data s, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (SenAttr s a))
dataTypeOf :: SenAttr s a -> DataType
$cdataTypeOf :: forall s a. (Data s, Data a) => SenAttr s a -> DataType
toConstr :: SenAttr s a -> Constr
$ctoConstr :: forall s a. (Data s, Data a) => SenAttr s a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SenAttr s a)
$cgunfold :: forall s a (c :: * -> *).
(Data s, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (SenAttr s a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a)
$cgfoldl :: forall s a (c :: * -> *).
(Data s, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SenAttr s a -> c (SenAttr s a)
$cp1Data :: forall s a. (Data s, Data a) => Typeable (SenAttr s a)
Data)
makeNamed :: a -> s -> SenAttr s a
makeNamed :: a -> s -> SenAttr s a
makeNamed a :: a
a s :: s
s = SenAttr :: forall s a.
a
-> Maybe String
-> Bool
-> Bool
-> Bool
-> Maybe Bool
-> Maybe Id
-> String
-> Maybe SenOrigin
-> s
-> SenAttr s a
SenAttr
{ senAttr :: a
senAttr = a
a
, priority :: Maybe String
priority = Maybe String
forall a. Maybe a
Nothing
, isAxiom :: Bool
isAxiom = Bool
True
, isDef :: Bool
isDef = Bool
False
, wasTheorem :: Bool
wasTheorem = Bool
False
, simpAnno :: Maybe Bool
simpAnno = Maybe Bool
forall a. Maybe a
Nothing
, attrOrigin :: Maybe Id
attrOrigin = Maybe Id
forall a. Maybe a
Nothing
, senMark :: String
senMark = ""
, senOrigin :: Maybe SenOrigin
senOrigin = Maybe SenOrigin
forall a. Maybe a
Nothing
, sentence :: s
sentence = s
s }
setOrigin :: IRI -> Node -> String -> SenAttr s a -> SenAttr s a
setOrigin :: IRI -> Int -> String -> SenAttr s a -> SenAttr s a
setOrigin lib :: IRI
lib node :: Int
node sen :: String
sen nsen :: SenAttr s a
nsen = SenAttr s a
nsen {senOrigin :: Maybe SenOrigin
senOrigin = SenOrigin -> Maybe SenOrigin
forall a. a -> Maybe a
Just (SenOrigin -> Maybe SenOrigin) -> SenOrigin -> Maybe SenOrigin
forall a b. (a -> b) -> a -> b
$ IRI -> Int -> String -> SenOrigin
SenOrigin IRI
lib Int
node String
sen}
setOriginIfLocal :: IRI -> Node -> String -> SenAttr s a -> SenAttr s a
setOriginIfLocal :: IRI -> Int -> String -> SenAttr s a -> SenAttr s a
setOriginIfLocal lib :: IRI
lib node :: Int
node sen :: String
sen nsen :: SenAttr s a
nsen =
case SenAttr s a -> Maybe SenOrigin
forall s a. SenAttr s a -> Maybe SenOrigin
senOrigin SenAttr s a
nsen of
Nothing -> IRI -> Int -> String -> SenAttr s a -> SenAttr s a
forall s a. IRI -> Int -> String -> SenAttr s a -> SenAttr s a
setOrigin IRI
lib Int
node String
sen SenAttr s a
nsen
_ -> SenAttr s a
nsen
type Named s = SenAttr s String
markSen :: String -> Named s -> Named s
markSen :: String -> Named s -> Named s
markSen m :: String
m n :: Named s
n = Named s
n { senMark :: String
senMark = String
m }
unmark :: Named s -> Named s
unmark :: Named s -> Named s
unmark = String -> Named s -> Named s
forall s. String -> Named s -> Named s
markSen ""
reName :: (a -> b) -> SenAttr s a -> SenAttr s b
reName :: (a -> b) -> SenAttr s a -> SenAttr s b
reName f :: a -> b
f x :: SenAttr s a
x = SenAttr s a
x { senAttr :: b
senAttr = a -> b
f (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
$ SenAttr s a -> a
forall s a. SenAttr s a -> a
senAttr SenAttr s a
x }
mapNamed :: (s -> t) -> SenAttr s a -> SenAttr t a
mapNamed :: (s -> t) -> SenAttr s a -> SenAttr t a
mapNamed f :: s -> t
f x :: SenAttr s a
x = SenAttr s a
x { sentence :: t
sentence = s -> t
f (s -> t) -> s -> t
forall a b. (a -> b) -> a -> b
$ SenAttr s a -> s
forall s a. SenAttr s a -> s
sentence SenAttr s a
x }
mapNamedM :: Monad m => (s -> m t) -> Named s -> m (Named t)
mapNamedM :: (s -> m t) -> Named s -> m (Named t)
mapNamedM f :: s -> m t
f x :: Named s
x = do
t
y <- s -> m t
f (s -> m t) -> s -> m t
forall a b. (a -> b) -> a -> b
$ Named s -> s
forall s a. SenAttr s a -> s
sentence Named s
x
Named t -> m (Named t)
forall (m :: * -> *) a. Monad m => a -> m a
return Named s
x {sentence :: t
sentence = t
y}
mapAnM :: (Monad m) => (a -> m b) -> [Annoted a] -> m [Annoted b]
mapAnM :: (a -> m b) -> [Annoted a] -> m [Annoted b]
mapAnM f :: a -> m b
f al :: [Annoted a]
al =
do [b]
il <- (Annoted a -> m b) -> [Annoted a] -> m [b]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (a -> m b
f (a -> m b) -> (Annoted a -> a) -> Annoted a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annoted a -> a
forall a. Annoted a -> a
item) [Annoted a]
al
[Annoted b] -> m [Annoted b]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Annoted b] -> m [Annoted b]) -> [Annoted b] -> m [Annoted b]
forall a b. (a -> b) -> a -> b
$ (Annoted a -> b -> Annoted b) -> [Annoted a] -> [b] -> [Annoted b]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ((b -> Annoted a -> Annoted b) -> Annoted a -> b -> Annoted b
forall a b c. (a -> b -> c) -> b -> a -> c
flip b -> Annoted a -> Annoted b
forall b a. b -> Annoted a -> Annoted b
replaceAnnoted) [Annoted a]
al [b]
il
instance Functor Annoted where
fmap :: (a -> b) -> Annoted a -> Annoted b
fmap f :: a -> b
f (Annoted x :: a
x o :: Range
o l :: [Annotation]
l r :: [Annotation]
r) = b -> Range -> [Annotation] -> [Annotation] -> Annoted b
forall a. a -> Range -> [Annotation] -> [Annotation] -> Annoted a
Annoted (a -> b
f a
x) Range
o [Annotation]
l [Annotation]
r
replaceAnnoted :: b -> Annoted a -> Annoted b
replaceAnnoted :: b -> Annoted a -> Annoted b
replaceAnnoted x :: b
x (Annoted _ o :: Range
o l :: [Annotation]
l r :: [Annotation]
r) = b -> Range -> [Annotation] -> [Annotation] -> Annoted b
forall a. a -> Range -> [Annotation] -> [Annotation] -> Annoted a
Annoted b
x Range
o [Annotation]
l [Annotation]
r
appendAnno :: Annoted a -> [Annotation] -> Annoted a
appendAnno :: Annoted a -> [Annotation] -> Annoted a
appendAnno (Annoted x :: a
x p :: Range
p l :: [Annotation]
l r :: [Annotation]
r) = a -> Range -> [Annotation] -> [Annotation] -> Annoted a
forall a. a -> Range -> [Annotation] -> [Annotation] -> Annoted a
Annoted a
x Range
p [Annotation]
l ([Annotation] -> Annoted a)
-> ([Annotation] -> [Annotation]) -> [Annotation] -> Annoted a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Annotation]
r [Annotation] -> [Annotation] -> [Annotation]
forall a. [a] -> [a] -> [a]
++)
addLeftAnno :: [Annotation] -> a -> Annoted a
addLeftAnno :: [Annotation] -> a -> Annoted a
addLeftAnno l :: [Annotation]
l i :: a
i = a -> Range -> [Annotation] -> [Annotation] -> Annoted a
forall a. a -> Range -> [Annotation] -> [Annotation] -> Annoted a
Annoted a
i Range
nullRange [Annotation]
l []
emptyAnno :: a -> Annoted a
emptyAnno :: a -> Annoted a
emptyAnno = [Annotation] -> a -> Annoted a
forall a. [Annotation] -> a -> Annoted a
addLeftAnno []
getRLabel :: Annoted a -> String
getRLabel :: Annoted a -> String
getRLabel a :: Annoted a
a =
case (Annotation -> Bool) -> [Annotation] -> [Annotation]
forall a. (a -> Bool) -> [a] -> [a]
filter Annotation -> Bool
isLabel (Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
r_annos Annoted a
a) of
Label l :: [String]
l _ : _ -> [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> [String]) -> [String] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap String -> [String]
words [String]
l
_ -> ""
identAnno :: String -> Annotation -> Bool
identAnno :: String -> Annotation -> Bool
identAnno str :: String
str an :: Annotation
an = case Annotation
an of
Unparsed_anno (Annote_word wrd :: String
wrd) _ _ -> String
wrd String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
str
_ -> Bool
False
hasIdentAnno :: String -> Annoted a -> Bool
hasIdentAnno :: String -> Annoted a -> Bool
hasIdentAnno str :: String
str a :: Annoted a
a = (Annotation -> Bool) -> [Annotation] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> Annotation -> Bool
identAnno String
str) ([Annotation] -> Bool) -> [Annotation] -> Bool
forall a b. (a -> b) -> a -> b
$ Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
l_annos Annoted a
a [Annotation] -> [Annotation] -> [Annotation]
forall a. [a] -> [a] -> [a]
++ Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
r_annos Annoted a
a
getPriority :: [Annotation] -> Maybe String
getPriority :: [Annotation] -> Maybe String
getPriority = (Maybe String -> Annotation -> Maybe String)
-> Maybe String -> [Annotation] -> Maybe String
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl
(\ mId :: Maybe String
mId anno :: Annotation
anno -> case Annotation
anno of
Unparsed_anno (Annote_word "priority") (Group_anno (x :: String
x : _)) _ -> String -> Maybe String
forall a. a -> Maybe a
Just String
x
_ -> Maybe String
mId
) Maybe String
forall a. Maybe a
Nothing
makeNamedSen :: Annoted a -> Named a
makeNamedSen :: Annoted a -> Named a
makeNamedSen a :: Annoted a
a = (String -> a -> Named a
forall a s. a -> s -> SenAttr s a
makeNamed (Annoted a -> String
forall a. Annoted a -> String
getRLabel Annoted a
a) (a -> Named a) -> a -> Named a
forall a b. (a -> b) -> a -> b
$ Annoted a -> a
forall a. Annoted a -> a
item Annoted a
a)
{ isAxiom :: Bool
isAxiom = Annoted a -> Bool
forall a. Annoted a -> Bool
notImplied Annoted a
a
, priority :: Maybe String
priority = [Annotation] -> Maybe String
getPriority ([Annotation] -> Maybe String) -> [Annotation] -> Maybe String
forall a b. (a -> b) -> a -> b
$ Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
r_annos Annoted a
a
, simpAnno :: Maybe Bool
simpAnno = case (String -> Annoted a -> Bool
forall a. String -> Annoted a -> Bool
hasIdentAnno "simp" Annoted a
a, String -> Annoted a -> Bool
forall a. String -> Annoted a -> Bool
hasIdentAnno "nosimp" Annoted a
a) of
(True, False) -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
(False, True) -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
_ -> Maybe Bool
forall a. Maybe a
Nothing }
annoArg :: Annote_text -> String
annoArg :: Annote_text -> String
annoArg txt :: Annote_text
txt = case Annote_text
txt of
Line_anno str :: String
str -> String
str
Group_anno ls :: [String]
ls -> [String] -> String
unlines [String]
ls
newtype Name = Name String deriving Typeable
instance Show Name where
show :: Name -> String
show (Name s :: String
s) = String
s
getAnnoName :: Annoted a -> Name
getAnnoName :: Annoted a -> Name
getAnnoName = String -> Name
Name (String -> Name) -> (Annoted a -> String) -> Annoted a -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Annotation -> ShowS) -> String -> [Annotation] -> String
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ an :: Annotation
an -> case Annotation
an of
Unparsed_anno (Annote_word wrd :: String
wrd) txt :: Annote_text
txt _ | String
wrd String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== "name" ->
(Annote_text -> String
annoArg Annote_text
txt String -> ShowS
forall a. [a] -> [a] -> [a]
++)
_ -> ShowS
forall a. a -> a
id) "" ([Annotation] -> String)
-> (Annoted a -> [Annotation]) -> Annoted a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Annoted a -> [Annotation]
forall a. Annoted a -> [Annotation]
l_annos
instance GetRange Annote_word where
getRange :: Annote_word -> Range
getRange = Range -> Annote_word -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: Annote_word -> [Pos]
rangeSpan x :: Annote_word
x = case Annote_word
x of
Annote_word a :: String
a -> [[Pos]] -> [Pos]
joinRanges [String -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan String
a]
Comment_start -> []
instance GetRange Annote_text where
getRange :: Annote_text -> Range
getRange = Range -> Annote_text -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: Annote_text -> [Pos]
rangeSpan x :: Annote_text
x = case Annote_text
x of
Line_anno a :: String
a -> [[Pos]] -> [Pos]
joinRanges [String -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan String
a]
Group_anno a :: [String]
a -> [[Pos]] -> [Pos]
joinRanges [[String] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [String]
a]
instance GetRange Display_format where
getRange :: Display_format -> Range
getRange = Range -> Display_format -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: Display_format -> [Pos]
rangeSpan x :: Display_format
x = case Display_format
x of
DF_HTML -> []
DF_LATEX -> []
DF_RTF -> []
instance GetRange PrecRel where
getRange :: PrecRel -> Range
getRange = Range -> PrecRel -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: PrecRel -> [Pos]
rangeSpan x :: PrecRel
x = case PrecRel
x of
Higher -> []
Lower -> []
BothDirections -> []
NoDirection -> []
instance GetRange AssocEither where
getRange :: AssocEither -> Range
getRange = Range -> AssocEither -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: AssocEither -> [Pos]
rangeSpan x :: AssocEither
x = case AssocEither
x of
ALeft -> []
ARight -> []
instance GetRange Semantic_anno where
getRange :: Semantic_anno -> Range
getRange = Range -> Semantic_anno -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: Semantic_anno -> [Pos]
rangeSpan x :: Semantic_anno
x = case Semantic_anno
x of
SA_cons -> []
SA_def -> []
SA_implies -> []
SA_mono -> []
SA_implied -> []
SA_mcons -> []
SA_ccons -> []
SA_wdef -> []
instance GetRange Annotation where
getRange :: Annotation -> Range
getRange x :: Annotation
x = case Annotation
x of
Unparsed_anno _ _ p :: Range
p -> Range
p
Display_anno _ _ p :: Range
p -> Range
p
List_anno _ _ _ p :: Range
p -> Range
p
Number_anno _ p :: Range
p -> Range
p
Float_anno _ _ p :: Range
p -> Range
p
String_anno _ _ p :: Range
p -> Range
p
Prec_anno _ _ _ p :: Range
p -> Range
p
Assoc_anno _ _ p :: Range
p -> Range
p
Label _ p :: Range
p -> Range
p
Prefix_anno _ p :: Range
p -> Range
p
Semantic_anno _ p :: Range
p -> Range
p
rangeSpan :: Annotation -> [Pos]
rangeSpan x :: Annotation
x = case Annotation
x of
Unparsed_anno a :: Annote_word
a b :: Annote_text
b c :: Range
c -> [[Pos]] -> [Pos]
joinRanges [Annote_word -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Annote_word
a, Annote_text -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Annote_text
b,
Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
c]
Display_anno a :: Id
a b :: [(Display_format, String)]
b c :: Range
c -> [[Pos]] -> [Pos]
joinRanges [Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
a, [(Display_format, String)] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [(Display_format, String)]
b,
Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
c]
List_anno a :: Id
a b :: Id
b c :: Id
c d :: Range
d -> [[Pos]] -> [Pos]
joinRanges [Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
a, Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
b,
Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
c, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
d]
Number_anno a :: Id
a b :: Range
b -> [[Pos]] -> [Pos]
joinRanges [Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
a, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
b]
Float_anno a :: Id
a b :: Id
b c :: Range
c -> [[Pos]] -> [Pos]
joinRanges [Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
a, Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
b,
Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
c]
String_anno a :: Id
a b :: Id
b c :: Range
c -> [[Pos]] -> [Pos]
joinRanges [Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
a, Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Id
b,
Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
c]
Prec_anno a :: PrecRel
a b :: [Id]
b c :: [Id]
c d :: Range
d -> [[Pos]] -> [Pos]
joinRanges [PrecRel -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan PrecRel
a, [Id] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [Id]
b,
[Id] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [Id]
c, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
d]
Assoc_anno a :: AssocEither
a b :: [Id]
b c :: Range
c -> [[Pos]] -> [Pos]
joinRanges [AssocEither -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan AssocEither
a, [Id] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [Id]
b,
Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
c]
Label a :: [String]
a b :: Range
b -> [[Pos]] -> [Pos]
joinRanges [[String] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [String]
a, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
b]
Prefix_anno a :: [(String, IRI)]
a b :: Range
b -> [[Pos]] -> [Pos]
joinRanges [[(String, IRI)] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [(String, IRI)]
a, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
b]
Semantic_anno a :: Semantic_anno
a b :: Range
b -> [[Pos]] -> [Pos]
joinRanges [Semantic_anno -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Semantic_anno
a, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
b]
instance GetRange a => GetRange (Annoted a) where
getRange :: Annoted a -> Range
getRange x :: Annoted a
x = case Annoted a
x of
Annoted _ p :: Range
p _ _ -> Range
p
rangeSpan :: Annoted a -> [Pos]
rangeSpan x :: Annoted a
x = case Annoted a
x of
Annoted a :: a
a b :: Range
b c :: [Annotation]
c d :: [Annotation]
d -> [[Pos]] -> [Pos]
joinRanges [a -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan a
a, Range -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Range
b,
[Annotation] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [Annotation]
c, [Annotation] -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan [Annotation]
d]
instance GetRange SenOrigin where
getRange :: SenOrigin -> Range
getRange = Range -> SenOrigin -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: SenOrigin -> [Pos]
rangeSpan x :: SenOrigin
x = case SenOrigin
x of
SenOrigin a :: IRI
a b :: Int
b c :: String
c -> [[Pos]] -> [Pos]
joinRanges [IRI -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan IRI
a, Int -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Int
b,
String -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan String
c]
instance (GetRange s, GetRange a) => GetRange (SenAttr s a) where
getRange :: SenAttr s a -> Range
getRange = Range -> SenAttr s a -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: SenAttr s a -> [Pos]
rangeSpan x :: SenAttr s a
x = case SenAttr s a
x of
SenAttr a :: a
a b :: Maybe String
b c :: Bool
c d :: Bool
d e :: Bool
e f :: Maybe Bool
f g :: Maybe Id
g h :: String
h i :: Maybe SenOrigin
i j :: s
j -> [[Pos]] -> [Pos]
joinRanges [a -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan a
a,
Maybe String -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Maybe String
b, Bool -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Bool
c, Bool -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Bool
d, Bool -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Bool
e,
Maybe Bool -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Maybe Bool
f, Maybe Id -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Maybe Id
g, String -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan String
h, Maybe SenOrigin -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan Maybe SenOrigin
i,
s -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan s
j]
instance GetRange Name where
getRange :: Name -> Range
getRange = Range -> Name -> Range
forall a b. a -> b -> a
const Range
nullRange
rangeSpan :: Name -> [Pos]
rangeSpan x :: Name
x = case Name
x of
Name a :: String
a -> [[Pos]] -> [Pos]
joinRanges [String -> [Pos]
forall a. GetRange a => a -> [Pos]
rangeSpan String
a]