{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE Safe #-}
module Data.YAML
(
decode
, decodeStrict
, FromYAML(..)
, Parser
, parseEither
, typeMismatch
, Mapping
, (.:), (.:?), (.:!), (.!=)
, withSeq
, withBool
, withFloat
, withInt
, withNull
, withStr
, withMap
, decodeNode
, decodeNode'
, Doc(..)
, Node(..)
, Scalar(..)
, SchemaResolver(..)
, failsafeSchemaResolver
, jsonSchemaResolver
, coreSchemaResolver
, decodeLoader
, Loader(..)
, 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.Event (Tag, isUntagged, tagToText)
import Data.YAML.Loader
import Data.YAML.Schema
import Util
newtype Doc n = Doc n deriving (Eq,Ord,Show)
data Node = Scalar !Scalar
| Mapping !Tag Mapping
| Sequence !Tag [Node]
| Anchor !NodeId !Node
deriving (Eq,Ord,Show)
type Mapping = Map Node Node
(.:) :: FromYAML a => Mapping -> Text -> Parser a
m .: k = maybe (fail $ "key " ++ show k ++ " not found") parseYAML (Map.lookup (Scalar (SStr k)) m)
(.:?) :: FromYAML a => Mapping -> Text -> Parser (Maybe a)
m .:? k = maybe (pure Nothing) parseYAML (Map.lookup (Scalar (SStr k)) m)
(.:!) :: FromYAML a => Mapping -> Text -> Parser (Maybe a)
m .:! k = maybe (pure Nothing) (fmap Just . parseYAML) (Map.lookup (Scalar (SStr k)) m)
(.!=) :: Parser (Maybe a) -> a -> Parser a
mv .!= def = fmap (maybe def id) mv
decodeNode :: BS.L.ByteString -> Either String [Doc Node]
decodeNode = decodeNode' coreSchemaResolver False False
decodeNode' :: SchemaResolver
-> Bool
-> Bool
-> BS.L.ByteString
-> Either String [Doc Node]
decodeNode' SchemaResolver{..} anchorNodes allowCycles bs0
= map Doc <$> runIdentity (decodeLoader failsafeLoader bs0)
where
failsafeLoader = Loader { yScalar = \t s v -> pure $ fmap Scalar (schemaResolverScalar t s v)
, ySequence = \t vs -> pure $ schemaResolverSequence t >>= \t' -> Right (Sequence t' vs)
, yMapping = \t kvs -> pure $ schemaResolverMapping t >>= \t' -> Right (Mapping t' (Map.fromList kvs))
, yAlias = if allowCycles
then \_ _ n -> pure $ Right n
else \_ c n -> pure $ if c then Left "cycle detected" else Right n
, yAnchor = if anchorNodes
then \j n -> pure $ Right (Anchor j n)
else \_ n -> pure $ Right n
}
newtype Parser a = P { unP :: Either String a }
instance Functor Parser where
fmap f (P x) = P (fmap f x)
x <$ P (Right _) = P (Right x)
_ <$ P (Left e) = P (Left e)
instance Applicative Parser where
pure = P . Right
P (Left e) <*> _ = P (Left e)
P (Right f) <*> P r = P (fmap f r)
P (Left e) *> _ = P (Left e)
P (Right _) *> p = p
instance Monad Parser where
return = pure
P m >>= k = P (m >>= unP . k)
(>>) = (*>)
fail = Fail.fail
instance Fail.MonadFail Parser where
fail = P . Left
instance Alternative Parser where
empty = fail "empty"
P (Left _) <|> y = y
x <|> _ = x
instance MonadPlus Parser where
mzero = empty
mplus = (<|>)
parseEither :: Parser a -> Either String a
parseEither = unP
typeMismatch :: String
-> Node
-> Parser a
typeMismatch expected node = fail ("expected " ++ expected ++ " instead of " ++ got)
where
got = case node of
Scalar (SBool _) -> "!!bool"
Scalar (SInt _) -> "!!int"
Scalar SNull -> "!!null"
Scalar (SStr _) -> "!!str"
Scalar (SFloat _) -> "!!float"
Scalar (SUnknown t v)
| isUntagged t -> tagged t ++ show v
| otherwise -> "(unsupported) " ++ tagged t ++ "scalar"
(Anchor _ _) -> "anchor"
(Mapping t _) -> tagged t ++ " mapping"
(Sequence t _) -> tagged t ++ " sequence"
tagged t0 = case tagToText t0 of
Nothing -> "non-specifically ? tagged (i.e. unresolved) "
Just t -> T.unpack t ++ " tagged"
class FromYAML a where
parseYAML :: Node -> Parser a
withNull :: String -> Parser a -> Node -> Parser a
withNull _ f (Scalar SNull) = f
withNull expected _ v = typeMismatch expected v
instance FromYAML Node where
parseYAML = pure
instance FromYAML Bool where
parseYAML = withBool "!!bool" pure
withBool :: String -> (Bool -> Parser a) -> Node -> Parser a
withBool _ f (Scalar (SBool b)) = f b
withBool expected _ v = typeMismatch expected v
instance FromYAML Text where
parseYAML = withStr "!!str" pure
withStr :: String -> (Text -> Parser a) -> Node -> Parser a
withStr _ f (Scalar (SStr b)) = f b
withStr expected _ v = typeMismatch expected v
instance FromYAML Integer where
parseYAML = withInt "!!int" pure
withInt :: String -> (Integer -> Parser a) -> Node -> Parser a
withInt _ f (Scalar (SInt b)) = f b
withInt expected _ v = typeMismatch expected v
instance FromYAML Natural where
parseYAML = withInt "!!int" $ \b -> if b < 0 then fail ("!!int " ++ show b ++ " out of range for 'Natural'")
else pure (fromInteger b)
{-# INLINE parseInt #-}
parseInt :: (Integral a, Bounded a) => [Char] -> Node -> Parser a
parseInt name = withInt "!!int" $ \b -> maybe (fail $ "!!int " ++ show b ++ " out of range for '" ++ name ++ "'") pure $
fromIntegerMaybe b
instance FromYAML Int where parseYAML = parseInt "Int"
instance FromYAML Int8 where parseYAML = parseInt "Int8"
instance FromYAML Int16 where parseYAML = parseInt "Int16"
instance FromYAML Int32 where parseYAML = parseInt "Int32"
instance FromYAML Int64 where parseYAML = parseInt "Int64"
instance FromYAML Word where parseYAML = parseInt "Word"
instance FromYAML Word8 where parseYAML = parseInt "Word8"
instance FromYAML Word16 where parseYAML = parseInt "Word16"
instance FromYAML Word32 where parseYAML = parseInt "Word32"
instance FromYAML Word64 where parseYAML = parseInt "Word64"
instance FromYAML Double where
parseYAML = withFloat "!!float" pure
withFloat :: String -> (Double -> Parser a) -> Node -> Parser a
withFloat _ f (Scalar (SFloat b)) = f b
withFloat expected _ v = typeMismatch expected v
instance (Ord k, FromYAML k, FromYAML v) => FromYAML (Map k v) where
parseYAML = withMap "!!map" $ \xs -> Map.fromList <$> mapM (\(a,b) -> (,) <$> parseYAML a <*> parseYAML b) (Map.toList xs)
withMap :: String -> (Mapping -> Parser a) -> Node -> Parser a
withMap _ f (Mapping tag xs)
| tag == tagMap = f xs
withMap expected _ v = typeMismatch expected v
instance FromYAML v => FromYAML [v] where
parseYAML = withSeq "!!seq" (mapM parseYAML)
withSeq :: String -> ([Node] -> Parser a) -> Node -> Parser a
withSeq _ f (Sequence tag xs)
| tag == tagSeq = f xs
withSeq expected _ v = typeMismatch expected v
instance FromYAML a => FromYAML (Maybe a) where
parseYAML (Scalar SNull) = pure Nothing
parseYAML j = Just <$> parseYAML j
instance (FromYAML a, FromYAML b) => FromYAML (a,b) where
parseYAML = withSeq "!!seq" $ \xs ->
case xs of
[a,b] -> (,) <$> parseYAML a
<*> parseYAML b
_ -> fail ("expected 2-sequence but got " ++ show (length xs) ++ "-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c) => FromYAML (a,b,c) where
parseYAML = withSeq "!!seq" $ \xs ->
case xs of
[a,b,c] -> (,,) <$> parseYAML a
<*> parseYAML b
<*> parseYAML c
_ -> fail ("expected 3-sequence but got " ++ show (length xs) ++ "-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d) => FromYAML (a,b,c,d) where
parseYAML = withSeq "!!seq" $ \xs ->
case xs of
[a,b,c,d] -> (,,,) <$> parseYAML a
<*> parseYAML b
<*> parseYAML c
<*> parseYAML d
_ -> fail ("expected 4-sequence but got " ++ show (length xs) ++ "-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e) => FromYAML (a,b,c,d,e) where
parseYAML = withSeq "!!seq" $ \xs ->
case xs of
[a,b,c,d,e] -> (,,,,) <$> parseYAML a
<*> parseYAML b
<*> parseYAML c
<*> parseYAML d
<*> parseYAML e
_ -> fail ("expected 5-sequence but got " ++ show (length xs) ++ "-sequence instead")
instance (FromYAML a, FromYAML b, FromYAML c, FromYAML d, FromYAML e, FromYAML f) => FromYAML (a,b,c,d,e,f) where
parseYAML = withSeq "!!seq" $ \xs ->
case xs of
[a,b,c,d,e,f] -> (,,,,,) <$> parseYAML a
<*> parseYAML b
<*> parseYAML c
<*> parseYAML d
<*> parseYAML e
<*> parseYAML f
_ -> fail ("expected 6-sequence but got " ++ show (length xs) ++ "-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 = withSeq "!!seq" $ \xs ->
case xs of
[a,b,c,d,e,f,g] -> (,,,,,,) <$> parseYAML a
<*> parseYAML b
<*> parseYAML c
<*> parseYAML d
<*> parseYAML e
<*> parseYAML f
<*> parseYAML g
_ -> fail ("expected 7-sequence but got " ++ show (length xs) ++ "-sequence instead")
decode :: FromYAML v => BS.L.ByteString -> Either String [v]
decode bs0 = decodeNode bs0 >>= mapM (parseEither . parseYAML . (\(Doc x) -> x))
decodeStrict :: FromYAML v => BS.ByteString -> Either String [v]
decodeStrict = decode . BS.L.fromChunks . (:[])