module Hix.Data.ComponentConfig where

import Data.Aeson (FromJSON (parseJSON), FromJSONKey, withObject, (.:))
import Path (Abs, Dir, File, Path, Rel)

newtype PackagePath =
  PackagePath { PackagePath -> Path Rel Dir
unPackagePath :: Path Rel Dir }
  deriving stock (PackagePath -> PackagePath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackagePath -> PackagePath -> Bool
$c/= :: PackagePath -> PackagePath -> Bool
== :: PackagePath -> PackagePath -> Bool
$c== :: PackagePath -> PackagePath -> Bool
Eq, Int -> PackagePath -> ShowS
[PackagePath] -> ShowS
PackagePath -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PackagePath] -> ShowS
$cshowList :: [PackagePath] -> ShowS
show :: PackagePath -> String
$cshow :: PackagePath -> String
showsPrec :: Int -> PackagePath -> ShowS
$cshowsPrec :: Int -> PackagePath -> ShowS
Show, Eq PackagePath
PackagePath -> PackagePath -> Bool
PackagePath -> PackagePath -> Ordering
PackagePath -> PackagePath -> PackagePath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackagePath -> PackagePath -> PackagePath
$cmin :: PackagePath -> PackagePath -> PackagePath
max :: PackagePath -> PackagePath -> PackagePath
$cmax :: PackagePath -> PackagePath -> PackagePath
>= :: PackagePath -> PackagePath -> Bool
$c>= :: PackagePath -> PackagePath -> Bool
> :: PackagePath -> PackagePath -> Bool
$c> :: PackagePath -> PackagePath -> Bool
<= :: PackagePath -> PackagePath -> Bool
$c<= :: PackagePath -> PackagePath -> Bool
< :: PackagePath -> PackagePath -> Bool
$c< :: PackagePath -> PackagePath -> Bool
compare :: PackagePath -> PackagePath -> Ordering
$ccompare :: PackagePath -> PackagePath -> Ordering
Ord, forall x. Rep PackagePath x -> PackagePath
forall x. PackagePath -> Rep PackagePath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PackagePath x -> PackagePath
$cfrom :: forall x. PackagePath -> Rep PackagePath x
Generic)
  deriving newtype (Value -> Parser [PackagePath]
Value -> Parser PackagePath
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PackagePath]
$cparseJSONList :: Value -> Parser [PackagePath]
parseJSON :: Value -> Parser PackagePath
$cparseJSON :: Value -> Parser PackagePath
FromJSON, FromJSONKeyFunction [PackagePath]
FromJSONKeyFunction PackagePath
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [PackagePath]
$cfromJSONKeyList :: FromJSONKeyFunction [PackagePath]
fromJSONKey :: FromJSONKeyFunction PackagePath
$cfromJSONKey :: FromJSONKeyFunction PackagePath
FromJSONKey)

newtype SourceDir =
  SourceDir { SourceDir -> Path Rel Dir
unSourceDir :: Path Rel Dir }
  deriving stock (SourceDir -> SourceDir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceDir -> SourceDir -> Bool
$c/= :: SourceDir -> SourceDir -> Bool
== :: SourceDir -> SourceDir -> Bool
$c== :: SourceDir -> SourceDir -> Bool
Eq, Int -> SourceDir -> ShowS
[SourceDir] -> ShowS
SourceDir -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceDir] -> ShowS
$cshowList :: [SourceDir] -> ShowS
show :: SourceDir -> String
$cshow :: SourceDir -> String
showsPrec :: Int -> SourceDir -> ShowS
$cshowsPrec :: Int -> SourceDir -> ShowS
Show, forall x. Rep SourceDir x -> SourceDir
forall x. SourceDir -> Rep SourceDir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SourceDir x -> SourceDir
$cfrom :: forall x. SourceDir -> Rep SourceDir x
Generic)
  deriving newtype (Value -> Parser [SourceDir]
Value -> Parser SourceDir
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SourceDir]
$cparseJSONList :: Value -> Parser [SourceDir]
parseJSON :: Value -> Parser SourceDir
$cparseJSON :: Value -> Parser SourceDir
FromJSON)

newtype SourceDirs =
  SourceDirs { SourceDirs -> [SourceDir]
unSourceDirs :: [SourceDir] }
  deriving stock (SourceDirs -> SourceDirs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceDirs -> SourceDirs -> Bool
$c/= :: SourceDirs -> SourceDirs -> Bool
== :: SourceDirs -> SourceDirs -> Bool
$c== :: SourceDirs -> SourceDirs -> Bool
Eq, Int -> SourceDirs -> ShowS
[SourceDirs] -> ShowS
SourceDirs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceDirs] -> ShowS
$cshowList :: [SourceDirs] -> ShowS
show :: SourceDirs -> String
$cshow :: SourceDirs -> String
showsPrec :: Int -> SourceDirs -> ShowS
$cshowsPrec :: Int -> SourceDirs -> ShowS
Show, forall x. Rep SourceDirs x -> SourceDirs
forall x. SourceDirs -> Rep SourceDirs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SourceDirs x -> SourceDirs
$cfrom :: forall x. SourceDirs -> Rep SourceDirs x
Generic)

instance FromJSON SourceDirs where
  parseJSON :: Value -> Parser SourceDirs
parseJSON Value
v =
    ([SourceDir] -> SourceDirs
SourceDirs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
    ([SourceDir] -> SourceDirs
SourceDirs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v)

newtype PackageName =
  PackageName { PackageName -> Text
unPackageName :: Text }
  deriving stock (PackageName -> PackageName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageName -> PackageName -> Bool
$c/= :: PackageName -> PackageName -> Bool
== :: PackageName -> PackageName -> Bool
$c== :: PackageName -> PackageName -> Bool
Eq, Int -> PackageName -> ShowS
[PackageName] -> ShowS
PackageName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PackageName] -> ShowS
$cshowList :: [PackageName] -> ShowS
show :: PackageName -> String
$cshow :: PackageName -> String
showsPrec :: Int -> PackageName -> ShowS
$cshowsPrec :: Int -> PackageName -> ShowS
Show, forall x. Rep PackageName x -> PackageName
forall x. PackageName -> Rep PackageName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PackageName x -> PackageName
$cfrom :: forall x. PackageName -> Rep PackageName x
Generic)
  deriving newtype (String -> PackageName
forall a. (String -> a) -> IsString a
fromString :: String -> PackageName
$cfromString :: String -> PackageName
IsString, Eq PackageName
PackageName -> PackageName -> Bool
PackageName -> PackageName -> Ordering
PackageName -> PackageName -> PackageName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageName -> PackageName -> PackageName
$cmin :: PackageName -> PackageName -> PackageName
max :: PackageName -> PackageName -> PackageName
$cmax :: PackageName -> PackageName -> PackageName
>= :: PackageName -> PackageName -> Bool
$c>= :: PackageName -> PackageName -> Bool
> :: PackageName -> PackageName -> Bool
$c> :: PackageName -> PackageName -> Bool
<= :: PackageName -> PackageName -> Bool
$c<= :: PackageName -> PackageName -> Bool
< :: PackageName -> PackageName -> Bool
$c< :: PackageName -> PackageName -> Bool
compare :: PackageName -> PackageName -> Ordering
$ccompare :: PackageName -> PackageName -> Ordering
Ord, Value -> Parser [PackageName]
Value -> Parser PackageName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PackageName]
$cparseJSONList :: Value -> Parser [PackageName]
parseJSON :: Value -> Parser PackageName
$cparseJSON :: Value -> Parser PackageName
FromJSON, FromJSONKeyFunction [PackageName]
FromJSONKeyFunction PackageName
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [PackageName]
$cfromJSONKeyList :: FromJSONKeyFunction [PackageName]
fromJSONKey :: FromJSONKeyFunction PackageName
$cfromJSONKey :: FromJSONKeyFunction PackageName
FromJSONKey)

newtype ModuleName =
  ModuleName { ModuleName -> Text
unModuleName :: Text }
  deriving stock (ModuleName -> ModuleName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleName -> ModuleName -> Bool
$c/= :: ModuleName -> ModuleName -> Bool
== :: ModuleName -> ModuleName -> Bool
$c== :: ModuleName -> ModuleName -> Bool
Eq, Int -> ModuleName -> ShowS
[ModuleName] -> ShowS
ModuleName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModuleName] -> ShowS
$cshowList :: [ModuleName] -> ShowS
show :: ModuleName -> String
$cshow :: ModuleName -> String
showsPrec :: Int -> ModuleName -> ShowS
$cshowsPrec :: Int -> ModuleName -> ShowS
Show, forall x. Rep ModuleName x -> ModuleName
forall x. ModuleName -> Rep ModuleName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModuleName x -> ModuleName
$cfrom :: forall x. ModuleName -> Rep ModuleName x
Generic)
  deriving newtype (String -> ModuleName
forall a. (String -> a) -> IsString a
fromString :: String -> ModuleName
$cfromString :: String -> ModuleName
IsString, Eq ModuleName
ModuleName -> ModuleName -> Bool
ModuleName -> ModuleName -> Ordering
ModuleName -> ModuleName -> ModuleName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleName -> ModuleName -> ModuleName
$cmin :: ModuleName -> ModuleName -> ModuleName
max :: ModuleName -> ModuleName -> ModuleName
$cmax :: ModuleName -> ModuleName -> ModuleName
>= :: ModuleName -> ModuleName -> Bool
$c>= :: ModuleName -> ModuleName -> Bool
> :: ModuleName -> ModuleName -> Bool
$c> :: ModuleName -> ModuleName -> Bool
<= :: ModuleName -> ModuleName -> Bool
$c<= :: ModuleName -> ModuleName -> Bool
< :: ModuleName -> ModuleName -> Bool
$c< :: ModuleName -> ModuleName -> Bool
compare :: ModuleName -> ModuleName -> Ordering
$ccompare :: ModuleName -> ModuleName -> Ordering
Ord, Value -> Parser [ModuleName]
Value -> Parser ModuleName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ModuleName]
$cparseJSONList :: Value -> Parser [ModuleName]
parseJSON :: Value -> Parser ModuleName
$cparseJSON :: Value -> Parser ModuleName
FromJSON, FromJSONKeyFunction [ModuleName]
FromJSONKeyFunction ModuleName
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [ModuleName]
$cfromJSONKeyList :: FromJSONKeyFunction [ModuleName]
fromJSONKey :: FromJSONKeyFunction ModuleName
$cfromJSONKey :: FromJSONKeyFunction ModuleName
FromJSONKey)

newtype ComponentName =
  ComponentName { ComponentName -> Text
unComponentName :: Text }
  deriving stock (ComponentName -> ComponentName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComponentName -> ComponentName -> Bool
$c/= :: ComponentName -> ComponentName -> Bool
== :: ComponentName -> ComponentName -> Bool
$c== :: ComponentName -> ComponentName -> Bool
Eq, Int -> ComponentName -> ShowS
[ComponentName] -> ShowS
ComponentName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComponentName] -> ShowS
$cshowList :: [ComponentName] -> ShowS
show :: ComponentName -> String
$cshow :: ComponentName -> String
showsPrec :: Int -> ComponentName -> ShowS
$cshowsPrec :: Int -> ComponentName -> ShowS
Show, forall x. Rep ComponentName x -> ComponentName
forall x. ComponentName -> Rep ComponentName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ComponentName x -> ComponentName
$cfrom :: forall x. ComponentName -> Rep ComponentName x
Generic)
  deriving newtype (String -> ComponentName
forall a. (String -> a) -> IsString a
fromString :: String -> ComponentName
$cfromString :: String -> ComponentName
IsString, Eq ComponentName
ComponentName -> ComponentName -> Bool
ComponentName -> ComponentName -> Ordering
ComponentName -> ComponentName -> ComponentName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ComponentName -> ComponentName -> ComponentName
$cmin :: ComponentName -> ComponentName -> ComponentName
max :: ComponentName -> ComponentName -> ComponentName
$cmax :: ComponentName -> ComponentName -> ComponentName
>= :: ComponentName -> ComponentName -> Bool
$c>= :: ComponentName -> ComponentName -> Bool
> :: ComponentName -> ComponentName -> Bool
$c> :: ComponentName -> ComponentName -> Bool
<= :: ComponentName -> ComponentName -> Bool
$c<= :: ComponentName -> ComponentName -> Bool
< :: ComponentName -> ComponentName -> Bool
$c< :: ComponentName -> ComponentName -> Bool
compare :: ComponentName -> ComponentName -> Ordering
$ccompare :: ComponentName -> ComponentName -> Ordering
Ord, Value -> Parser [ComponentName]
Value -> Parser ComponentName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ComponentName]
$cparseJSONList :: Value -> Parser [ComponentName]
parseJSON :: Value -> Parser ComponentName
$cparseJSON :: Value -> Parser ComponentName
FromJSON, FromJSONKeyFunction [ComponentName]
FromJSONKeyFunction ComponentName
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [ComponentName]
$cfromJSONKeyList :: FromJSONKeyFunction [ComponentName]
fromJSONKey :: FromJSONKeyFunction ComponentName
$cfromJSONKey :: FromJSONKeyFunction ComponentName
FromJSONKey)

newtype EnvName =
  EnvName { EnvName -> Text
unEnvName :: Text }
  deriving stock (EnvName -> EnvName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnvName -> EnvName -> Bool
$c/= :: EnvName -> EnvName -> Bool
== :: EnvName -> EnvName -> Bool
$c== :: EnvName -> EnvName -> Bool
Eq, Int -> EnvName -> ShowS
[EnvName] -> ShowS
EnvName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnvName] -> ShowS
$cshowList :: [EnvName] -> ShowS
show :: EnvName -> String
$cshow :: EnvName -> String
showsPrec :: Int -> EnvName -> ShowS
$cshowsPrec :: Int -> EnvName -> ShowS
Show, forall x. Rep EnvName x -> EnvName
forall x. EnvName -> Rep EnvName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnvName x -> EnvName
$cfrom :: forall x. EnvName -> Rep EnvName x
Generic)
  deriving newtype (String -> EnvName
forall a. (String -> a) -> IsString a
fromString :: String -> EnvName
$cfromString :: String -> EnvName
IsString, Eq EnvName
EnvName -> EnvName -> Bool
EnvName -> EnvName -> Ordering
EnvName -> EnvName -> EnvName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnvName -> EnvName -> EnvName
$cmin :: EnvName -> EnvName -> EnvName
max :: EnvName -> EnvName -> EnvName
$cmax :: EnvName -> EnvName -> EnvName
>= :: EnvName -> EnvName -> Bool
$c>= :: EnvName -> EnvName -> Bool
> :: EnvName -> EnvName -> Bool
$c> :: EnvName -> EnvName -> Bool
<= :: EnvName -> EnvName -> Bool
$c<= :: EnvName -> EnvName -> Bool
< :: EnvName -> EnvName -> Bool
$c< :: EnvName -> EnvName -> Bool
compare :: EnvName -> EnvName -> Ordering
$ccompare :: EnvName -> EnvName -> Ordering
Ord, Value -> Parser [EnvName]
Value -> Parser EnvName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EnvName]
$cparseJSONList :: Value -> Parser [EnvName]
parseJSON :: Value -> Parser EnvName
$cparseJSON :: Value -> Parser EnvName
FromJSON, FromJSONKeyFunction [EnvName]
FromJSONKeyFunction EnvName
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [EnvName]
$cfromJSONKeyList :: FromJSONKeyFunction [EnvName]
fromJSONKey :: FromJSONKeyFunction EnvName
$cfromJSONKey :: FromJSONKeyFunction EnvName
FromJSONKey)

newtype EnvRunner =
  EnvRunner (Path Abs File)
  deriving stock (EnvRunner -> EnvRunner -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnvRunner -> EnvRunner -> Bool
$c/= :: EnvRunner -> EnvRunner -> Bool
== :: EnvRunner -> EnvRunner -> Bool
$c== :: EnvRunner -> EnvRunner -> Bool
Eq, Int -> EnvRunner -> ShowS
[EnvRunner] -> ShowS
EnvRunner -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnvRunner] -> ShowS
$cshowList :: [EnvRunner] -> ShowS
show :: EnvRunner -> String
$cshow :: EnvRunner -> String
showsPrec :: Int -> EnvRunner -> ShowS
$cshowsPrec :: Int -> EnvRunner -> ShowS
Show, forall x. Rep EnvRunner x -> EnvRunner
forall x. EnvRunner -> Rep EnvRunner x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnvRunner x -> EnvRunner
$cfrom :: forall x. EnvRunner -> Rep EnvRunner x
Generic)
  deriving newtype (Value -> Parser [EnvRunner]
Value -> Parser EnvRunner
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EnvRunner]
$cparseJSONList :: Value -> Parser [EnvRunner]
parseJSON :: Value -> Parser EnvRunner
$cparseJSON :: Value -> Parser EnvRunner
FromJSON)

data PreludePackage =
  PreludePackageName Text
  |
  PreludePackageSpec { PreludePackage -> Text
name :: Text }
  deriving stock (PreludePackage -> PreludePackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreludePackage -> PreludePackage -> Bool
$c/= :: PreludePackage -> PreludePackage -> Bool
== :: PreludePackage -> PreludePackage -> Bool
$c== :: PreludePackage -> PreludePackage -> Bool
Eq, Int -> PreludePackage -> ShowS
[PreludePackage] -> ShowS
PreludePackage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PreludePackage] -> ShowS
$cshowList :: [PreludePackage] -> ShowS
show :: PreludePackage -> String
$cshow :: PreludePackage -> String
showsPrec :: Int -> PreludePackage -> ShowS
$cshowsPrec :: Int -> PreludePackage -> ShowS
Show, forall x. Rep PreludePackage x -> PreludePackage
forall x. PreludePackage -> Rep PreludePackage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PreludePackage x -> PreludePackage
$cfrom :: forall x. PreludePackage -> Rep PreludePackage x
Generic)

instance FromJSON PreludePackage where
  parseJSON :: Value -> Parser PreludePackage
parseJSON Value
v =
    Value -> Parser PreludePackage
hpackStruct Value
v forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser PreludePackage
plainName
    where
      hpackStruct :: Value -> Parser PreludePackage
hpackStruct = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PreludePackageSpec" \ Object
o -> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
      plainName :: Parser PreludePackage
plainName = Text -> PreludePackage
PreludePackageName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

data PreludeConfig =
  PreludeConfig {
    PreludeConfig -> PreludePackage
package :: PreludePackage,
    PreludeConfig -> ModuleName
module_ :: ModuleName
  }
  deriving stock (PreludeConfig -> PreludeConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreludeConfig -> PreludeConfig -> Bool
$c/= :: PreludeConfig -> PreludeConfig -> Bool
== :: PreludeConfig -> PreludeConfig -> Bool
$c== :: PreludeConfig -> PreludeConfig -> Bool
Eq, Int -> PreludeConfig -> ShowS
[PreludeConfig] -> ShowS
PreludeConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PreludeConfig] -> ShowS
$cshowList :: [PreludeConfig] -> ShowS
show :: PreludeConfig -> String
$cshow :: PreludeConfig -> String
showsPrec :: Int -> PreludeConfig -> ShowS
$cshowsPrec :: Int -> PreludeConfig -> ShowS
Show, forall x. Rep PreludeConfig x -> PreludeConfig
forall x. PreludeConfig -> Rep PreludeConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PreludeConfig x -> PreludeConfig
$cfrom :: forall x. PreludeConfig -> Rep PreludeConfig x
Generic)

instance FromJSON PreludeConfig where
  parseJSON :: Value -> Parser PreludeConfig
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PreludeConfig" \ Object
o -> do
      PreludePackage
package <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"package"
      ModuleName
module_ <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"module"
      pure PreludeConfig {PreludePackage
ModuleName
module_ :: ModuleName
package :: PreludePackage
$sel:module_:PreludeConfig :: ModuleName
$sel:package:PreludeConfig :: PreludePackage
..}

data ComponentConfig =
  ComponentConfig {
    ComponentConfig -> ComponentName
name :: ComponentName,
    ComponentConfig -> SourceDirs
sourceDirs :: SourceDirs,
    ComponentConfig -> Maybe EnvRunner
runner :: Maybe EnvRunner,
    ComponentConfig -> [String]
extensions :: [String],
    ComponentConfig -> String
language :: String,
    ComponentConfig -> [String]
ghcOptions :: [String],
    ComponentConfig -> Maybe PreludeConfig
prelude :: Maybe PreludeConfig
  }
  deriving stock (ComponentConfig -> ComponentConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComponentConfig -> ComponentConfig -> Bool
$c/= :: ComponentConfig -> ComponentConfig -> Bool
== :: ComponentConfig -> ComponentConfig -> Bool
$c== :: ComponentConfig -> ComponentConfig -> Bool
Eq, Int -> ComponentConfig -> ShowS
[ComponentConfig] -> ShowS
ComponentConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComponentConfig] -> ShowS
$cshowList :: [ComponentConfig] -> ShowS
show :: ComponentConfig -> String
$cshow :: ComponentConfig -> String
showsPrec :: Int -> ComponentConfig -> ShowS
$cshowsPrec :: Int -> ComponentConfig -> ShowS
Show, forall x. Rep ComponentConfig x -> ComponentConfig
forall x. ComponentConfig -> Rep ComponentConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ComponentConfig x -> ComponentConfig
$cfrom :: forall x. ComponentConfig -> Rep ComponentConfig x
Generic)
  deriving anyclass (Value -> Parser [ComponentConfig]
Value -> Parser ComponentConfig
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ComponentConfig]
$cparseJSONList :: Value -> Parser [ComponentConfig]
parseJSON :: Value -> Parser ComponentConfig
$cparseJSON :: Value -> Parser ComponentConfig
FromJSON)

data PackageConfig =
  PackageConfig {
    PackageConfig -> PackageName
name :: PackageName,
    PackageConfig -> Path Rel Dir
src :: Path Rel Dir,
    PackageConfig -> Map ComponentName ComponentConfig
components :: Map ComponentName ComponentConfig
  }
  deriving stock (PackageConfig -> PackageConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageConfig -> PackageConfig -> Bool
$c/= :: PackageConfig -> PackageConfig -> Bool
== :: PackageConfig -> PackageConfig -> Bool
$c== :: PackageConfig -> PackageConfig -> Bool
Eq, Int -> PackageConfig -> ShowS
[PackageConfig] -> ShowS
PackageConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PackageConfig] -> ShowS
$cshowList :: [PackageConfig] -> ShowS
show :: PackageConfig -> String
$cshow :: PackageConfig -> String
showsPrec :: Int -> PackageConfig -> ShowS
$cshowsPrec :: Int -> PackageConfig -> ShowS
Show, forall x. Rep PackageConfig x -> PackageConfig
forall x. PackageConfig -> Rep PackageConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PackageConfig x -> PackageConfig
$cfrom :: forall x. PackageConfig -> Rep PackageConfig x
Generic)
  deriving anyclass (Value -> Parser [PackageConfig]
Value -> Parser PackageConfig
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PackageConfig]
$cparseJSONList :: Value -> Parser [PackageConfig]
parseJSON :: Value -> Parser PackageConfig
$cparseJSON :: Value -> Parser PackageConfig
FromJSON)

type PackagesConfig = Map PackageName PackageConfig

data Target =
  Target {
    Target -> PackageConfig
package :: PackageConfig,
    Target -> ComponentConfig
component :: ComponentConfig,
    Target -> Maybe SourceDir
sourceDir :: Maybe SourceDir
  }
  deriving stock (Target -> Target -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c== :: Target -> Target -> Bool
Eq, Int -> Target -> ShowS
[Target] -> ShowS
Target -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Target] -> ShowS
$cshowList :: [Target] -> ShowS
show :: Target -> String
$cshow :: Target -> String
showsPrec :: Int -> Target -> ShowS
$cshowsPrec :: Int -> Target -> ShowS
Show, forall x. Rep Target x -> Target
forall x. Target -> Rep Target x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Target x -> Target
$cfrom :: forall x. Target -> Rep Target x
Generic)