{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
module Data.YAML.Event.Internal
( EvStream
, Event(..)
, EvPos(..)
, Directives(..)
, ScalarStyle(..)
, Chomp(..)
, IndentOfs(..)
, NodeStyle(..)
, scalarNodeStyle
, Tag(..), untagged, isUntagged, tagToText
, Anchor
, Pos(..)
, Y.Encoding(..)
) where
import qualified Data.Text as T
import Data.YAML.Pos (Pos (..))
import qualified Data.YAML.Token as Y
import Util
data Event
= StreamStart
| StreamEnd
| DocumentStart !Directives
| DocumentEnd !Bool
| !Text
| Alias !Anchor
| Scalar !(Maybe Anchor) !Tag !ScalarStyle !Text
| SequenceStart !(Maybe Anchor) !Tag !NodeStyle
| SequenceEnd
| MappingStart !(Maybe Anchor) !Tag !NodeStyle
| MappingEnd
deriving (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Event -> ShowS
showsPrec :: Int -> Event -> ShowS
$cshow :: Event -> String
show :: Event -> String
$cshowList :: [Event] -> ShowS
showList :: [Event] -> ShowS
Show, Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
/= :: Event -> Event -> Bool
Eq, (forall x. Event -> Rep Event x)
-> (forall x. Rep Event x -> Event) -> Generic Event
forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Event -> Rep Event x
from :: forall x. Event -> Rep Event x
$cto :: forall x. Rep Event x -> Event
to :: forall x. Rep Event x -> Event
Generic)
instance NFData Event where
rnf :: Event -> ()
rnf Event
StreamStart = ()
rnf Event
StreamEnd = ()
rnf (DocumentStart Directives
_) = ()
rnf (DocumentEnd Bool
_) = ()
rnf (Comment Text
_) = ()
rnf (Alias Text
_) = ()
rnf (Scalar Maybe Text
a Tag
_ ScalarStyle
_ Text
_) = Maybe Text -> ()
forall a. NFData a => a -> ()
rnf Maybe Text
a
rnf (SequenceStart Maybe Text
a Tag
_ NodeStyle
_) = Maybe Text -> ()
forall a. NFData a => a -> ()
rnf Maybe Text
a
rnf Event
SequenceEnd = ()
rnf (MappingStart Maybe Text
a Tag
_ NodeStyle
_) = Maybe Text -> ()
forall a. NFData a => a -> ()
rnf Maybe Text
a
rnf Event
MappingEnd = ()
data EvPos = EvPos
{ EvPos -> Event
eEvent :: !Event
, EvPos -> Pos
ePos :: !Pos
} deriving (EvPos -> EvPos -> Bool
(EvPos -> EvPos -> Bool) -> (EvPos -> EvPos -> Bool) -> Eq EvPos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EvPos -> EvPos -> Bool
== :: EvPos -> EvPos -> Bool
$c/= :: EvPos -> EvPos -> Bool
/= :: EvPos -> EvPos -> Bool
Eq, Int -> EvPos -> ShowS
[EvPos] -> ShowS
EvPos -> String
(Int -> EvPos -> ShowS)
-> (EvPos -> String) -> ([EvPos] -> ShowS) -> Show EvPos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EvPos -> ShowS
showsPrec :: Int -> EvPos -> ShowS
$cshow :: EvPos -> String
show :: EvPos -> String
$cshowList :: [EvPos] -> ShowS
showList :: [EvPos] -> ShowS
Show, (forall x. EvPos -> Rep EvPos x)
-> (forall x. Rep EvPos x -> EvPos) -> Generic EvPos
forall x. Rep EvPos x -> EvPos
forall x. EvPos -> Rep EvPos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EvPos -> Rep EvPos x
from :: forall x. EvPos -> Rep EvPos x
$cto :: forall x. Rep EvPos x -> EvPos
to :: forall x. Rep EvPos x -> EvPos
Generic)
instance NFData EvPos where rnf :: EvPos -> ()
rnf (EvPos Event
ev Pos
p) = (Event, Pos) -> ()
forall a. NFData a => a -> ()
rnf (Event
ev,Pos
p)
data Directives = NoDirEndMarker
| DirEndMarkerNoVersion
| DirEndMarkerVersion !Word
deriving (Int -> Directives -> ShowS
[Directives] -> ShowS
Directives -> String
(Int -> Directives -> ShowS)
-> (Directives -> String)
-> ([Directives] -> ShowS)
-> Show Directives
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Directives -> ShowS
showsPrec :: Int -> Directives -> ShowS
$cshow :: Directives -> String
show :: Directives -> String
$cshowList :: [Directives] -> ShowS
showList :: [Directives] -> ShowS
Show, Directives -> Directives -> Bool
(Directives -> Directives -> Bool)
-> (Directives -> Directives -> Bool) -> Eq Directives
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Directives -> Directives -> Bool
== :: Directives -> Directives -> Bool
$c/= :: Directives -> Directives -> Bool
/= :: Directives -> Directives -> Bool
Eq, (forall x. Directives -> Rep Directives x)
-> (forall x. Rep Directives x -> Directives) -> Generic Directives
forall x. Rep Directives x -> Directives
forall x. Directives -> Rep Directives x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Directives -> Rep Directives x
from :: forall x. Directives -> Rep Directives x
$cto :: forall x. Rep Directives x -> Directives
to :: forall x. Rep Directives x -> Directives
Generic)
instance NFData Directives where rnf :: Directives -> ()
rnf !Directives
_ = ()
data ScalarStyle = Plain
| SingleQuoted
| DoubleQuoted
| Literal !Chomp !IndentOfs
| Folded !Chomp !IndentOfs
deriving (ScalarStyle -> ScalarStyle -> Bool
(ScalarStyle -> ScalarStyle -> Bool)
-> (ScalarStyle -> ScalarStyle -> Bool) -> Eq ScalarStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScalarStyle -> ScalarStyle -> Bool
== :: ScalarStyle -> ScalarStyle -> Bool
$c/= :: ScalarStyle -> ScalarStyle -> Bool
/= :: ScalarStyle -> ScalarStyle -> Bool
Eq,Eq ScalarStyle
Eq ScalarStyle =>
(ScalarStyle -> ScalarStyle -> Ordering)
-> (ScalarStyle -> ScalarStyle -> Bool)
-> (ScalarStyle -> ScalarStyle -> Bool)
-> (ScalarStyle -> ScalarStyle -> Bool)
-> (ScalarStyle -> ScalarStyle -> Bool)
-> (ScalarStyle -> ScalarStyle -> ScalarStyle)
-> (ScalarStyle -> ScalarStyle -> ScalarStyle)
-> Ord ScalarStyle
ScalarStyle -> ScalarStyle -> Bool
ScalarStyle -> ScalarStyle -> Ordering
ScalarStyle -> ScalarStyle -> ScalarStyle
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
$ccompare :: ScalarStyle -> ScalarStyle -> Ordering
compare :: ScalarStyle -> ScalarStyle -> Ordering
$c< :: ScalarStyle -> ScalarStyle -> Bool
< :: ScalarStyle -> ScalarStyle -> Bool
$c<= :: ScalarStyle -> ScalarStyle -> Bool
<= :: ScalarStyle -> ScalarStyle -> Bool
$c> :: ScalarStyle -> ScalarStyle -> Bool
> :: ScalarStyle -> ScalarStyle -> Bool
$c>= :: ScalarStyle -> ScalarStyle -> Bool
>= :: ScalarStyle -> ScalarStyle -> Bool
$cmax :: ScalarStyle -> ScalarStyle -> ScalarStyle
max :: ScalarStyle -> ScalarStyle -> ScalarStyle
$cmin :: ScalarStyle -> ScalarStyle -> ScalarStyle
min :: ScalarStyle -> ScalarStyle -> ScalarStyle
Ord,Int -> ScalarStyle -> ShowS
[ScalarStyle] -> ShowS
ScalarStyle -> String
(Int -> ScalarStyle -> ShowS)
-> (ScalarStyle -> String)
-> ([ScalarStyle] -> ShowS)
-> Show ScalarStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalarStyle -> ShowS
showsPrec :: Int -> ScalarStyle -> ShowS
$cshow :: ScalarStyle -> String
show :: ScalarStyle -> String
$cshowList :: [ScalarStyle] -> ShowS
showList :: [ScalarStyle] -> ShowS
Show,(forall x. ScalarStyle -> Rep ScalarStyle x)
-> (forall x. Rep ScalarStyle x -> ScalarStyle)
-> Generic ScalarStyle
forall x. Rep ScalarStyle x -> ScalarStyle
forall x. ScalarStyle -> Rep ScalarStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScalarStyle -> Rep ScalarStyle x
from :: forall x. ScalarStyle -> Rep ScalarStyle x
$cto :: forall x. Rep ScalarStyle x -> ScalarStyle
to :: forall x. Rep ScalarStyle x -> ScalarStyle
Generic)
instance NFData ScalarStyle where rnf :: ScalarStyle -> ()
rnf !ScalarStyle
_ = ()
data Chomp = Strip
| Clip
| Keep
deriving (Chomp -> Chomp -> Bool
(Chomp -> Chomp -> Bool) -> (Chomp -> Chomp -> Bool) -> Eq Chomp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Chomp -> Chomp -> Bool
== :: Chomp -> Chomp -> Bool
$c/= :: Chomp -> Chomp -> Bool
/= :: Chomp -> Chomp -> Bool
Eq,Eq Chomp
Eq Chomp =>
(Chomp -> Chomp -> Ordering)
-> (Chomp -> Chomp -> Bool)
-> (Chomp -> Chomp -> Bool)
-> (Chomp -> Chomp -> Bool)
-> (Chomp -> Chomp -> Bool)
-> (Chomp -> Chomp -> Chomp)
-> (Chomp -> Chomp -> Chomp)
-> Ord Chomp
Chomp -> Chomp -> Bool
Chomp -> Chomp -> Ordering
Chomp -> Chomp -> Chomp
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
$ccompare :: Chomp -> Chomp -> Ordering
compare :: Chomp -> Chomp -> Ordering
$c< :: Chomp -> Chomp -> Bool
< :: Chomp -> Chomp -> Bool
$c<= :: Chomp -> Chomp -> Bool
<= :: Chomp -> Chomp -> Bool
$c> :: Chomp -> Chomp -> Bool
> :: Chomp -> Chomp -> Bool
$c>= :: Chomp -> Chomp -> Bool
>= :: Chomp -> Chomp -> Bool
$cmax :: Chomp -> Chomp -> Chomp
max :: Chomp -> Chomp -> Chomp
$cmin :: Chomp -> Chomp -> Chomp
min :: Chomp -> Chomp -> Chomp
Ord,Int -> Chomp -> ShowS
[Chomp] -> ShowS
Chomp -> String
(Int -> Chomp -> ShowS)
-> (Chomp -> String) -> ([Chomp] -> ShowS) -> Show Chomp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Chomp -> ShowS
showsPrec :: Int -> Chomp -> ShowS
$cshow :: Chomp -> String
show :: Chomp -> String
$cshowList :: [Chomp] -> ShowS
showList :: [Chomp] -> ShowS
Show,(forall x. Chomp -> Rep Chomp x)
-> (forall x. Rep Chomp x -> Chomp) -> Generic Chomp
forall x. Rep Chomp x -> Chomp
forall x. Chomp -> Rep Chomp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Chomp -> Rep Chomp x
from :: forall x. Chomp -> Rep Chomp x
$cto :: forall x. Rep Chomp x -> Chomp
to :: forall x. Rep Chomp x -> Chomp
Generic)
instance NFData Chomp where rnf :: Chomp -> ()
rnf !Chomp
_ = ()
data IndentOfs = IndentAuto | IndentOfs1 | IndentOfs2 | IndentOfs3 | IndentOfs4 | IndentOfs5 | IndentOfs6 | IndentOfs7 | IndentOfs8 | IndentOfs9
deriving (IndentOfs -> IndentOfs -> Bool
(IndentOfs -> IndentOfs -> Bool)
-> (IndentOfs -> IndentOfs -> Bool) -> Eq IndentOfs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndentOfs -> IndentOfs -> Bool
== :: IndentOfs -> IndentOfs -> Bool
$c/= :: IndentOfs -> IndentOfs -> Bool
/= :: IndentOfs -> IndentOfs -> Bool
Eq, Eq IndentOfs
Eq IndentOfs =>
(IndentOfs -> IndentOfs -> Ordering)
-> (IndentOfs -> IndentOfs -> Bool)
-> (IndentOfs -> IndentOfs -> Bool)
-> (IndentOfs -> IndentOfs -> Bool)
-> (IndentOfs -> IndentOfs -> Bool)
-> (IndentOfs -> IndentOfs -> IndentOfs)
-> (IndentOfs -> IndentOfs -> IndentOfs)
-> Ord IndentOfs
IndentOfs -> IndentOfs -> Bool
IndentOfs -> IndentOfs -> Ordering
IndentOfs -> IndentOfs -> IndentOfs
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
$ccompare :: IndentOfs -> IndentOfs -> Ordering
compare :: IndentOfs -> IndentOfs -> Ordering
$c< :: IndentOfs -> IndentOfs -> Bool
< :: IndentOfs -> IndentOfs -> Bool
$c<= :: IndentOfs -> IndentOfs -> Bool
<= :: IndentOfs -> IndentOfs -> Bool
$c> :: IndentOfs -> IndentOfs -> Bool
> :: IndentOfs -> IndentOfs -> Bool
$c>= :: IndentOfs -> IndentOfs -> Bool
>= :: IndentOfs -> IndentOfs -> Bool
$cmax :: IndentOfs -> IndentOfs -> IndentOfs
max :: IndentOfs -> IndentOfs -> IndentOfs
$cmin :: IndentOfs -> IndentOfs -> IndentOfs
min :: IndentOfs -> IndentOfs -> IndentOfs
Ord, Int -> IndentOfs -> ShowS
[IndentOfs] -> ShowS
IndentOfs -> String
(Int -> IndentOfs -> ShowS)
-> (IndentOfs -> String)
-> ([IndentOfs] -> ShowS)
-> Show IndentOfs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndentOfs -> ShowS
showsPrec :: Int -> IndentOfs -> ShowS
$cshow :: IndentOfs -> String
show :: IndentOfs -> String
$cshowList :: [IndentOfs] -> ShowS
showList :: [IndentOfs] -> ShowS
Show, Int -> IndentOfs
IndentOfs -> Int
IndentOfs -> [IndentOfs]
IndentOfs -> IndentOfs
IndentOfs -> IndentOfs -> [IndentOfs]
IndentOfs -> IndentOfs -> IndentOfs -> [IndentOfs]
(IndentOfs -> IndentOfs)
-> (IndentOfs -> IndentOfs)
-> (Int -> IndentOfs)
-> (IndentOfs -> Int)
-> (IndentOfs -> [IndentOfs])
-> (IndentOfs -> IndentOfs -> [IndentOfs])
-> (IndentOfs -> IndentOfs -> [IndentOfs])
-> (IndentOfs -> IndentOfs -> IndentOfs -> [IndentOfs])
-> Enum IndentOfs
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: IndentOfs -> IndentOfs
succ :: IndentOfs -> IndentOfs
$cpred :: IndentOfs -> IndentOfs
pred :: IndentOfs -> IndentOfs
$ctoEnum :: Int -> IndentOfs
toEnum :: Int -> IndentOfs
$cfromEnum :: IndentOfs -> Int
fromEnum :: IndentOfs -> Int
$cenumFrom :: IndentOfs -> [IndentOfs]
enumFrom :: IndentOfs -> [IndentOfs]
$cenumFromThen :: IndentOfs -> IndentOfs -> [IndentOfs]
enumFromThen :: IndentOfs -> IndentOfs -> [IndentOfs]
$cenumFromTo :: IndentOfs -> IndentOfs -> [IndentOfs]
enumFromTo :: IndentOfs -> IndentOfs -> [IndentOfs]
$cenumFromThenTo :: IndentOfs -> IndentOfs -> IndentOfs -> [IndentOfs]
enumFromThenTo :: IndentOfs -> IndentOfs -> IndentOfs -> [IndentOfs]
Enum, (forall x. IndentOfs -> Rep IndentOfs x)
-> (forall x. Rep IndentOfs x -> IndentOfs) -> Generic IndentOfs
forall x. Rep IndentOfs x -> IndentOfs
forall x. IndentOfs -> Rep IndentOfs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IndentOfs -> Rep IndentOfs x
from :: forall x. IndentOfs -> Rep IndentOfs x
$cto :: forall x. Rep IndentOfs x -> IndentOfs
to :: forall x. Rep IndentOfs x -> IndentOfs
Generic)
instance NFData IndentOfs where rnf :: IndentOfs -> ()
rnf !IndentOfs
_ = ()
data NodeStyle = Flow
| Block
deriving (NodeStyle -> NodeStyle -> Bool
(NodeStyle -> NodeStyle -> Bool)
-> (NodeStyle -> NodeStyle -> Bool) -> Eq NodeStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeStyle -> NodeStyle -> Bool
== :: NodeStyle -> NodeStyle -> Bool
$c/= :: NodeStyle -> NodeStyle -> Bool
/= :: NodeStyle -> NodeStyle -> Bool
Eq,Eq NodeStyle
Eq NodeStyle =>
(NodeStyle -> NodeStyle -> Ordering)
-> (NodeStyle -> NodeStyle -> Bool)
-> (NodeStyle -> NodeStyle -> Bool)
-> (NodeStyle -> NodeStyle -> Bool)
-> (NodeStyle -> NodeStyle -> Bool)
-> (NodeStyle -> NodeStyle -> NodeStyle)
-> (NodeStyle -> NodeStyle -> NodeStyle)
-> Ord NodeStyle
NodeStyle -> NodeStyle -> Bool
NodeStyle -> NodeStyle -> Ordering
NodeStyle -> NodeStyle -> NodeStyle
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
$ccompare :: NodeStyle -> NodeStyle -> Ordering
compare :: NodeStyle -> NodeStyle -> Ordering
$c< :: NodeStyle -> NodeStyle -> Bool
< :: NodeStyle -> NodeStyle -> Bool
$c<= :: NodeStyle -> NodeStyle -> Bool
<= :: NodeStyle -> NodeStyle -> Bool
$c> :: NodeStyle -> NodeStyle -> Bool
> :: NodeStyle -> NodeStyle -> Bool
$c>= :: NodeStyle -> NodeStyle -> Bool
>= :: NodeStyle -> NodeStyle -> Bool
$cmax :: NodeStyle -> NodeStyle -> NodeStyle
max :: NodeStyle -> NodeStyle -> NodeStyle
$cmin :: NodeStyle -> NodeStyle -> NodeStyle
min :: NodeStyle -> NodeStyle -> NodeStyle
Ord,Int -> NodeStyle -> ShowS
[NodeStyle] -> ShowS
NodeStyle -> String
(Int -> NodeStyle -> ShowS)
-> (NodeStyle -> String)
-> ([NodeStyle] -> ShowS)
-> Show NodeStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NodeStyle -> ShowS
showsPrec :: Int -> NodeStyle -> ShowS
$cshow :: NodeStyle -> String
show :: NodeStyle -> String
$cshowList :: [NodeStyle] -> ShowS
showList :: [NodeStyle] -> ShowS
Show,(forall x. NodeStyle -> Rep NodeStyle x)
-> (forall x. Rep NodeStyle x -> NodeStyle) -> Generic NodeStyle
forall x. Rep NodeStyle x -> NodeStyle
forall x. NodeStyle -> Rep NodeStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NodeStyle -> Rep NodeStyle x
from :: forall x. NodeStyle -> Rep NodeStyle x
$cto :: forall x. Rep NodeStyle x -> NodeStyle
to :: forall x. Rep NodeStyle x -> NodeStyle
Generic)
instance NFData NodeStyle where rnf :: NodeStyle -> ()
rnf !NodeStyle
_ = ()
scalarNodeStyle :: ScalarStyle -> NodeStyle
scalarNodeStyle :: ScalarStyle -> NodeStyle
scalarNodeStyle ScalarStyle
Plain = NodeStyle
Flow
scalarNodeStyle ScalarStyle
SingleQuoted = NodeStyle
Flow
scalarNodeStyle ScalarStyle
DoubleQuoted = NodeStyle
Flow
scalarNodeStyle (Literal Chomp
_ IndentOfs
_) = NodeStyle
Block
scalarNodeStyle (Folded Chomp
_ IndentOfs
_ ) = NodeStyle
Block
type Anchor = Text
newtype Tag = Tag (Maybe Text)
deriving (Tag -> Tag -> Bool
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
/= :: Tag -> Tag -> Bool
Eq,Eq Tag
Eq Tag =>
(Tag -> Tag -> Ordering)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Tag)
-> (Tag -> Tag -> Tag)
-> Ord Tag
Tag -> Tag -> Bool
Tag -> Tag -> Ordering
Tag -> Tag -> Tag
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
$ccompare :: Tag -> Tag -> Ordering
compare :: Tag -> Tag -> Ordering
$c< :: Tag -> Tag -> Bool
< :: Tag -> Tag -> Bool
$c<= :: Tag -> Tag -> Bool
<= :: Tag -> Tag -> Bool
$c> :: Tag -> Tag -> Bool
> :: Tag -> Tag -> Bool
$c>= :: Tag -> Tag -> Bool
>= :: Tag -> Tag -> Bool
$cmax :: Tag -> Tag -> Tag
max :: Tag -> Tag -> Tag
$cmin :: Tag -> Tag -> Tag
min :: Tag -> Tag -> Tag
Ord,(forall x. Tag -> Rep Tag x)
-> (forall x. Rep Tag x -> Tag) -> Generic Tag
forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Tag -> Rep Tag x
from :: forall x. Tag -> Rep Tag x
$cto :: forall x. Rep Tag x -> Tag
to :: forall x. Rep Tag x -> Tag
Generic)
instance Show Tag where
show :: Tag -> String
show (Tag Maybe Text
x) = Maybe Text -> String
forall a. Show a => a -> String
show Maybe Text
x
instance NFData Tag where rnf :: Tag -> ()
rnf (Tag Maybe Text
x) = Maybe Text -> ()
forall a. NFData a => a -> ()
rnf Maybe Text
x
type EvStream = [Either (Pos,String) EvPos]
tagToText :: Tag -> Maybe T.Text
tagToText :: Tag -> Maybe Text
tagToText (Tag Maybe Text
x) = Maybe Text
x
untagged :: Tag
untagged :: Tag
untagged = Maybe Text -> Tag
Tag Maybe Text
forall a. Maybe a
Nothing
isUntagged :: Tag -> Bool
isUntagged :: Tag -> Bool
isUntagged (Tag Maybe Text
Nothing) = Bool
True
isUntagged Tag
_ = Bool
False