{-# LANGUAGE BangPatterns  #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe          #-}

-- |
-- Copyright: © Herbert Valerio Riedel 2015-2018
-- SPDX-License-Identifier: GPL-2.0-or-later
--
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 qualified Data.YAML.Token as Y

import           Util


-- | YAML Event Types
--
-- The events correspond to the ones from [LibYAML](http://pyyaml.org/wiki/LibYAML)
--
-- The grammar below defines well-formed streams of 'Event's:
--
-- @
-- stream   ::= 'StreamStart' document* 'StreamEnd'
-- document ::= 'DocumentStart' node 'DocumentEnd'
-- node     ::= 'Alias'
--            | 'Scalar'
--            | 'Comment'
--            | sequence
--            | mapping
-- sequence ::= 'SequenceStart' node* 'SequenceEnd'
-- mapping  ::= 'MappingStart' (node node)* 'MappingEnd'
-- @
--
-- @since 0.2.0
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 (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
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: 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
$cto :: forall x. Rep Event x -> Event
$cfrom :: forall x. Event -> Rep Event x
Generic)

-- | @since 0.2.0
instance NFData Event where
  rnf :: Event -> ()
rnf  StreamStart          = ()
  rnf  StreamEnd            = ()
  rnf (DocumentStart _)     = ()
  rnf (DocumentEnd _)       = ()
  rnf (Comment _)           = ()
  rnf (Alias _)             = ()
  rnf (Scalar a :: Maybe Anchor
a _ _ _)      = Maybe Anchor -> ()
forall a. NFData a => a -> ()
rnf Maybe Anchor
a
  rnf (SequenceStart a :: Maybe Anchor
a _ _) = Maybe Anchor -> ()
forall a. NFData a => a -> ()
rnf Maybe Anchor
a
  rnf  SequenceEnd          = ()
  rnf (MappingStart a :: Maybe Anchor
a _ _)  = Maybe Anchor -> ()
forall a. NFData a => a -> ()
rnf Maybe Anchor
a
  rnf  MappingEnd           = ()

-- |'Event' with corresponding Pos in YAML stream
--
-- @since 0.2.0
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
/= :: EvPos -> EvPos -> Bool
$c/= :: EvPos -> EvPos -> Bool
== :: EvPos -> EvPos -> Bool
$c== :: 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
showList :: [EvPos] -> ShowS
$cshowList :: [EvPos] -> ShowS
show :: EvPos -> String
$cshow :: EvPos -> String
showsPrec :: Int -> EvPos -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep EvPos x -> EvPos
$cfrom :: forall x. EvPos -> Rep EvPos x
Generic)

-- | @since 0.2.0
instance NFData EvPos where rnf :: EvPos -> ()
rnf (EvPos ev :: Event
ev p :: Pos
p) = (Event, Pos) -> ()
forall a. NFData a => a -> ()
rnf (Event
ev,Pos
p)

-- | Encodes document @%YAML@ directives and the directives end-marker
--
-- @since 0.2.0
data Directives = NoDirEndMarker    -- ^ no directives and also no @---@ marker
                | DirEndMarkerNoVersion -- ^ @---@ marker present, but no explicit @%YAML@ directive present
                | DirEndMarkerVersion !Word -- ^ @---@ marker present, as well as a @%YAML 1.mi@ version directive; the minor version @mi@ is stored in the 'Word' field.
                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
showList :: [Directives] -> ShowS
$cshowList :: [Directives] -> ShowS
show :: Directives -> String
$cshow :: Directives -> String
showsPrec :: Int -> Directives -> ShowS
$cshowsPrec :: Int -> Directives -> ShowS
Show, Directives -> Directives -> Bool
(Directives -> Directives -> Bool)
-> (Directives -> Directives -> Bool) -> Eq Directives
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Directives -> Directives -> Bool
$c/= :: Directives -> Directives -> Bool
== :: Directives -> Directives -> Bool
$c== :: 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
$cto :: forall x. Rep Directives x -> Directives
$cfrom :: forall x. Directives -> Rep Directives x
Generic)

-- | @since 0.2.0
instance NFData Directives where rnf :: Directives -> ()
rnf !Directives
_ = ()

-- | 'Scalar'-specific node style
--
-- This can be considered a more granular superset of 'NodeStyle'.
-- See also 'scalarNodeStyle'.
--
-- @since 0.2.0
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
/= :: ScalarStyle -> ScalarStyle -> Bool
$c/= :: ScalarStyle -> ScalarStyle -> Bool
== :: ScalarStyle -> ScalarStyle -> Bool
$c== :: 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
min :: ScalarStyle -> ScalarStyle -> ScalarStyle
$cmin :: ScalarStyle -> ScalarStyle -> ScalarStyle
max :: ScalarStyle -> ScalarStyle -> ScalarStyle
$cmax :: ScalarStyle -> ScalarStyle -> ScalarStyle
>= :: ScalarStyle -> ScalarStyle -> Bool
$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
compare :: ScalarStyle -> ScalarStyle -> Ordering
$ccompare :: ScalarStyle -> ScalarStyle -> Ordering
$cp1Ord :: Eq 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
showList :: [ScalarStyle] -> ShowS
$cshowList :: [ScalarStyle] -> ShowS
show :: ScalarStyle -> String
$cshow :: ScalarStyle -> String
showsPrec :: Int -> ScalarStyle -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep ScalarStyle x -> ScalarStyle
$cfrom :: forall x. ScalarStyle -> Rep ScalarStyle x
Generic)

-- | @since 0.2.0
instance NFData ScalarStyle where rnf :: ScalarStyle -> ()
rnf !ScalarStyle
_ = ()

-- | <https://yaml.org/spec/1.2/spec.html#id2794534 Block Chomping Indicator>
--
-- @since 0.2.0
data Chomp = Strip -- ^ Remove all trailing line breaks and shows the presence of @-@ chomping indicator.
           | Clip  -- ^ Keep first trailing line break; this also the default behavior used if no explicit chomping indicator is specified.
           | Keep  -- ^ Keep all trailing line breaks and shows the presence of @+@ chomping indicator.
           deriving (Chomp -> Chomp -> Bool
(Chomp -> Chomp -> Bool) -> (Chomp -> Chomp -> Bool) -> Eq Chomp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chomp -> Chomp -> Bool
$c/= :: Chomp -> Chomp -> Bool
== :: Chomp -> Chomp -> Bool
$c== :: 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
min :: Chomp -> Chomp -> Chomp
$cmin :: Chomp -> Chomp -> Chomp
max :: Chomp -> Chomp -> Chomp
$cmax :: Chomp -> Chomp -> Chomp
>= :: Chomp -> Chomp -> Bool
$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
compare :: Chomp -> Chomp -> Ordering
$ccompare :: Chomp -> Chomp -> Ordering
$cp1Ord :: Eq 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
showList :: [Chomp] -> ShowS
$cshowList :: [Chomp] -> ShowS
show :: Chomp -> String
$cshow :: Chomp -> String
showsPrec :: Int -> Chomp -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep Chomp x -> Chomp
$cfrom :: forall x. Chomp -> Rep Chomp x
Generic)

-- | @since 0.2.0
instance NFData Chomp where rnf :: Chomp -> ()
rnf !Chomp
_ = ()

-- | Block Indentation Indicator
--
-- 'IndentAuto' is the special case for auto Block Indentation Indicator
--
-- @since 0.2.0
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
/= :: IndentOfs -> IndentOfs -> Bool
$c/= :: IndentOfs -> IndentOfs -> Bool
== :: IndentOfs -> IndentOfs -> Bool
$c== :: 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
min :: IndentOfs -> IndentOfs -> IndentOfs
$cmin :: IndentOfs -> IndentOfs -> IndentOfs
max :: IndentOfs -> IndentOfs -> IndentOfs
$cmax :: IndentOfs -> IndentOfs -> IndentOfs
>= :: IndentOfs -> IndentOfs -> Bool
$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
compare :: IndentOfs -> IndentOfs -> Ordering
$ccompare :: IndentOfs -> IndentOfs -> Ordering
$cp1Ord :: Eq 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
showList :: [IndentOfs] -> ShowS
$cshowList :: [IndentOfs] -> ShowS
show :: IndentOfs -> String
$cshow :: IndentOfs -> String
showsPrec :: Int -> IndentOfs -> ShowS
$cshowsPrec :: Int -> 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
enumFromThenTo :: IndentOfs -> IndentOfs -> IndentOfs -> [IndentOfs]
$cenumFromThenTo :: IndentOfs -> IndentOfs -> IndentOfs -> [IndentOfs]
enumFromTo :: IndentOfs -> IndentOfs -> [IndentOfs]
$cenumFromTo :: IndentOfs -> IndentOfs -> [IndentOfs]
enumFromThen :: IndentOfs -> IndentOfs -> [IndentOfs]
$cenumFromThen :: IndentOfs -> IndentOfs -> [IndentOfs]
enumFrom :: IndentOfs -> [IndentOfs]
$cenumFrom :: IndentOfs -> [IndentOfs]
fromEnum :: IndentOfs -> Int
$cfromEnum :: IndentOfs -> Int
toEnum :: Int -> IndentOfs
$ctoEnum :: Int -> IndentOfs
pred :: IndentOfs -> IndentOfs
$cpred :: IndentOfs -> IndentOfs
succ :: IndentOfs -> IndentOfs
$csucc :: 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
$cto :: forall x. Rep IndentOfs x -> IndentOfs
$cfrom :: forall x. IndentOfs -> Rep IndentOfs x
Generic)

-- | @since 0.2.0
instance NFData IndentOfs where rnf :: IndentOfs -> ()
rnf !IndentOfs
_ = ()

-- | Node style
--
-- @since 0.2.0
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
/= :: NodeStyle -> NodeStyle -> Bool
$c/= :: NodeStyle -> NodeStyle -> Bool
== :: NodeStyle -> NodeStyle -> Bool
$c== :: 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
min :: NodeStyle -> NodeStyle -> NodeStyle
$cmin :: NodeStyle -> NodeStyle -> NodeStyle
max :: NodeStyle -> NodeStyle -> NodeStyle
$cmax :: NodeStyle -> NodeStyle -> NodeStyle
>= :: NodeStyle -> NodeStyle -> Bool
$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
compare :: NodeStyle -> NodeStyle -> Ordering
$ccompare :: NodeStyle -> NodeStyle -> Ordering
$cp1Ord :: Eq 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
showList :: [NodeStyle] -> ShowS
$cshowList :: [NodeStyle] -> ShowS
show :: NodeStyle -> String
$cshow :: NodeStyle -> String
showsPrec :: Int -> NodeStyle -> ShowS
$cshowsPrec :: Int -> 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
$cto :: forall x. Rep NodeStyle x -> NodeStyle
$cfrom :: forall x. NodeStyle -> Rep NodeStyle x
Generic)

-- | @since 0.2.0
instance NFData NodeStyle where rnf :: NodeStyle -> ()
rnf !NodeStyle
_ = ()

-- | Convert 'ScalarStyle' to 'NodeStyle'
--
-- @since 0.2.0
scalarNodeStyle :: ScalarStyle -> NodeStyle
scalarNodeStyle :: ScalarStyle -> NodeStyle
scalarNodeStyle Plain         = NodeStyle
Flow
scalarNodeStyle SingleQuoted  = NodeStyle
Flow
scalarNodeStyle DoubleQuoted  = NodeStyle
Flow
scalarNodeStyle (Literal _ _) = NodeStyle
Block
scalarNodeStyle (Folded _ _ ) = NodeStyle
Block

-- | YAML Anchor identifiers
type Anchor = Text

-- | YAML Tags
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
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: 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
min :: Tag -> Tag -> Tag
$cmin :: Tag -> Tag -> Tag
max :: Tag -> Tag -> Tag
$cmax :: Tag -> Tag -> Tag
>= :: Tag -> Tag -> Bool
$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
compare :: Tag -> Tag -> Ordering
$ccompare :: Tag -> Tag -> Ordering
$cp1Ord :: Eq 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
$cto :: forall x. Rep Tag x -> Tag
$cfrom :: forall x. Tag -> Rep Tag x
Generic)

instance Show Tag where
  show :: Tag -> String
show (Tag x :: Maybe Anchor
x) = Maybe Anchor -> String
forall a. Show a => a -> String
show Maybe Anchor
x

-- | @since 0.2.0
instance NFData Tag where rnf :: Tag -> ()
rnf (Tag x :: Maybe Anchor
x) = Maybe Anchor -> ()
forall a. NFData a => a -> ()
rnf Maybe Anchor
x

-- | Event stream produced by 'Data.YAML.Event.parseEvents'
--
-- A 'Left' value denotes parsing errors. The event stream ends
-- immediately once a 'Left' value is returned.
type EvStream = [Either (Pos,String) EvPos]


-- | Position in parsed YAML source
--
-- __NOTE__: if 'posCharOffset' is negative the 'Pos' value doesn't refer to a proper location; this may be emitted in corner cases when no proper location can be inferred.
data Pos = Pos
    { Pos -> Int
posByteOffset :: !Int -- ^ 0-based byte offset
    , Pos -> Int
posCharOffset :: !Int -- ^ 0-based character (Unicode code-point) offset
    , Pos -> Int
posLine       :: !Int -- ^ 1-based line number
    , Pos -> Int
posColumn     :: !Int -- ^ 0-based character (Unicode code-point) column number
    }  deriving (Pos -> Pos -> Bool
(Pos -> Pos -> Bool) -> (Pos -> Pos -> Bool) -> Eq Pos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pos -> Pos -> Bool
$c/= :: Pos -> Pos -> Bool
== :: Pos -> Pos -> Bool
$c== :: Pos -> Pos -> Bool
Eq, Int -> Pos -> ShowS
[Pos] -> ShowS
Pos -> String
(Int -> Pos -> ShowS)
-> (Pos -> String) -> ([Pos] -> ShowS) -> Show Pos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pos] -> ShowS
$cshowList :: [Pos] -> ShowS
show :: Pos -> String
$cshow :: Pos -> String
showsPrec :: Int -> Pos -> ShowS
$cshowsPrec :: Int -> Pos -> ShowS
Show, (forall x. Pos -> Rep Pos x)
-> (forall x. Rep Pos x -> Pos) -> Generic Pos
forall x. Rep Pos x -> Pos
forall x. Pos -> Rep Pos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Pos x -> Pos
$cfrom :: forall x. Pos -> Rep Pos x
Generic)

-- | @since 0.2.0
instance NFData Pos where rnf :: Pos -> ()
rnf !Pos
_ = ()

-- | Convert 'Tag' to its string representation
--
-- Returns 'Nothing' for 'untagged'
tagToText :: Tag -> Maybe T.Text
tagToText :: Tag -> Maybe Anchor
tagToText (Tag x :: Maybe Anchor
x) = Maybe Anchor
x

-- | An \"untagged\" YAML tag
untagged :: Tag
untagged :: Tag
untagged = Maybe Anchor -> Tag
Tag Maybe Anchor
forall a. Maybe a
Nothing

-- | Equivalent to @(== 'untagged')@
isUntagged :: Tag -> Bool
isUntagged :: Tag -> Bool
isUntagged (Tag Nothing) = Bool
True
isUntagged _             = Bool
False