{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE Safe #-}
module Data.YAML
(
decode
, decode1
, decodeStrict
, decode1Strict
, FromYAML(..)
, Parser
, parseEither
, failAtNode
, typeMismatch
, Mapping
, (.:), (.:?), (.:!), (.!=)
, encode
, encode1
, encodeStrict
, encode1Strict
, ToYAML(..)
, Pair
, mapping
, (.=)
, withScalar
, withSeq
, withBool
, withFloat
, withInt
, withNull
, withStr
, withMap
, decodeNode
, decodeNode'
, encodeNode
, encodeNode'
, Doc(Doc,docRoot)
, Node(..)
, Scalar(..)
, Pos(..)
, prettyPosWithSource
, SchemaResolver
, failsafeSchemaResolver
, jsonSchemaResolver
, coreSchemaResolver
, SchemaEncoder
, failsafeSchemaEncoder
, jsonSchemaEncoder
, coreSchemaEncoder
, decodeLoader
, Loader(..)
, LoaderT
, NodeId
) where
import qualified Control.Monad.Fail as Fail
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BS.L
import qualified Data.Map as Map
import qualified Data.Text as T
import Data.YAML.Dumper
import Data.YAML.Event (isUntagged, tagToText)
import Data.YAML.Internal
import Data.YAML.Loader
import Data.YAML.Pos
import Data.YAML.Schema.Internal
import Util
(.:) :: FromYAML a => Mapping Pos -> Text -> Parser a
Mapping Pos
m .: :: forall a. FromYAML a => Mapping Pos -> Text -> Parser a
.: Text
k = Parser a -> (Node Pos -> Parser a) -> Maybe (Node Pos) -> Parser a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Parser a
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> Parser a) -> [Char] -> Parser a
forall a b. (a -> b) -> a -> b
$ [Char]
"key " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
k [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" not found") Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML (Node Pos -> Mapping Pos -> Maybe (Node Pos)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Pos -> Scalar -> Node Pos
forall loc. loc -> Scalar -> Node loc
Scalar Pos
fakePos (Text -> Scalar
SStr Text
k)) Mapping Pos
m)
(.:?) :: FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
Mapping Pos
m .:? :: forall a. FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
.:? Text
k = Parser (Maybe a)
-> (Node Pos -> Parser (Maybe a))
-> Maybe (Node Pos)
-> Parser (Maybe a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe a -> Parser (Maybe a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing) Node Pos -> Parser (Maybe a)
forall a. FromYAML a => Node Pos -> Parser a
parseYAML (Node Pos -> Mapping Pos -> Maybe (Node Pos)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Pos -> Scalar -> Node Pos
forall loc. loc -> Scalar -> Node loc
Scalar Pos
fakePos (Text -> Scalar
SStr Text
k)) Mapping Pos
m)
(.:!) :: FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
Mapping Pos
m .:! :: forall a. FromYAML a => Mapping Pos -> Text -> Parser (Maybe a)
.:! Text
k = Parser (Maybe a)
-> (Node Pos -> Parser (Maybe a))
-> Maybe (Node Pos)
-> Parser (Maybe a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe a -> Parser (Maybe a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing) ((a -> Maybe a) -> Parser a -> Parser (Maybe a)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just (Parser a -> Parser (Maybe a))
-> (Node Pos -> Parser a) -> Node Pos -> Parser (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML) (Node Pos -> Mapping Pos -> Maybe (Node Pos)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Pos -> Scalar -> Node Pos
forall loc. loc -> Scalar -> Node loc
Scalar Pos
fakePos (Text -> Scalar
SStr Text
k)) Mapping Pos
m)
(.!=) :: Parser (Maybe a) -> a -> Parser a
Parser (Maybe a)
mv .!= :: forall a. Parser (Maybe a) -> a -> Parser a
.!= a
def = (Maybe a -> a) -> Parser (Maybe a) -> Parser a
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> (a -> a) -> Maybe a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
def a -> a
forall a. a -> a
id) Parser (Maybe a)
mv
fakePos :: Pos
fakePos :: Pos
fakePos = Pos { posByteOffset :: Int
posByteOffset = -Int
1 , posCharOffset :: Int
posCharOffset = -Int
1 , posLine :: Int
posLine = Int
1 , posColumn :: Int
posColumn = Int
0 }
decodeNode :: BS.L.ByteString -> Either (Pos, String) [Doc (Node Pos)]
decodeNode :: ByteString -> Either (Pos, [Char]) [Doc (Node Pos)]
decodeNode = SchemaResolver
-> Bool
-> Bool
-> ByteString
-> Either (Pos, [Char]) [Doc (Node Pos)]
decodeNode' SchemaResolver
coreSchemaResolver Bool
False Bool
False
decodeNode' :: SchemaResolver
-> Bool
-> Bool
-> BS.L.ByteString
-> Either (Pos, String) [Doc (Node Pos)]
decodeNode' :: SchemaResolver
-> Bool
-> Bool
-> ByteString
-> Either (Pos, [Char]) [Doc (Node Pos)]
decodeNode' SchemaResolver{Bool
Tag -> Either [Char] Tag
Tag -> ScalarStyle -> Text -> Either [Char] Scalar
schemaResolverScalar :: Tag -> ScalarStyle -> Text -> Either [Char] Scalar
schemaResolverSequence :: Tag -> Either [Char] Tag
schemaResolverMapping :: Tag -> Either [Char] Tag
schemaResolverMappingDuplicates :: Bool
schemaResolverMappingDuplicates :: SchemaResolver -> Bool
schemaResolverMapping :: SchemaResolver -> Tag -> Either [Char] Tag
schemaResolverSequence :: SchemaResolver -> Tag -> Either [Char] Tag
schemaResolverScalar :: SchemaResolver
-> Tag -> ScalarStyle -> Text -> Either [Char] Scalar
..} Bool
anchorNodes Bool
allowCycles ByteString
bs0
= (Node Pos -> Doc (Node Pos)) -> [Node Pos] -> [Doc (Node Pos)]
forall a b. (a -> b) -> [a] -> [b]
map Node Pos -> Doc (Node Pos)
forall n. n -> Doc n
Doc ([Node Pos] -> [Doc (Node Pos)])
-> Either (Pos, [Char]) [Node Pos]
-> Either (Pos, [Char]) [Doc (Node Pos)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Identity (Either (Pos, [Char]) [Node Pos])
-> Either (Pos, [Char]) [Node Pos]
forall a. Identity a -> a
runIdentity (Loader Identity (Node Pos)
-> ByteString -> Identity (Either (Pos, [Char]) [Node Pos])
forall n (m :: * -> *).
MonadFix m =>
Loader m n -> ByteString -> m (Either (Pos, [Char]) [n])
decodeLoader Loader Identity (Node Pos)
failsafeLoader ByteString
bs0)
where
failsafeLoader :: Loader Identity (Node Pos)
failsafeLoader = Loader { yScalar :: Tag -> ScalarStyle -> Text -> LoaderT Identity (Node Pos)
yScalar = \Tag
t ScalarStyle
s Text
v Pos
pos-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ case Tag -> ScalarStyle -> Text -> Either [Char] Scalar
schemaResolverScalar Tag
t ScalarStyle
s Text
v of
Left [Char]
e -> (Pos, [Char]) -> Either (Pos, [Char]) (Node Pos)
forall a b. a -> Either a b
Left (Pos
pos,[Char]
e)
Right Scalar
v' -> Node Pos -> Either (Pos, [Char]) (Node Pos)
forall a b. b -> Either a b
Right (Pos -> Scalar -> Node Pos
forall loc. loc -> Scalar -> Node loc
Scalar Pos
pos Scalar
v')
, ySequence :: Tag -> [Node Pos] -> LoaderT Identity (Node Pos)
ySequence = \Tag
t [Node Pos]
vs Pos
pos -> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ case Tag -> Either [Char] Tag
schemaResolverSequence Tag
t of
Left [Char]
e -> (Pos, [Char]) -> Either (Pos, [Char]) (Node Pos)
forall a b. a -> Either a b
Left (Pos
pos,[Char]
e)
Right Tag
t' -> Node Pos -> Either (Pos, [Char]) (Node Pos)
forall a b. b -> Either a b
Right (Pos -> Tag -> [Node Pos] -> Node Pos
forall loc. loc -> Tag -> [Node loc] -> Node loc
Sequence Pos
pos Tag
t' [Node Pos]
vs)
, yMapping :: Tag -> [(Node Pos, Node Pos)] -> LoaderT Identity (Node Pos)
yMapping = \Tag
t [(Node Pos, Node Pos)]
kvs Pos
pos-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ case Tag -> Either [Char] Tag
schemaResolverMapping Tag
t of
Left [Char]
e -> (Pos, [Char]) -> Either (Pos, [Char]) (Node Pos)
forall a b. a -> Either a b
Left (Pos
pos,[Char]
e)
Right Tag
t' -> Pos -> Tag -> Mapping Pos -> Node Pos
forall loc. loc -> Tag -> Mapping loc -> Node loc
Mapping Pos
pos Tag
t' (Mapping Pos -> Node Pos)
-> Either (Pos, [Char]) (Mapping Pos)
-> Either (Pos, [Char]) (Node Pos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Node Pos, Node Pos)] -> Either (Pos, [Char]) (Mapping Pos)
mkMap [(Node Pos, Node Pos)]
kvs
, yAlias :: NodeId -> Bool -> Node Pos -> LoaderT Identity (Node Pos)
yAlias = if Bool
allowCycles
then \NodeId
_ Bool
_ Node Pos
n Pos
_-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ Node Pos -> Either (Pos, [Char]) (Node Pos)
forall a b. b -> Either a b
Right Node Pos
n
else \NodeId
_ Bool
c Node Pos
n Pos
pos -> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ if Bool
c then (Pos, [Char]) -> Either (Pos, [Char]) (Node Pos)
forall a b. a -> Either a b
Left (Pos
pos,[Char]
"cycle detected") else Node Pos -> Either (Pos, [Char]) (Node Pos)
forall a b. b -> Either a b
Right Node Pos
n
, yAnchor :: NodeId -> Node Pos -> LoaderT Identity (Node Pos)
yAnchor = if Bool
anchorNodes
then \NodeId
j Node Pos
n Pos
pos -> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ Node Pos -> Either (Pos, [Char]) (Node Pos)
forall a b. b -> Either a b
Right (Pos -> NodeId -> Node Pos -> Node Pos
forall loc. loc -> NodeId -> Node loc -> Node loc
Anchor Pos
pos NodeId
j Node Pos
n)
else \NodeId
_ Node Pos
n Pos
_ -> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a. a -> Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos)))
-> Either (Pos, [Char]) (Node Pos)
-> Identity (Either (Pos, [Char]) (Node Pos))
forall a b. (a -> b) -> a -> b
$ Node Pos -> Either (Pos, [Char]) (Node Pos)
forall a b. b -> Either a b
Right Node Pos
n
}
mkMap :: [(Node Pos, Node Pos)] -> Either (Pos, String) (Map (Node Pos) (Node Pos))
mkMap :: [(Node Pos, Node Pos)] -> Either (Pos, [Char]) (Mapping Pos)
mkMap [(Node Pos, Node Pos)]
kvs
| Bool
schemaResolverMappingDuplicates = Mapping Pos -> Either (Pos, [Char]) (Mapping Pos)
forall a b. b -> Either a b
Right (Mapping Pos -> Either (Pos, [Char]) (Mapping Pos))
-> Mapping Pos -> Either (Pos, [Char]) (Mapping Pos)
forall a b. (a -> b) -> a -> b
$! [(Node Pos, Node Pos)] -> Mapping Pos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Node Pos, Node Pos)]
kvs
| Bool
otherwise = case [(Node Pos, Node Pos)] -> Either (Node Pos, Node Pos) (Mapping Pos)
forall k a. Ord k => [(k, a)] -> Either (k, a) (Map k a)
mapFromListNoDupes [(Node Pos, Node Pos)]
kvs of
Left (Node Pos
k,Node Pos
_) -> (Pos, [Char]) -> Either (Pos, [Char]) (Mapping Pos)
forall a b. a -> Either a b
Left (Node Pos -> Pos
forall loc. Node loc -> loc
nodeLoc Node Pos
k,[Char]
"Duplicate key in mapping: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Node Pos -> [Char]
forall a. Show a => a -> [Char]
show Node Pos
k)
Right Mapping Pos
m -> Mapping Pos -> Either (Pos, [Char]) (Mapping Pos)
forall a b. b -> Either a b
Right Mapping Pos
m
newtype Parser a = P { forall a. Parser a -> Either (Pos, [Char]) a
unP :: Either (Pos, String) a }
instance Functor Parser where
fmap :: forall a b. (a -> b) -> Parser a -> Parser b
fmap a -> b
f (P Either (Pos, [Char]) a
x) = Either (Pos, [Char]) b -> Parser b
forall a. Either (Pos, [Char]) a -> Parser a
P ((a -> b) -> Either (Pos, [Char]) a -> Either (Pos, [Char]) b
forall a b.
(a -> b) -> Either (Pos, [Char]) a -> Either (Pos, [Char]) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Either (Pos, [Char]) a
x)
a
x <$ :: forall a b. a -> Parser b -> Parser a
<$ P (Right b
_) = Either (Pos, [Char]) a -> Parser a
forall a. Either (Pos, [Char]) a -> Parser a
P (a -> Either (Pos, [Char]) a
forall a b. b -> Either a b
Right a
x)
a
_ <$ P (Left (Pos, [Char])
e) = Either (Pos, [Char]) a -> Parser a
forall a. Either (Pos, [Char]) a -> Parser a
P ((Pos, [Char]) -> Either (Pos, [Char]) a
forall a b. a -> Either a b
Left (Pos, [Char])
e)
instance Applicative Parser where
pure :: forall a. a -> Parser a
pure = Either (Pos, [Char]) a -> Parser a
forall a. Either (Pos, [Char]) a -> Parser a
P (Either (Pos, [Char]) a -> Parser a)
-> (a -> Either (Pos, [Char]) a) -> a -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Either (Pos, [Char]) a
forall a b. b -> Either a b
Right
P (Left (Pos, [Char])
e) <*> :: forall a b. Parser (a -> b) -> Parser a -> Parser b
<*> Parser a
_ = Either (Pos, [Char]) b -> Parser b
forall a. Either (Pos, [Char]) a -> Parser a
P ((Pos, [Char]) -> Either (Pos, [Char]) b
forall a b. a -> Either a b
Left (Pos, [Char])
e)
P (Right a -> b
f) <*> P Either (Pos, [Char]) a
r = Either (Pos, [Char]) b -> Parser b
forall a. Either (Pos, [Char]) a -> Parser a
P ((a -> b) -> Either (Pos, [Char]) a -> Either (Pos, [Char]) b
forall a b.
(a -> b) -> Either (Pos, [Char]) a -> Either (Pos, [Char]) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Either (Pos, [Char]) a
r)
P (Left (Pos, [Char])
e) *> :: forall a b. Parser a -> Parser b -> Parser b
*> Parser b
_ = Either (Pos, [Char]) b -> Parser b
forall a. Either (Pos, [Char]) a -> Parser a
P ((Pos, [Char]) -> Either (Pos, [Char]) b
forall a b. a -> Either a b
Left (Pos, [Char])
e)
P (Right a
_) *> Parser b
p = Parser b
p
instance Monad Parser where
return :: forall a. a -> Parser a
return = a -> Parser a
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
P Either (Pos, [Char]) a
m >>= :: forall a b. Parser a -> (a -> Parser b) -> Parser b
>>= a -> Parser b
k = Either (Pos, [Char]) b -> Parser b
forall a. Either (Pos, [Char]) a -> Parser a
P (Either (Pos, [Char]) a
m Either (Pos, [Char]) a
-> (a -> Either (Pos, [Char]) b) -> Either (Pos, [Char]) b
forall a b.
Either (Pos, [Char]) a
-> (a -> Either (Pos, [Char]) b) -> Either (Pos, [Char]) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Parser b -> Either (Pos, [Char]) b
forall a. Parser a -> Either (Pos, [Char]) a
unP (Parser b -> Either (Pos, [Char]) b)
-> (a -> Parser b) -> a -> Either (Pos, [Char]) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Parser b
k)
>> :: forall a b. Parser a -> Parser b -> Parser b
(>>) = Parser a -> Parser b -> Parser b
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
#if !(MIN_VERSION_base(4,13,0))
fail = Fail.fail
#endif
instance Fail.MonadFail Parser where
fail :: forall a. [Char] -> Parser a
fail [Char]
s = Either (Pos, [Char]) a -> Parser a
forall a. Either (Pos, [Char]) a -> Parser a
P ((Pos, [Char]) -> Either (Pos, [Char]) a
forall a b. a -> Either a b
Left (Pos
fakePos, [Char]
s))
failAtNode :: Node Pos -> String -> Parser a
failAtNode :: forall a. Node Pos -> [Char] -> Parser a
failAtNode Node Pos
n [Char]
s = Either (Pos, [Char]) a -> Parser a
forall a. Either (Pos, [Char]) a -> Parser a
P ((Pos, [Char]) -> Either (Pos, [Char]) a
forall a b. a -> Either a b
Left (Node Pos -> Pos
forall loc. Node loc -> loc
nodeLoc Node Pos
n, [Char]
s))
instance Alternative Parser where
empty :: forall a. Parser a
empty = [Char] -> Parser a
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"empty"
P (Left (Pos, [Char])
_) <|> :: forall a. Parser a -> Parser a -> Parser a
<|> Parser a
y = Parser a
y
Parser a
x <|> Parser a
_ = Parser a
x
instance MonadPlus Parser where
mzero :: forall a. Parser a
mzero = Parser a
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
mplus :: forall a. Parser a -> Parser a -> Parser a
mplus = Parser a -> Parser a -> Parser a
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
parseEither :: Parser a -> Either (Pos, String) a
parseEither :: forall a. Parser a -> Either (Pos, [Char]) a
parseEither = Parser a -> Either (Pos, [Char]) a
forall a. Parser a -> Either (Pos, [Char]) a
unP
typeMismatch :: String
-> Node Pos
-> Parser a
typeMismatch :: forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
node = Node Pos -> [Char] -> Parser a
forall a. Node Pos -> [Char] -> Parser a
failAtNode Node Pos
node ([Char]
"expected " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
expected [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" instead of " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
got)
where
got :: [Char]
got = case Node Pos
node of
Scalar Pos
_ (SBool Bool
_) -> [Char]
"!!bool"
Scalar Pos
_ (SInt Integer
_) -> [Char]
"!!int"
Scalar Pos
_ Scalar
SNull -> [Char]
"!!null"
Scalar Pos
_ (SStr Text
_) -> [Char]
"!!str"
Scalar Pos
_ (SFloat Double
_) -> [Char]
"!!float"
Scalar Pos
_ (SUnknown Tag
t Text
v)
| Tag -> Bool
isUntagged Tag
t -> Tag -> [Char]
tagged Tag
t [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show Text
v
| Bool
otherwise -> [Char]
"(unsupported) " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Tag -> [Char]
tagged Tag
t [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"scalar"
Anchor Pos
_ NodeId
_ Node Pos
_ -> [Char]
"anchor"
Mapping Pos
_ Tag
t Mapping Pos
_ -> Tag -> [Char]
tagged Tag
t [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" mapping"
Sequence Pos
_ Tag
t [Node Pos]
_ -> Tag -> [Char]
tagged Tag
t [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" sequence"
tagged :: Tag -> [Char]
tagged Tag
t0 = case Tag -> Maybe Text
tagToText Tag
t0 of
Maybe Text
Nothing -> [Char]
"non-specifically ? tagged (i.e. unresolved) "
Just Text
t -> Text -> [Char]
T.unpack Text
t [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" tagged"
class FromYAML a where
parseYAML :: Node Pos -> Parser a
{-# INLINE fixupFailPos #-}
fixupFailPos :: Pos -> Parser a -> Parser a
fixupFailPos :: forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (P (Left (Pos
pos0,[Char]
emsg)))
| Pos
pos0 Pos -> Pos -> Bool
forall a. Eq a => a -> a -> Bool
== Pos
fakePos = Either (Pos, [Char]) a -> Parser a
forall a. Either (Pos, [Char]) a -> Parser a
P ((Pos, [Char]) -> Either (Pos, [Char]) a
forall a b. a -> Either a b
Left (Pos
pos,[Char]
emsg))
fixupFailPos Pos
_ Parser a
p = Parser a
p
withNull :: String -> Parser a -> Node Pos -> Parser a
withNull :: forall a. [Char] -> Parser a -> Node Pos -> Parser a
withNull [Char]
_ Parser a
f (Scalar Pos
pos Scalar
SNull) = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos Parser a
f
withNull [Char]
expected Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
withScalar :: String -> (Scalar -> Parser a) -> Node Pos -> Parser a
withScalar :: forall a. [Char] -> (Scalar -> Parser a) -> Node Pos -> Parser a
withScalar [Char]
_ Scalar -> Parser a
f (Scalar Pos
pos Scalar
sca) = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (Scalar -> Parser a
f Scalar
sca)
withScalar [Char]
expected Scalar -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance (loc ~ Pos) => FromYAML (Node loc) where
parseYAML :: Node Pos -> Parser (Node loc)
parseYAML = Node Pos -> Parser (Node loc)
Node Pos -> Parser (Node Pos)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance FromYAML Scalar where
parseYAML :: Node Pos -> Parser Scalar
parseYAML = [Char] -> (Scalar -> Parser Scalar) -> Node Pos -> Parser Scalar
forall a. [Char] -> (Scalar -> Parser a) -> Node Pos -> Parser a
withScalar [Char]
"scalar" Scalar -> Parser Scalar
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance FromYAML Bool where
parseYAML :: Node Pos -> Parser Bool
parseYAML = [Char] -> (Bool -> Parser Bool) -> Node Pos -> Parser Bool
forall a. [Char] -> (Bool -> Parser a) -> Node Pos -> Parser a
withBool [Char]
"!!bool" Bool -> Parser Bool
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
withBool :: String -> (Bool -> Parser a) -> Node Pos -> Parser a
withBool :: forall a. [Char] -> (Bool -> Parser a) -> Node Pos -> Parser a
withBool [Char]
_ Bool -> Parser a
f (Scalar Pos
pos (SBool Bool
b)) = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (Bool -> Parser a
f Bool
b)
withBool [Char]
expected Bool -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance FromYAML Text where
parseYAML :: Node Pos -> Parser Text
parseYAML = [Char] -> (Text -> Parser Text) -> Node Pos -> Parser Text
forall a. [Char] -> (Text -> Parser a) -> Node Pos -> Parser a
withStr [Char]
"!!str" Text -> Parser Text
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
withStr :: String -> (Text -> Parser a) -> Node Pos -> Parser a
withStr :: forall a. [Char] -> (Text -> Parser a) -> Node Pos -> Parser a
withStr [Char]
_ Text -> Parser a
f (Scalar Pos
pos (SStr Text
b)) = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (Text -> Parser a
f Text
b)
withStr [Char]
expected Text -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance FromYAML Integer where
parseYAML :: Node Pos -> Parser Integer
parseYAML = [Char] -> (Integer -> Parser Integer) -> Node Pos -> Parser Integer
forall a. [Char] -> (Integer -> Parser a) -> Node Pos -> Parser a
withInt [Char]
"!!int" Integer -> Parser Integer
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
withInt :: String -> (Integer -> Parser a) -> Node Pos -> Parser a
withInt :: forall a. [Char] -> (Integer -> Parser a) -> Node Pos -> Parser a
withInt [Char]
_ Integer -> Parser a
f (Scalar Pos
pos (SInt Integer
b)) = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (Integer -> Parser a
f Integer
b)
withInt [Char]
expected Integer -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance FromYAML Natural where
parseYAML :: Node Pos -> Parser Natural
parseYAML = [Char] -> (Integer -> Parser Natural) -> Node Pos -> Parser Natural
forall a. [Char] -> (Integer -> Parser a) -> Node Pos -> Parser a
withInt [Char]
"!!int" ((Integer -> Parser Natural) -> Node Pos -> Parser Natural)
-> (Integer -> Parser Natural) -> Node Pos -> Parser Natural
forall a b. (a -> b) -> a -> b
$ \Integer
b -> if Integer
b Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 then [Char] -> Parser Natural
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"!!int " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
b [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" out of range for 'Natural'")
else Natural -> Parser Natural
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Natural
forall a. Num a => Integer -> a
fromInteger Integer
b)
{-# INLINE parseInt #-}
parseInt :: (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt :: forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
name = [Char] -> (Integer -> Parser a) -> Node Pos -> Parser a
forall a. [Char] -> (Integer -> Parser a) -> Node Pos -> Parser a
withInt [Char]
"!!int" ((Integer -> Parser a) -> Node Pos -> Parser a)
-> (Integer -> Parser a) -> Node Pos -> Parser a
forall a b. (a -> b) -> a -> b
$ \Integer
b -> Parser a -> (a -> Parser a) -> Maybe a -> Parser a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Parser a
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> Parser a) -> [Char] -> Parser a
forall a b. (a -> b) -> a -> b
$ [Char]
"!!int " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
b [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" out of range for '" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
name [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'") a -> Parser a
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe a -> Parser a) -> Maybe a -> Parser a
forall a b. (a -> b) -> a -> b
$
Integer -> Maybe a
forall n. (Integral n, Bounded n) => Integer -> Maybe n
fromIntegerMaybe Integer
b
instance FromYAML Int where parseYAML :: Node Pos -> Parser Int
parseYAML = [Char] -> Node Pos -> Parser Int
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Int"
instance FromYAML Int8 where parseYAML :: Node Pos -> Parser Int8
parseYAML = [Char] -> Node Pos -> Parser Int8
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Int8"
instance FromYAML Int16 where parseYAML :: Node Pos -> Parser Int16
parseYAML = [Char] -> Node Pos -> Parser Int16
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Int16"
instance FromYAML Int32 where parseYAML :: Node Pos -> Parser Int32
parseYAML = [Char] -> Node Pos -> Parser Int32
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Int32"
instance FromYAML Int64 where parseYAML :: Node Pos -> Parser Int64
parseYAML = [Char] -> Node Pos -> Parser Int64
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Int64"
instance FromYAML Word where parseYAML :: Node Pos -> Parser NodeId
parseYAML = [Char] -> Node Pos -> Parser NodeId
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Word"
instance FromYAML Word8 where parseYAML :: Node Pos -> Parser Word8
parseYAML = [Char] -> Node Pos -> Parser Word8
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Word8"
instance FromYAML Word16 where parseYAML :: Node Pos -> Parser Word16
parseYAML = [Char] -> Node Pos -> Parser Word16
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Word16"
instance FromYAML Word32 where parseYAML :: Node Pos -> Parser Word32
parseYAML = [Char] -> Node Pos -> Parser Word32
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Word32"
instance FromYAML Word64 where parseYAML :: Node Pos -> Parser Word64
parseYAML = [Char] -> Node Pos -> Parser Word64
forall a. (Integral a, Bounded a) => [Char] -> Node Pos -> Parser a
parseInt [Char]
"Word64"
instance FromYAML Double where
parseYAML :: Node Pos -> Parser Double
parseYAML = [Char] -> (Double -> Parser Double) -> Node Pos -> Parser Double
forall a. [Char] -> (Double -> Parser a) -> Node Pos -> Parser a
withFloat [Char]
"!!float" Double -> Parser Double
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
withFloat :: String -> (Double -> Parser a) -> Node Pos -> Parser a
withFloat :: forall a. [Char] -> (Double -> Parser a) -> Node Pos -> Parser a
withFloat [Char]
_ Double -> Parser a
f (Scalar Pos
pos (SFloat Double
b)) = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (Double -> Parser a
f Double
b)
withFloat [Char]
expected Double -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance (Ord k, FromYAML k, FromYAML v) => FromYAML (Map k v) where
parseYAML :: Node Pos -> Parser (Map k v)
parseYAML = [Char]
-> (Mapping Pos -> Parser (Map k v))
-> Node Pos
-> Parser (Map k v)
forall a.
[Char] -> (Mapping Pos -> Parser a) -> Node Pos -> Parser a
withMap [Char]
"!!map" ((Mapping Pos -> Parser (Map k v)) -> Node Pos -> Parser (Map k v))
-> (Mapping Pos -> Parser (Map k v))
-> Node Pos
-> Parser (Map k v)
forall a b. (a -> b) -> a -> b
$ \Mapping Pos
xs -> [(k, v)] -> Map k v
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(k, v)] -> Map k v) -> Parser [(k, v)] -> Parser (Map k v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Node Pos, Node Pos) -> Parser (k, v))
-> [(Node Pos, Node Pos)] -> Parser [(k, v)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(Node Pos
a,Node Pos
b) -> (,) (k -> v -> (k, v)) -> Parser k -> Parser (v -> (k, v))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser k
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a Parser (v -> (k, v)) -> Parser v -> Parser (k, v)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser v
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b) (Mapping Pos -> [(Node Pos, Node Pos)]
forall k a. Map k a -> [(k, a)]
Map.toList Mapping Pos
xs)
withMap :: String -> (Mapping Pos -> Parser a) -> Node Pos -> Parser a
withMap :: forall a.
[Char] -> (Mapping Pos -> Parser a) -> Node Pos -> Parser a
withMap [Char]
_ Mapping Pos -> Parser a
f (Mapping Pos
pos Tag
tag Mapping Pos
xs)
| Tag
tag Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
tagMap = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos (Mapping Pos -> Parser a
f Mapping Pos
xs)
withMap [Char]
expected Mapping Pos -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance FromYAML v => FromYAML [v] where
parseYAML :: Node Pos -> Parser [v]
parseYAML = [Char] -> ([Node Pos] -> Parser [v]) -> Node Pos -> Parser [v]
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" ((Node Pos -> Parser v) -> [Node Pos] -> Parser [v]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Node Pos -> Parser v
forall a. FromYAML a => Node Pos -> Parser a
parseYAML)
withSeq :: String -> ([Node Pos] -> Parser a) -> Node Pos-> Parser a
withSeq :: forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
_ [Node Pos] -> Parser a
f (Sequence Pos
pos Tag
tag [Node Pos]
xs)
| Tag
tag Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Tag
tagSeq = Pos -> Parser a -> Parser a
forall a. Pos -> Parser a -> Parser a
fixupFailPos Pos
pos ([Node Pos] -> Parser a
f [Node Pos]
xs)
withSeq [Char]
expected [Node Pos] -> Parser a
_ Node Pos
v = [Char] -> Node Pos -> Parser a
forall a. [Char] -> Node Pos -> Parser a
typeMismatch [Char]
expected Node Pos
v
instance FromYAML a => FromYAML (Maybe a) where
parseYAML :: Node Pos -> Parser (Maybe a)
parseYAML (Scalar Pos
_ Scalar
SNull) = Maybe a -> Parser (Maybe a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
parseYAML Node Pos
j = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Parser a -> Parser (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
j
instance (FromYAML a, FromYAML b) => FromYAML (a,b) where
parseYAML :: Node Pos -> Parser (a, b)
parseYAML = [Char]
-> ([Node Pos] -> Parser (a, b)) -> Node Pos -> Parser (a, b)
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" (([Node Pos] -> Parser (a, b)) -> Node Pos -> Parser (a, b))
-> ([Node Pos] -> Parser (a, b)) -> Node Pos -> Parser (a, b)
forall a b. (a -> b) -> a -> b
$ \[Node Pos]
xs ->
case [Node Pos]
xs of
[Node Pos
a,Node Pos
b] -> (,) (a -> b -> (a, b)) -> Parser a -> Parser (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a
Parser (b -> (a, b)) -> Parser b -> Parser (a, b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser b
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b
[Node Pos]
_ -> [Char] -> Parser (a, b)
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"expected 2-sequence but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show ([Node Pos] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node Pos]
xs) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c) => FromYAML (a,b,c) where
parseYAML :: Node Pos -> Parser (a, b, c)
parseYAML = [Char]
-> ([Node Pos] -> Parser (a, b, c)) -> Node Pos -> Parser (a, b, c)
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" (([Node Pos] -> Parser (a, b, c)) -> Node Pos -> Parser (a, b, c))
-> ([Node Pos] -> Parser (a, b, c)) -> Node Pos -> Parser (a, b, c)
forall a b. (a -> b) -> a -> b
$ \[Node Pos]
xs ->
case [Node Pos]
xs of
[Node Pos
a,Node Pos
b,Node Pos
c] -> (,,) (a -> b -> c -> (a, b, c))
-> Parser a -> Parser (b -> c -> (a, b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a
Parser (b -> c -> (a, b, c)) -> Parser b -> Parser (c -> (a, b, c))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser b
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b
Parser (c -> (a, b, c)) -> Parser c -> Parser (a, b, c)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser c
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
c
[Node Pos]
_ -> [Char] -> Parser (a, b, c)
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"expected 3-sequence but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show ([Node Pos] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node Pos]
xs) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d) => FromYAML (a,b,c,d) where
parseYAML :: Node Pos -> Parser (a, b, c, d)
parseYAML = [Char]
-> ([Node Pos] -> Parser (a, b, c, d))
-> Node Pos
-> Parser (a, b, c, d)
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" (([Node Pos] -> Parser (a, b, c, d))
-> Node Pos -> Parser (a, b, c, d))
-> ([Node Pos] -> Parser (a, b, c, d))
-> Node Pos
-> Parser (a, b, c, d)
forall a b. (a -> b) -> a -> b
$ \[Node Pos]
xs ->
case [Node Pos]
xs of
[Node Pos
a,Node Pos
b,Node Pos
c,Node Pos
d] -> (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> Parser a -> Parser (b -> c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a
Parser (b -> c -> d -> (a, b, c, d))
-> Parser b -> Parser (c -> d -> (a, b, c, d))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser b
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b
Parser (c -> d -> (a, b, c, d))
-> Parser c -> Parser (d -> (a, b, c, d))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser c
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
c
Parser (d -> (a, b, c, d)) -> Parser d -> Parser (a, b, c, d)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser d
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
d
[Node Pos]
_ -> [Char] -> Parser (a, b, c, d)
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"expected 4-sequence but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show ([Node Pos] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node Pos]
xs) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e) => FromYAML (a,b,c,d,e) where
parseYAML :: Node Pos -> Parser (a, b, c, d, e)
parseYAML = [Char]
-> ([Node Pos] -> Parser (a, b, c, d, e))
-> Node Pos
-> Parser (a, b, c, d, e)
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" (([Node Pos] -> Parser (a, b, c, d, e))
-> Node Pos -> Parser (a, b, c, d, e))
-> ([Node Pos] -> Parser (a, b, c, d, e))
-> Node Pos
-> Parser (a, b, c, d, e)
forall a b. (a -> b) -> a -> b
$ \[Node Pos]
xs ->
case [Node Pos]
xs of
[Node Pos
a,Node Pos
b,Node Pos
c,Node Pos
d,Node Pos
e] -> (,,,,) (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Parser a -> Parser (b -> c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a
Parser (b -> c -> d -> e -> (a, b, c, d, e))
-> Parser b -> Parser (c -> d -> e -> (a, b, c, d, e))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser b
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b
Parser (c -> d -> e -> (a, b, c, d, e))
-> Parser c -> Parser (d -> e -> (a, b, c, d, e))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser c
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
c
Parser (d -> e -> (a, b, c, d, e))
-> Parser d -> Parser (e -> (a, b, c, d, e))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser d
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
d
Parser (e -> (a, b, c, d, e)) -> Parser e -> Parser (a, b, c, d, e)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser e
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
e
[Node Pos]
_ -> [Char] -> Parser (a, b, c, d, e)
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"expected 5-sequence but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show ([Node Pos] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node Pos]
xs) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e, FromYAML f) => FromYAML (a,b,c,d,e,f) where
parseYAML :: Node Pos -> Parser (a, b, c, d, e, f)
parseYAML = [Char]
-> ([Node Pos] -> Parser (a, b, c, d, e, f))
-> Node Pos
-> Parser (a, b, c, d, e, f)
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" (([Node Pos] -> Parser (a, b, c, d, e, f))
-> Node Pos -> Parser (a, b, c, d, e, f))
-> ([Node Pos] -> Parser (a, b, c, d, e, f))
-> Node Pos
-> Parser (a, b, c, d, e, f)
forall a b. (a -> b) -> a -> b
$ \[Node Pos]
xs ->
case [Node Pos]
xs of
[Node Pos
a,Node Pos
b,Node Pos
c,Node Pos
d,Node Pos
e,Node Pos
f] -> (,,,,,) (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Parser a -> Parser (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a
Parser (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Parser b -> Parser (c -> d -> e -> f -> (a, b, c, d, e, f))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser b
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b
Parser (c -> d -> e -> f -> (a, b, c, d, e, f))
-> Parser c -> Parser (d -> e -> f -> (a, b, c, d, e, f))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser c
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
c
Parser (d -> e -> f -> (a, b, c, d, e, f))
-> Parser d -> Parser (e -> f -> (a, b, c, d, e, f))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser d
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
d
Parser (e -> f -> (a, b, c, d, e, f))
-> Parser e -> Parser (f -> (a, b, c, d, e, f))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser e
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
e
Parser (f -> (a, b, c, d, e, f))
-> Parser f -> Parser (a, b, c, d, e, f)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser f
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
f
[Node Pos]
_ -> [Char] -> Parser (a, b, c, d, e, f)
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"expected 6-sequence but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show ([Node Pos] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node Pos]
xs) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e, FromYAML f, FromYAML g) => FromYAML (a,b,c,d,e,f,g) where
parseYAML :: Node Pos -> Parser (a, b, c, d, e, f, g)
parseYAML = [Char]
-> ([Node Pos] -> Parser (a, b, c, d, e, f, g))
-> Node Pos
-> Parser (a, b, c, d, e, f, g)
forall a.
[Char] -> ([Node Pos] -> Parser a) -> Node Pos -> Parser a
withSeq [Char]
"!!seq" (([Node Pos] -> Parser (a, b, c, d, e, f, g))
-> Node Pos -> Parser (a, b, c, d, e, f, g))
-> ([Node Pos] -> Parser (a, b, c, d, e, f, g))
-> Node Pos
-> Parser (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \[Node Pos]
xs ->
case [Node Pos]
xs of
[Node Pos
a,Node Pos
b,Node Pos
c,Node Pos
d,Node Pos
e,Node Pos
f,Node Pos
g] -> (,,,,,,) (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser a
-> Parser (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node Pos -> Parser a
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
a
Parser (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser b
-> Parser (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser b
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
b
Parser (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser c -> Parser (d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser c
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
c
Parser (d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser d -> Parser (e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser d
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
d
Parser (e -> f -> g -> (a, b, c, d, e, f, g))
-> Parser e -> Parser (f -> g -> (a, b, c, d, e, f, g))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser e
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
e
Parser (f -> g -> (a, b, c, d, e, f, g))
-> Parser f -> Parser (g -> (a, b, c, d, e, f, g))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser f
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
f
Parser (g -> (a, b, c, d, e, f, g))
-> Parser g -> Parser (a, b, c, d, e, f, g)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Node Pos -> Parser g
forall a. FromYAML a => Node Pos -> Parser a
parseYAML Node Pos
g
[Node Pos]
_ -> [Char] -> Parser (a, b, c, d, e, f, g)
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char]
"expected 7-sequence but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show ([Node Pos] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node Pos]
xs) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"-sequence instead")
decode :: FromYAML v => BS.L.ByteString -> Either (Pos, String) [v]
decode :: forall v. FromYAML v => ByteString -> Either (Pos, [Char]) [v]
decode ByteString
bs0 = ByteString -> Either (Pos, [Char]) [Doc (Node Pos)]
decodeNode ByteString
bs0 Either (Pos, [Char]) [Doc (Node Pos)]
-> ([Doc (Node Pos)] -> Either (Pos, [Char]) [v])
-> Either (Pos, [Char]) [v]
forall a b.
Either (Pos, [Char]) a
-> (a -> Either (Pos, [Char]) b) -> Either (Pos, [Char]) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Doc (Node Pos) -> Either (Pos, [Char]) v)
-> [Doc (Node Pos)] -> Either (Pos, [Char]) [v]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Parser v -> Either (Pos, [Char]) v
forall a. Parser a -> Either (Pos, [Char]) a
parseEither (Parser v -> Either (Pos, [Char]) v)
-> (Doc (Node Pos) -> Parser v)
-> Doc (Node Pos)
-> Either (Pos, [Char]) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node Pos -> Parser v
forall a. FromYAML a => Node Pos -> Parser a
parseYAML (Node Pos -> Parser v)
-> (Doc (Node Pos) -> Node Pos) -> Doc (Node Pos) -> Parser v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\(Doc Node Pos
x) -> Node Pos
x))
decode1 :: FromYAML v => BS.L.ByteString -> Either (Pos, String) v
decode1 :: forall v. FromYAML v => ByteString -> Either (Pos, [Char]) v
decode1 ByteString
bs0 = do
[Doc (Node Pos)]
docs <- ByteString -> Either (Pos, [Char]) [Doc (Node Pos)]
decodeNode ByteString
bs0
case [Doc (Node Pos)]
docs of
[] -> (Pos, [Char]) -> Either (Pos, [Char]) v
forall a b. a -> Either a b
Left (Pos { posByteOffset :: Int
posByteOffset = Int
0, posCharOffset :: Int
posCharOffset = Int
0, posLine :: Int
posLine = Int
1, posColumn :: Int
posColumn = Int
0 }, [Char]
"empty YAML stream")
[Doc Node Pos
v] -> Parser v -> Either (Pos, [Char]) v
forall a. Parser a -> Either (Pos, [Char]) a
parseEither (Parser v -> Either (Pos, [Char]) v)
-> Parser v -> Either (Pos, [Char]) v
forall a b. (a -> b) -> a -> b
$ Node Pos -> Parser v
forall a. FromYAML a => Node Pos -> Parser a
parseYAML (Node Pos -> Parser v) -> Node Pos -> Parser v
forall a b. (a -> b) -> a -> b
$ Node Pos
v
(Doc (Node Pos)
_:Doc Node Pos
n:[Doc (Node Pos)]
_) -> (Pos, [Char]) -> Either (Pos, [Char]) v
forall a b. a -> Either a b
Left (Node Pos -> Pos
forall loc. Node loc -> loc
nodeLoc Node Pos
n, [Char]
"unexpected multiple YAML documents")
decodeStrict :: FromYAML v => BS.ByteString -> Either (Pos, String) [v]
decodeStrict :: forall v. FromYAML v => ByteString -> Either (Pos, [Char]) [v]
decodeStrict = ByteString -> Either (Pos, [Char]) [v]
forall v. FromYAML v => ByteString -> Either (Pos, [Char]) [v]
decode (ByteString -> Either (Pos, [Char]) [v])
-> (ByteString -> ByteString)
-> ByteString
-> Either (Pos, [Char]) [v]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BS.L.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])
decode1Strict :: FromYAML v => BS.ByteString -> Either (Pos, String) v
decode1Strict :: forall v. FromYAML v => ByteString -> Either (Pos, [Char]) v
decode1Strict = ByteString -> Either (Pos, [Char]) v
forall v. FromYAML v => ByteString -> Either (Pos, [Char]) v
decode1 (ByteString -> Either (Pos, [Char]) v)
-> (ByteString -> ByteString)
-> ByteString
-> Either (Pos, [Char]) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BS.L.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])
class ToYAML a where
toYAML :: a -> Node ()
instance Loc loc => ToYAML (Node loc) where
toYAML :: Node loc -> Node ()
toYAML = Node loc -> Node ()
forall loc (f :: * -> *). (Loc loc, Functor f) => f loc -> f ()
forall (f :: * -> *). Functor f => f loc -> f ()
toUnit
instance ToYAML Bool where
toYAML :: Bool -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Bool -> Scalar) -> Bool -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Scalar
SBool
instance ToYAML Double where
toYAML :: Double -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Double -> Scalar) -> Double -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Scalar
SFloat
instance ToYAML Int where toYAML :: Int -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Int -> Scalar) -> Int -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Int -> Integer) -> Int -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Int8 where toYAML :: Int8 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Int8 -> Scalar) -> Int8 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Int8 -> Integer) -> Int8 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Int16 where toYAML :: Int16 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Int16 -> Scalar) -> Int16 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Int16 -> Integer) -> Int16 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Int32 where toYAML :: Int32 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Int32 -> Scalar) -> Int32 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Int32 -> Integer) -> Int32 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Int64 where toYAML :: Int64 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Int64 -> Scalar) -> Int64 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Int64 -> Integer) -> Int64 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Word where toYAML :: NodeId -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (NodeId -> Scalar) -> NodeId -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (NodeId -> Integer) -> NodeId -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeId -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Word8 where toYAML :: Word8 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Word8 -> Scalar) -> Word8 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Word8 -> Integer) -> Word8 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Word16 where toYAML :: Word16 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Word16 -> Scalar) -> Word16 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Word16 -> Integer) -> Word16 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Word32 where toYAML :: Word32 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Word32 -> Scalar) -> Word32 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Word32 -> Integer) -> Word32 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Word64 where toYAML :: Word64 -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Word64 -> Scalar) -> Word64 -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Word64 -> Integer) -> Word64 -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Natural where toYAML :: Natural -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Natural -> Scalar) -> Natural -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt (Integer -> Scalar) -> (Natural -> Integer) -> Natural -> Scalar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Integer
forall a. Integral a => a -> Integer
toInteger
instance ToYAML Integer where toYAML :: Integer -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Integer -> Scalar) -> Integer -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scalar
SInt
instance ToYAML Text where
toYAML :: Text -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () (Scalar -> Node ()) -> (Text -> Scalar) -> Text -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Scalar
SStr
instance ToYAML Scalar where
toYAML :: Scalar -> Node ()
toYAML = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar ()
instance ToYAML a => ToYAML (Maybe a) where
toYAML :: Maybe a -> Node ()
toYAML Maybe a
Nothing = () -> Scalar -> Node ()
forall loc. loc -> Scalar -> Node loc
Scalar () Scalar
SNull
toYAML (Just a
a) = a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a
instance ToYAML a => ToYAML [a] where
toYAML :: [a] -> Node ()
toYAML = () -> Tag -> [Node ()] -> Node ()
forall loc. loc -> Tag -> [Node loc] -> Node loc
Sequence () Tag
tagSeq ([Node ()] -> Node ()) -> ([a] -> [Node ()]) -> [a] -> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Node ()) -> [a] -> [Node ()]
forall a b. (a -> b) -> [a] -> [b]
map a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML
instance (Ord k, ToYAML k, ToYAML v) => ToYAML (Map k v) where
toYAML :: Map k v -> Node ()
toYAML Map k v
kv = () -> Tag -> Mapping () -> Node ()
forall loc. loc -> Tag -> Mapping loc -> Node loc
Mapping () Tag
tagMap ([(Node (), Node ())] -> Mapping ()
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Node (), Node ())] -> Mapping ())
-> [(Node (), Node ())] -> Mapping ()
forall a b. (a -> b) -> a -> b
$ ((k, v) -> (Node (), Node ())) -> [(k, v)] -> [(Node (), Node ())]
forall a b. (a -> b) -> [a] -> [b]
map (\(k
k,v
v) -> (k -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML k
k , v -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML v
v)) (Map k v -> [(k, v)]
forall k a. Map k a -> [(k, a)]
Map.toList Map k v
kv))
instance (ToYAML a, ToYAML b) => ToYAML (a, b) where
toYAML :: (a, b) -> Node ()
toYAML (a
a,b
b) = [Node ()] -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML [a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a, b -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML b
b]
instance (ToYAML a, ToYAML b, ToYAML c) => ToYAML (a, b, c) where
toYAML :: (a, b, c) -> Node ()
toYAML (a
a,b
b,c
c) = [Node ()] -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML [a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a, b -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML b
b, c -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML c
c]
instance (ToYAML a, ToYAML b, ToYAML c, ToYAML d) => ToYAML (a, b, c, d) where
toYAML :: (a, b, c, d) -> Node ()
toYAML (a
a,b
b,c
c,d
d) = [Node ()] -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML [a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a, b -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML b
b, c -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML c
c, d -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML d
d]
instance (ToYAML a, ToYAML b, ToYAML c, ToYAML d, ToYAML e) => ToYAML (a, b, c, d, e) where
toYAML :: (a, b, c, d, e) -> Node ()
toYAML (a
a,b
b,c
c,d
d,e
e) = [Node ()] -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML [a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a, b -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML b
b, c -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML c
c, d -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML d
d, e -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML e
e]
instance (ToYAML a, ToYAML b, ToYAML c, ToYAML d, ToYAML e, ToYAML f) => ToYAML (a, b, c, d, e, f) where
toYAML :: (a, b, c, d, e, f) -> Node ()
toYAML (a
a,b
b,c
c,d
d,e
e,f
f) = [Node ()] -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML [a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a, b -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML b
b, c -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML c
c, d -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML d
d, e -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML e
e, f -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML f
f]
instance (ToYAML a, ToYAML b, ToYAML c, ToYAML d, ToYAML e, ToYAML f, ToYAML g) => ToYAML (a, b, c, d, e, f, g) where
toYAML :: (a, b, c, d, e, f, g) -> Node ()
toYAML (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = [Node ()] -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML [a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
a, b -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML b
b, c -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML c
c, d -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML d
d, e -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML e
e, f -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML f
f, g -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML g
g]
encode :: ToYAML v => [v] -> BS.L.ByteString
encode :: forall v. ToYAML v => [v] -> ByteString
encode [v]
vList = [Doc (Node ())] -> ByteString
encodeNode ([Doc (Node ())] -> ByteString) -> [Doc (Node ())] -> ByteString
forall a b. (a -> b) -> a -> b
$ (v -> Doc (Node ())) -> [v] -> [Doc (Node ())]
forall a b. (a -> b) -> [a] -> [b]
map (Node () -> Doc (Node ())
forall n. n -> Doc n
Doc (Node () -> Doc (Node ())) -> (v -> Node ()) -> v -> Doc (Node ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML) [v]
vList
encode1 :: ToYAML v => v -> BS.L.ByteString
encode1 :: forall v. ToYAML v => v -> ByteString
encode1 v
a = [v] -> ByteString
forall v. ToYAML v => [v] -> ByteString
encode [v
a]
encodeStrict :: ToYAML v => [v] -> BS.ByteString
encodeStrict :: forall v. ToYAML v => [v] -> ByteString
encodeStrict = ByteString -> ByteString
bsToStrict (ByteString -> ByteString)
-> ([v] -> ByteString) -> [v] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [v] -> ByteString
forall v. ToYAML v => [v] -> ByteString
encode
encode1Strict :: ToYAML v => v -> BS.ByteString
encode1Strict :: forall v. ToYAML v => v -> ByteString
encode1Strict = ByteString -> ByteString
bsToStrict (ByteString -> ByteString) -> (v -> ByteString) -> v -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> ByteString
forall v. ToYAML v => v -> ByteString
encode1
class Loc loc where
toUnit :: Functor f => f loc -> f ()
toUnit = (() () -> f loc -> f ()
forall a b. a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$)
instance Loc Pos
instance Loc () where toUnit :: forall (f :: * -> *). Functor f => f () -> f ()
toUnit = f () -> f ()
forall a. a -> a
id
type Pair = (Node (), Node ())
(.=) :: ToYAML a => Text -> a -> Pair
Text
name .= :: forall a. ToYAML a => Text -> a -> (Node (), Node ())
.= a
node = (Text -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML Text
name, a -> Node ()
forall a. ToYAML a => a -> Node ()
toYAML a
node)
mapping :: [Pair] -> Node ()
mapping :: [(Node (), Node ())] -> Node ()
mapping = () -> Tag -> Mapping () -> Node ()
forall loc. loc -> Tag -> Mapping loc -> Node loc
Mapping () Tag
tagMap (Mapping () -> Node ())
-> ([(Node (), Node ())] -> Mapping ())
-> [(Node (), Node ())]
-> Node ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Node (), Node ())] -> Mapping ()
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList