blob: 46429221c15acfdf8bc2aa951de25ef911a486ca (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
|
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE UndecidableInstances #-}
-- | Functions for producing sources reading from yaml strings or files, using the aeson library.
module Conftrack.Source.Yaml (YamlSource(..), mkYamlSource, mkYamlSourceWith, mkYamlFileSource) where
import Conftrack.Source (SomeSource(..), ConfigSource (..))
import Conftrack.Source.Aeson
import Prelude hiding (readFile)
import qualified Data.Aeson as A
import qualified Data.Yaml as Y
import Data.Text (Text)
import qualified Data.Aeson.Text as A
import qualified Data.Text.Lazy as LT
import Data.Functor ((<&>))
import System.OsPath (OsPath)
import qualified System.OsPath as OS
import System.File.OsPath (readFile)
import qualified Data.ByteString as BS
newtype YamlSource = YamlSource JsonSource
deriving newtype (ConfigSource, Show)
mkYamlSource :: A.Value -> SomeSource
mkYamlSource value = mkYamlSourceWith ("Yaml string " <> LT.toStrict (A.encodeToLazyText value)) value
mkYamlSourceWith :: Text -> A.Value -> SomeSource
mkYamlSourceWith description value = SomeSource (source, [])
where source = YamlSource (JsonSource value description)
mkYamlFileSource :: OsPath -> IO (Either Y.ParseException SomeSource)
mkYamlFileSource path = do
bytes <- readFile path <&> BS.toStrict
pathAsText <- OS.decodeUtf path <&> LT.toStrict . LT.pack
pure $ Y.decodeEither' bytes
<&> mkYamlSourceWith ("YAML file " <> pathAsText)
|