module Hix.Data.ComponentConfig where

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

import Hix.Data.PackageName (PackageName)

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

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

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

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

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

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

instance Pretty ComponentName where
  pretty :: ComponentName -> Doc
pretty (ComponentName Text
n) = String -> Doc
forall a. IsString a => String -> a
fromString (Text -> String
forall a. ToString a => a -> String
toString Text
n)

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

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

instance FromJSON PreludePackage where
  parseJSON :: Value -> Parser PreludePackage
parseJSON Value
v =
    Value -> Parser PreludePackage
hpackStruct Value
v Parser PreludePackage
-> Parser PreludePackage -> Parser PreludePackage
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser PreludePackage
plainName
    where
      hpackStruct :: Value -> Parser PreludePackage
hpackStruct = String
-> (Object -> Parser PreludePackage)
-> Value
-> Parser PreludePackage
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PreludePackageSpec" \ Object
o -> Object
o Object -> Key -> Parser PreludePackage
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
      plainName :: Parser PreludePackage
plainName = Text -> PreludePackage
PreludePackageName (Text -> PreludePackage) -> Parser Text -> Parser PreludePackage
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
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
(PreludeConfig -> PreludeConfig -> Bool)
-> (PreludeConfig -> PreludeConfig -> Bool) -> Eq PreludeConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PreludeConfig -> PreludeConfig -> Bool
== :: PreludeConfig -> PreludeConfig -> Bool
$c/= :: PreludeConfig -> PreludeConfig -> Bool
/= :: PreludeConfig -> PreludeConfig -> Bool
Eq, Int -> PreludeConfig -> ShowS
[PreludeConfig] -> ShowS
PreludeConfig -> String
(Int -> PreludeConfig -> ShowS)
-> (PreludeConfig -> String)
-> ([PreludeConfig] -> ShowS)
-> Show PreludeConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PreludeConfig -> ShowS
showsPrec :: Int -> PreludeConfig -> ShowS
$cshow :: PreludeConfig -> String
show :: PreludeConfig -> String
$cshowList :: [PreludeConfig] -> ShowS
showList :: [PreludeConfig] -> ShowS
Show, (forall x. PreludeConfig -> Rep PreludeConfig x)
-> (forall x. Rep PreludeConfig x -> PreludeConfig)
-> Generic PreludeConfig
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
$cfrom :: forall x. PreludeConfig -> Rep PreludeConfig x
from :: forall x. PreludeConfig -> Rep PreludeConfig x
$cto :: forall x. Rep PreludeConfig x -> PreludeConfig
to :: forall x. Rep PreludeConfig x -> PreludeConfig
Generic)

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

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
(ComponentConfig -> ComponentConfig -> Bool)
-> (ComponentConfig -> ComponentConfig -> Bool)
-> Eq ComponentConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentConfig -> ComponentConfig -> Bool
== :: ComponentConfig -> ComponentConfig -> Bool
$c/= :: ComponentConfig -> ComponentConfig -> Bool
/= :: ComponentConfig -> ComponentConfig -> Bool
Eq, Int -> ComponentConfig -> ShowS
[ComponentConfig] -> ShowS
ComponentConfig -> String
(Int -> ComponentConfig -> ShowS)
-> (ComponentConfig -> String)
-> ([ComponentConfig] -> ShowS)
-> Show ComponentConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentConfig -> ShowS
showsPrec :: Int -> ComponentConfig -> ShowS
$cshow :: ComponentConfig -> String
show :: ComponentConfig -> String
$cshowList :: [ComponentConfig] -> ShowS
showList :: [ComponentConfig] -> ShowS
Show, (forall x. ComponentConfig -> Rep ComponentConfig x)
-> (forall x. Rep ComponentConfig x -> ComponentConfig)
-> Generic ComponentConfig
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
$cfrom :: forall x. ComponentConfig -> Rep ComponentConfig x
from :: forall x. ComponentConfig -> Rep ComponentConfig x
$cto :: forall x. Rep ComponentConfig x -> ComponentConfig
to :: forall x. Rep ComponentConfig x -> ComponentConfig
Generic)
  deriving anyclass (Maybe ComponentConfig
Value -> Parser [ComponentConfig]
Value -> Parser ComponentConfig
(Value -> Parser ComponentConfig)
-> (Value -> Parser [ComponentConfig])
-> Maybe ComponentConfig
-> FromJSON ComponentConfig
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ComponentConfig
parseJSON :: Value -> Parser ComponentConfig
$cparseJSONList :: Value -> Parser [ComponentConfig]
parseJSONList :: Value -> Parser [ComponentConfig]
$comittedField :: Maybe ComponentConfig
omittedField :: Maybe 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
(PackageConfig -> PackageConfig -> Bool)
-> (PackageConfig -> PackageConfig -> Bool) -> Eq PackageConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackageConfig -> PackageConfig -> Bool
== :: PackageConfig -> PackageConfig -> Bool
$c/= :: PackageConfig -> PackageConfig -> Bool
/= :: PackageConfig -> PackageConfig -> Bool
Eq, Int -> PackageConfig -> ShowS
[PackageConfig] -> ShowS
PackageConfig -> String
(Int -> PackageConfig -> ShowS)
-> (PackageConfig -> String)
-> ([PackageConfig] -> ShowS)
-> Show PackageConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PackageConfig -> ShowS
showsPrec :: Int -> PackageConfig -> ShowS
$cshow :: PackageConfig -> String
show :: PackageConfig -> String
$cshowList :: [PackageConfig] -> ShowS
showList :: [PackageConfig] -> ShowS
Show, (forall x. PackageConfig -> Rep PackageConfig x)
-> (forall x. Rep PackageConfig x -> PackageConfig)
-> Generic PackageConfig
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
$cfrom :: forall x. PackageConfig -> Rep PackageConfig x
from :: forall x. PackageConfig -> Rep PackageConfig x
$cto :: forall x. Rep PackageConfig x -> PackageConfig
to :: forall x. Rep PackageConfig x -> PackageConfig
Generic)
  deriving anyclass (Maybe PackageConfig
Value -> Parser [PackageConfig]
Value -> Parser PackageConfig
(Value -> Parser PackageConfig)
-> (Value -> Parser [PackageConfig])
-> Maybe PackageConfig
-> FromJSON PackageConfig
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PackageConfig
parseJSON :: Value -> Parser PackageConfig
$cparseJSONList :: Value -> Parser [PackageConfig]
parseJSONList :: Value -> Parser [PackageConfig]
$comittedField :: Maybe PackageConfig
omittedField :: Maybe 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
(Target -> Target -> Bool)
-> (Target -> Target -> Bool) -> Eq Target
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
/= :: Target -> Target -> Bool
Eq, Int -> Target -> ShowS
[Target] -> ShowS
Target -> String
(Int -> Target -> ShowS)
-> (Target -> String) -> ([Target] -> ShowS) -> Show Target
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Target -> ShowS
showsPrec :: Int -> Target -> ShowS
$cshow :: Target -> String
show :: Target -> String
$cshowList :: [Target] -> ShowS
showList :: [Target] -> ShowS
Show, (forall x. Target -> Rep Target x)
-> (forall x. Rep Target x -> Target) -> Generic Target
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
$cfrom :: forall x. Target -> Rep Target x
from :: forall x. Target -> Rep Target x
$cto :: forall x. Rep Target x -> Target
to :: forall x. Rep Target x -> Target
Generic)

data TargetOrDefault =
  ExplicitTarget Target
  |
  DefaultTarget Target
  |
  NoDefaultTarget Text
  deriving stock (TargetOrDefault -> TargetOrDefault -> Bool
(TargetOrDefault -> TargetOrDefault -> Bool)
-> (TargetOrDefault -> TargetOrDefault -> Bool)
-> Eq TargetOrDefault
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TargetOrDefault -> TargetOrDefault -> Bool
== :: TargetOrDefault -> TargetOrDefault -> Bool
$c/= :: TargetOrDefault -> TargetOrDefault -> Bool
/= :: TargetOrDefault -> TargetOrDefault -> Bool
Eq, Int -> TargetOrDefault -> ShowS
[TargetOrDefault] -> ShowS
TargetOrDefault -> String
(Int -> TargetOrDefault -> ShowS)
-> (TargetOrDefault -> String)
-> ([TargetOrDefault] -> ShowS)
-> Show TargetOrDefault
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TargetOrDefault -> ShowS
showsPrec :: Int -> TargetOrDefault -> ShowS
$cshow :: TargetOrDefault -> String
show :: TargetOrDefault -> String
$cshowList :: [TargetOrDefault] -> ShowS
showList :: [TargetOrDefault] -> ShowS
Show, (forall x. TargetOrDefault -> Rep TargetOrDefault x)
-> (forall x. Rep TargetOrDefault x -> TargetOrDefault)
-> Generic TargetOrDefault
forall x. Rep TargetOrDefault x -> TargetOrDefault
forall x. TargetOrDefault -> Rep TargetOrDefault x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TargetOrDefault -> Rep TargetOrDefault x
from :: forall x. TargetOrDefault -> Rep TargetOrDefault x
$cto :: forall x. Rep TargetOrDefault x -> TargetOrDefault
to :: forall x. Rep TargetOrDefault x -> TargetOrDefault
Generic)