{-# 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
| Comment !Text
| Alias !Anchor
| Scalar !(Maybe Anchor) !Tag !ScalarStyle !Text
| SequenceStart !(Maybe Anchor) !Tag !NodeStyle
| SequenceEnd
| MappingStart !(Maybe Anchor) !Tag !NodeStyle
| MappingEnd
deriving (Show, Eq, Generic)
instance NFData Event where
rnf StreamStart = ()
rnf StreamEnd = ()
rnf (DocumentStart _) = ()
rnf (DocumentEnd _) = ()
rnf (Comment _) = ()
rnf (Alias _) = ()
rnf (Scalar a _ _ _) = rnf a
rnf (SequenceStart a _ _) = rnf a
rnf SequenceEnd = ()
rnf (MappingStart a _ _) = rnf a
rnf MappingEnd = ()
data EvPos = EvPos
{ eEvent :: !Event
, ePos :: !Pos
} deriving (Eq, Show, Generic)
instance NFData EvPos where rnf (EvPos ev p) = rnf (ev,p)
data Directives = NoDirEndMarker
| DirEndMarkerNoVersion
| DirEndMarkerVersion !Word
deriving (Show, Eq, Generic)
instance NFData Directives where rnf !_ = ()
data ScalarStyle = Plain
| SingleQuoted
| DoubleQuoted
| Literal !Chomp !IndentOfs
| Folded !Chomp !IndentOfs
deriving (Eq,Ord,Show,Generic)
instance NFData ScalarStyle where rnf !_ = ()
data Chomp = Strip
| Clip
| Keep
deriving (Eq,Ord,Show,Generic)
instance NFData Chomp where rnf !_ = ()
data IndentOfs = IndentAuto | IndentOfs1 | IndentOfs2 | IndentOfs3 | IndentOfs4 | IndentOfs5 | IndentOfs6 | IndentOfs7 | IndentOfs8 | IndentOfs9
deriving (Eq, Ord, Show, Enum, Generic)
instance NFData IndentOfs where rnf !_ = ()
data NodeStyle = Flow
| Block
deriving (Eq,Ord,Show,Generic)
instance NFData NodeStyle where rnf !_ = ()
scalarNodeStyle :: ScalarStyle -> NodeStyle
scalarNodeStyle Plain = Flow
scalarNodeStyle SingleQuoted = Flow
scalarNodeStyle DoubleQuoted = Flow
scalarNodeStyle (Literal _ _) = Block
scalarNodeStyle (Folded _ _ ) = Block
type Anchor = Text
newtype Tag = Tag (Maybe Text)
deriving (Eq,Ord,Generic)
instance Show Tag where
show (Tag x) = show x
instance NFData Tag where rnf (Tag x) = rnf x
type EvStream = [Either (Pos,String) EvPos]
tagToText :: Tag -> Maybe T.Text
tagToText (Tag x) = x
untagged :: Tag
untagged = Tag Nothing
isUntagged :: Tag -> Bool
isUntagged (Tag Nothing) = True
isUntagged _ = False