{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module HIE.Bios.Config.YAML
( CradleConfigYAML(..)
, CradleComponent(..)
, MultiSubComponent(..)
, CabalConfig(..)
, CabalComponent(..)
, StackConfig(..)
, StackComponent(..)
, DirectConfig(..)
, BiosConfig(..)
, NoneConfig(..)
, OtherConfig(..)
, OneOrManyComponents(..)
, Callable(..)
) where
import Control.Applicative ((<|>))
import Data.Aeson
#if MIN_VERSION_aeson(2,0,0)
import Data.Aeson.KeyMap (keys)
#else
import qualified Data.HashMap.Strict as Map
import qualified Data.Text as T
#endif
import Data.Aeson.Types (Parser, typeMismatch)
import qualified Data.Char as C (toLower)
import Data.List ((\\))
import GHC.Generics (Generic)
#if !MIN_VERSION_aeson(2,0,0)
type Key = T.Text
type KeyMap v = Map.HashMap T.Text v
keys :: KeyMap v -> [Key]
keys = Map.keys
#endif
checkObjectKeys :: [Key] -> Object -> Parser ()
checkObjectKeys :: [Key] -> Object -> Parser ()
checkObjectKeys [Key]
allowedKeys Object
obj =
let extraKeys :: [Key]
extraKeys = Object -> [Key]
forall v. KeyMap v -> [Key]
keys Object
obj [Key] -> [Key] -> [Key]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Key]
allowedKeys
in case [Key]
extraKeys of
[] -> () -> Parser ()
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
[Key]
_ -> String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ()) -> String -> Parser ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [ String
"Unexpected keys "
, [Key] -> String
forall a. Show a => a -> String
show [Key]
extraKeys
, String
", keys allowed: "
, [Key] -> String
forall a. Show a => a -> String
show [Key]
allowedKeys
]
data CradleConfigYAML a
= CradleConfigYAML { forall a. CradleConfigYAML a -> CradleComponent a
cradle :: CradleComponent a
, forall a. CradleConfigYAML a -> Maybe [String]
dependencies :: Maybe [FilePath]
} deriving ((forall x. CradleConfigYAML a -> Rep (CradleConfigYAML a) x)
-> (forall x. Rep (CradleConfigYAML a) x -> CradleConfigYAML a)
-> Generic (CradleConfigYAML a)
forall x. Rep (CradleConfigYAML a) x -> CradleConfigYAML a
forall x. CradleConfigYAML a -> Rep (CradleConfigYAML a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CradleConfigYAML a) x -> CradleConfigYAML a
forall a x. CradleConfigYAML a -> Rep (CradleConfigYAML a) x
$cfrom :: forall a x. CradleConfigYAML a -> Rep (CradleConfigYAML a) x
from :: forall x. CradleConfigYAML a -> Rep (CradleConfigYAML a) x
$cto :: forall a x. Rep (CradleConfigYAML a) x -> CradleConfigYAML a
to :: forall x. Rep (CradleConfigYAML a) x -> CradleConfigYAML a
Generic, Maybe (CradleConfigYAML a)
Value -> Parser [CradleConfigYAML a]
Value -> Parser (CradleConfigYAML a)
(Value -> Parser (CradleConfigYAML a))
-> (Value -> Parser [CradleConfigYAML a])
-> Maybe (CradleConfigYAML a)
-> FromJSON (CradleConfigYAML a)
forall a. FromJSON a => Maybe (CradleConfigYAML a)
forall a. FromJSON a => Value -> Parser [CradleConfigYAML a]
forall a. FromJSON a => Value -> Parser (CradleConfigYAML a)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: forall a. FromJSON a => Value -> Parser (CradleConfigYAML a)
parseJSON :: Value -> Parser (CradleConfigYAML a)
$cparseJSONList :: forall a. FromJSON a => Value -> Parser [CradleConfigYAML a]
parseJSONList :: Value -> Parser [CradleConfigYAML a]
$comittedField :: forall a. FromJSON a => Maybe (CradleConfigYAML a)
omittedField :: Maybe (CradleConfigYAML a)
FromJSON)
data CradleComponent a
= Multi [MultiSubComponent a]
| Cabal CabalConfig
| Stack StackConfig
| Direct DirectConfig
| Bios BiosConfig
| None NoneConfig
| Other (OtherConfig a)
deriving ((forall x. CradleComponent a -> Rep (CradleComponent a) x)
-> (forall x. Rep (CradleComponent a) x -> CradleComponent a)
-> Generic (CradleComponent a)
forall x. Rep (CradleComponent a) x -> CradleComponent a
forall x. CradleComponent a -> Rep (CradleComponent a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CradleComponent a) x -> CradleComponent a
forall a x. CradleComponent a -> Rep (CradleComponent a) x
$cfrom :: forall a x. CradleComponent a -> Rep (CradleComponent a) x
from :: forall x. CradleComponent a -> Rep (CradleComponent a) x
$cto :: forall a x. Rep (CradleComponent a) x -> CradleComponent a
to :: forall x. Rep (CradleComponent a) x -> CradleComponent a
Generic)
instance FromJSON a => FromJSON (CradleComponent a) where
parseJSON :: Value -> Parser (CradleComponent a)
parseJSON = let opts :: Options
opts = Options
defaultOptions { constructorTagModifier :: String -> String
constructorTagModifier = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
C.toLower
, sumEncoding :: SumEncoding
sumEncoding = SumEncoding
ObjectWithSingleField
}
in Options -> Value -> Parser (CradleComponent a)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
opts
data NoneConfig = NoneConfig
data OtherConfig a
= OtherConfig { forall a. OtherConfig a -> a
otherConfig :: a
, forall a. OtherConfig a -> Value
originalYamlValue :: Value
}
instance FromJSON a => FromJSON (OtherConfig a) where
parseJSON :: Value -> Parser (OtherConfig a)
parseJSON Value
v = a -> Value -> OtherConfig a
forall a. a -> Value -> OtherConfig a
OtherConfig
(a -> Value -> OtherConfig a)
-> Parser a -> Parser (Value -> OtherConfig a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Parser (Value -> OtherConfig a)
-> Parser Value -> Parser (OtherConfig a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser Value
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
v
instance FromJSON NoneConfig where
parseJSON :: Value -> Parser NoneConfig
parseJSON Value
Null = NoneConfig -> Parser NoneConfig
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NoneConfig
NoneConfig
parseJSON Value
v = String -> Value -> Parser NoneConfig
forall a. String -> Value -> Parser a
typeMismatch String
"NoneConfig" Value
v
data MultiSubComponent a
= MultiSubComponent { forall a. MultiSubComponent a -> String
path :: FilePath
, forall a. MultiSubComponent a -> CradleConfigYAML a
config :: CradleConfigYAML a
} deriving ((forall x. MultiSubComponent a -> Rep (MultiSubComponent a) x)
-> (forall x. Rep (MultiSubComponent a) x -> MultiSubComponent a)
-> Generic (MultiSubComponent a)
forall x. Rep (MultiSubComponent a) x -> MultiSubComponent a
forall x. MultiSubComponent a -> Rep (MultiSubComponent a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (MultiSubComponent a) x -> MultiSubComponent a
forall a x. MultiSubComponent a -> Rep (MultiSubComponent a) x
$cfrom :: forall a x. MultiSubComponent a -> Rep (MultiSubComponent a) x
from :: forall x. MultiSubComponent a -> Rep (MultiSubComponent a) x
$cto :: forall a x. Rep (MultiSubComponent a) x -> MultiSubComponent a
to :: forall x. Rep (MultiSubComponent a) x -> MultiSubComponent a
Generic, Maybe (MultiSubComponent a)
Value -> Parser [MultiSubComponent a]
Value -> Parser (MultiSubComponent a)
(Value -> Parser (MultiSubComponent a))
-> (Value -> Parser [MultiSubComponent a])
-> Maybe (MultiSubComponent a)
-> FromJSON (MultiSubComponent a)
forall a. FromJSON a => Maybe (MultiSubComponent a)
forall a. FromJSON a => Value -> Parser [MultiSubComponent a]
forall a. FromJSON a => Value -> Parser (MultiSubComponent a)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: forall a. FromJSON a => Value -> Parser (MultiSubComponent a)
parseJSON :: Value -> Parser (MultiSubComponent a)
$cparseJSONList :: forall a. FromJSON a => Value -> Parser [MultiSubComponent a]
parseJSONList :: Value -> Parser [MultiSubComponent a]
$comittedField :: forall a. FromJSON a => Maybe (MultiSubComponent a)
omittedField :: Maybe (MultiSubComponent a)
FromJSON)
data CabalConfig
= CabalConfig { CabalConfig -> Maybe String
cabalProject :: Maybe FilePath
, CabalConfig -> OneOrManyComponents CabalComponent
cabalComponents :: OneOrManyComponents CabalComponent
}
instance FromJSON CabalConfig where
parseJSON :: Value -> Parser CabalConfig
parseJSON v :: Value
v@(Array Array
_) = Maybe String -> OneOrManyComponents CabalComponent -> CabalConfig
CabalConfig Maybe String
forall a. Maybe a
Nothing (OneOrManyComponents CabalComponent -> CabalConfig)
-> ([CabalComponent] -> OneOrManyComponents CabalComponent)
-> [CabalComponent]
-> CabalConfig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CabalComponent] -> OneOrManyComponents CabalComponent
forall component. [component] -> OneOrManyComponents component
ManyComponents ([CabalComponent] -> CabalConfig)
-> Parser [CabalComponent] -> Parser CabalConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [CabalComponent]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
parseJSON v :: Value
v@(Object Object
obj) = ([Key] -> Object -> Parser ()
checkObjectKeys [Key
"cabalProject", Key
"component", Key
"components"] Object
obj)
Parser () -> Parser CabalConfig -> Parser CabalConfig
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Maybe String -> OneOrManyComponents CabalComponent -> CabalConfig
CabalConfig
(Maybe String -> OneOrManyComponents CabalComponent -> CabalConfig)
-> Parser (Maybe String)
-> Parser (OneOrManyComponents CabalComponent -> CabalConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"cabalProject"
Parser (OneOrManyComponents CabalComponent -> CabalConfig)
-> Parser (OneOrManyComponents CabalComponent)
-> Parser CabalConfig
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser (OneOrManyComponents CabalComponent)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v)
parseJSON Value
Null = CabalConfig -> Parser CabalConfig
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CabalConfig -> Parser CabalConfig)
-> CabalConfig -> Parser CabalConfig
forall a b. (a -> b) -> a -> b
$ Maybe String -> OneOrManyComponents CabalComponent -> CabalConfig
CabalConfig Maybe String
forall a. Maybe a
Nothing OneOrManyComponents CabalComponent
forall component. OneOrManyComponents component
NoComponent
parseJSON Value
v = String -> Value -> Parser CabalConfig
forall a. String -> Value -> Parser a
typeMismatch String
"CabalConfig" Value
v
data CabalComponent
= CabalComponent { CabalComponent -> String
cabalPath :: FilePath
, CabalComponent -> String
cabalComponent :: String
, CabalComponent -> Maybe String
cabalComponentProject :: Maybe FilePath
}
instance FromJSON CabalComponent where
parseJSON :: Value -> Parser CabalComponent
parseJSON =
let parseCabalComponent :: Object -> Parser CabalComponent
parseCabalComponent Object
obj = [Key] -> Object -> Parser ()
checkObjectKeys [Key
"path", Key
"component", Key
"cabalProject"] Object
obj
Parser () -> Parser CabalComponent -> Parser CabalComponent
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (String -> String -> Maybe String -> CabalComponent
CabalComponent
(String -> String -> Maybe String -> CabalComponent)
-> Parser String
-> Parser (String -> Maybe String -> CabalComponent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"path"
Parser (String -> Maybe String -> CabalComponent)
-> Parser String -> Parser (Maybe String -> CabalComponent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"component"
Parser (Maybe String -> CabalComponent)
-> Parser (Maybe String) -> Parser CabalComponent
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"cabalProject"
)
in String
-> (Object -> Parser CabalComponent)
-> Value
-> Parser CabalComponent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CabalComponent" Object -> Parser CabalComponent
parseCabalComponent
data StackConfig
= StackConfig { StackConfig -> Maybe String
stackYaml :: Maybe FilePath
, StackConfig -> OneOrManyComponents StackComponent
stackComponents :: OneOrManyComponents StackComponent
}
data StackComponent
= StackComponent { StackComponent -> String
stackPath :: FilePath
, StackComponent -> String
stackComponent :: String
, StackComponent -> Maybe String
stackComponentYAML :: Maybe FilePath
}
instance FromJSON StackConfig where
parseJSON :: Value -> Parser StackConfig
parseJSON v :: Value
v@(Array Array
_) = Maybe String -> OneOrManyComponents StackComponent -> StackConfig
StackConfig Maybe String
forall a. Maybe a
Nothing (OneOrManyComponents StackComponent -> StackConfig)
-> ([StackComponent] -> OneOrManyComponents StackComponent)
-> [StackComponent]
-> StackConfig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [StackComponent] -> OneOrManyComponents StackComponent
forall component. [component] -> OneOrManyComponents component
ManyComponents ([StackComponent] -> StackConfig)
-> Parser [StackComponent] -> Parser StackConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [StackComponent]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
parseJSON v :: Value
v@(Object Object
obj) = ([Key] -> Object -> Parser ()
checkObjectKeys [Key
"component", Key
"components", Key
"stackYaml"] Object
obj)
Parser () -> Parser StackConfig -> Parser StackConfig
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Maybe String -> OneOrManyComponents StackComponent -> StackConfig
StackConfig
(Maybe String -> OneOrManyComponents StackComponent -> StackConfig)
-> Parser (Maybe String)
-> Parser (OneOrManyComponents StackComponent -> StackConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"stackYaml"
Parser (OneOrManyComponents StackComponent -> StackConfig)
-> Parser (OneOrManyComponents StackComponent)
-> Parser StackConfig
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser (OneOrManyComponents StackComponent)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
)
parseJSON Value
Null = StackConfig -> Parser StackConfig
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StackConfig -> Parser StackConfig)
-> StackConfig -> Parser StackConfig
forall a b. (a -> b) -> a -> b
$ Maybe String -> OneOrManyComponents StackComponent -> StackConfig
StackConfig Maybe String
forall a. Maybe a
Nothing OneOrManyComponents StackComponent
forall component. OneOrManyComponents component
NoComponent
parseJSON Value
v = String -> Value -> Parser StackConfig
forall a. String -> Value -> Parser a
typeMismatch String
"StackConfig" Value
v
instance FromJSON StackComponent where
parseJSON :: Value -> Parser StackComponent
parseJSON =
let parseStackComponent :: Object -> Parser StackComponent
parseStackComponent Object
obj = ([Key] -> Object -> Parser ()
checkObjectKeys [Key
"path", Key
"component", Key
"stackYaml"] Object
obj)
Parser () -> Parser StackComponent -> Parser StackComponent
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (String -> String -> Maybe String -> StackComponent
StackComponent
(String -> String -> Maybe String -> StackComponent)
-> Parser String
-> Parser (String -> Maybe String -> StackComponent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"path"
Parser (String -> Maybe String -> StackComponent)
-> Parser String -> Parser (Maybe String -> StackComponent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"component"
Parser (Maybe String -> StackComponent)
-> Parser (Maybe String) -> Parser StackComponent
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"stackYaml")
in String
-> (Object -> Parser StackComponent)
-> Value
-> Parser StackComponent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"StackComponent" Object -> Parser StackComponent
parseStackComponent
data OneOrManyComponents component
= SingleComponent String
| ManyComponents [component]
| NoComponent
instance FromJSON component => FromJSON (OneOrManyComponents component) where
parseJSON :: Value -> Parser (OneOrManyComponents component)
parseJSON =
let parseComponents :: Object -> Parser (OneOrManyComponents component)
parseComponents Object
o = (Object -> Parser (OneOrManyComponents component)
forall {component}.
Object -> Parser (OneOrManyComponents component)
parseSingleComponent Object
o Parser (OneOrManyComponents component)
-> Parser (OneOrManyComponents component)
-> Parser (OneOrManyComponents component)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Object -> Parser (OneOrManyComponents component)
forall {component}.
FromJSON component =>
Object -> Parser (OneOrManyComponents component)
parseSubComponents Object
o Parser (OneOrManyComponents component)
-> Parser (OneOrManyComponents component)
-> Parser (OneOrManyComponents component)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> OneOrManyComponents component
-> Parser (OneOrManyComponents component)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OneOrManyComponents component
forall component. OneOrManyComponents component
NoComponent)
parseSingleComponent :: Object -> Parser (OneOrManyComponents component)
parseSingleComponent Object
o = String -> OneOrManyComponents component
forall component. String -> OneOrManyComponents component
SingleComponent (String -> OneOrManyComponents component)
-> Parser String -> Parser (OneOrManyComponents component)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"component"
parseSubComponents :: Object -> Parser (OneOrManyComponents component)
parseSubComponents Object
o = [component] -> OneOrManyComponents component
forall component. [component] -> OneOrManyComponents component
ManyComponents ([component] -> OneOrManyComponents component)
-> Parser [component] -> Parser (OneOrManyComponents component)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [component]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"components"
in String
-> (Object -> Parser (OneOrManyComponents component))
-> Value
-> Parser (OneOrManyComponents component)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Components" Object -> Parser (OneOrManyComponents component)
forall {component}.
FromJSON component =>
Object -> Parser (OneOrManyComponents component)
parseComponents
data DirectConfig
= DirectConfig { DirectConfig -> [String]
arguments :: [String] }
deriving ((forall x. DirectConfig -> Rep DirectConfig x)
-> (forall x. Rep DirectConfig x -> DirectConfig)
-> Generic DirectConfig
forall x. Rep DirectConfig x -> DirectConfig
forall x. DirectConfig -> Rep DirectConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DirectConfig -> Rep DirectConfig x
from :: forall x. DirectConfig -> Rep DirectConfig x
$cto :: forall x. Rep DirectConfig x -> DirectConfig
to :: forall x. Rep DirectConfig x -> DirectConfig
Generic, Maybe DirectConfig
Value -> Parser [DirectConfig]
Value -> Parser DirectConfig
(Value -> Parser DirectConfig)
-> (Value -> Parser [DirectConfig])
-> Maybe DirectConfig
-> FromJSON DirectConfig
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DirectConfig
parseJSON :: Value -> Parser DirectConfig
$cparseJSONList :: Value -> Parser [DirectConfig]
parseJSONList :: Value -> Parser [DirectConfig]
$comittedField :: Maybe DirectConfig
omittedField :: Maybe DirectConfig
FromJSON)
data BiosConfig =
BiosConfig { BiosConfig -> Callable
callable :: Callable
, BiosConfig -> Maybe Callable
depsCallable :: Maybe Callable
, BiosConfig -> Maybe String
ghcPath :: Maybe FilePath
}
instance FromJSON BiosConfig where
parseJSON :: Value -> Parser BiosConfig
parseJSON = String
-> (Object -> Parser BiosConfig) -> Value -> Parser BiosConfig
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"BiosConfig" Object -> Parser BiosConfig
parseBiosConfig
data Callable
= Program FilePath
| Shell String
parseBiosConfig :: Object -> Parser BiosConfig
parseBiosConfig :: Object -> Parser BiosConfig
parseBiosConfig Object
obj =
let parseCallable :: Object -> Parser Callable
parseCallable Object
o = (String -> Callable
Program (String -> Callable) -> Parser String -> Parser Callable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"program") Parser Callable -> Parser Callable -> Parser Callable
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> Callable
Shell (String -> Callable) -> Parser String -> Parser Callable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"shell")
parseDepsCallable :: Object -> Parser (Maybe Callable)
parseDepsCallable Object
o = (Callable -> Maybe Callable
forall a. a -> Maybe a
Just (Callable -> Maybe Callable)
-> (String -> Callable) -> String -> Maybe Callable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Callable
Program (String -> Maybe Callable)
-> Parser String -> Parser (Maybe Callable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dependency-program")
Parser (Maybe Callable)
-> Parser (Maybe Callable) -> Parser (Maybe Callable)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Callable -> Maybe Callable
forall a. a -> Maybe a
Just (Callable -> Maybe Callable)
-> (String -> Callable) -> String -> Maybe Callable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Callable
Shell (String -> Maybe Callable)
-> Parser String -> Parser (Maybe Callable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dependency-shell")
Parser (Maybe Callable)
-> Parser (Maybe Callable) -> Parser (Maybe Callable)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Maybe Callable -> Parser (Maybe Callable)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Callable
forall a. Maybe a
Nothing)
parse :: Object -> Parser BiosConfig
parse Object
o = Callable -> Maybe Callable -> Maybe String -> BiosConfig
BiosConfig (Callable -> Maybe Callable -> Maybe String -> BiosConfig)
-> Parser Callable
-> Parser (Maybe Callable -> Maybe String -> BiosConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser Callable
parseCallable Object
o
Parser (Maybe Callable -> Maybe String -> BiosConfig)
-> Parser (Maybe Callable) -> Parser (Maybe String -> BiosConfig)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Parser (Maybe Callable)
parseDepsCallable Object
o
Parser (Maybe String -> BiosConfig)
-> Parser (Maybe String) -> Parser BiosConfig
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"with-ghc")
check :: Object -> Parser ()
check = [Key] -> Object -> Parser ()
checkObjectKeys [Key
"program", Key
"shell", Key
"dependency-program", Key
"dependency-shell", Key
"with-ghc"]
in Object -> Parser ()
check Object
obj Parser () -> Parser BiosConfig -> Parser BiosConfig
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Object -> Parser BiosConfig
parse Object
obj