{-# LANGUAGE ApplicativeDo         #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE RecordWildCards       #-}

module HaskellWorks.CabalCache.Types where

import Data.Aeson
import Data.Text    (Text)
import GHC.Generics
import Prelude      hiding (id)

type CompilerId = Text
type PackageId  = Text

data PlanJson = PlanJson
  { PlanJson -> CompilerId
compilerId  :: CompilerId
  , PlanJson -> [Package]
installPlan :: [Package]
  } deriving (PlanJson -> PlanJson -> Bool
(PlanJson -> PlanJson -> Bool)
-> (PlanJson -> PlanJson -> Bool) -> Eq PlanJson
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlanJson -> PlanJson -> Bool
$c/= :: PlanJson -> PlanJson -> Bool
== :: PlanJson -> PlanJson -> Bool
$c== :: PlanJson -> PlanJson -> Bool
Eq, Int -> PlanJson -> ShowS
[PlanJson] -> ShowS
PlanJson -> String
(Int -> PlanJson -> ShowS)
-> (PlanJson -> String) -> ([PlanJson] -> ShowS) -> Show PlanJson
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlanJson] -> ShowS
$cshowList :: [PlanJson] -> ShowS
show :: PlanJson -> String
$cshow :: PlanJson -> String
showsPrec :: Int -> PlanJson -> ShowS
$cshowsPrec :: Int -> PlanJson -> ShowS
Show, (forall x. PlanJson -> Rep PlanJson x)
-> (forall x. Rep PlanJson x -> PlanJson) -> Generic PlanJson
forall x. Rep PlanJson x -> PlanJson
forall x. PlanJson -> Rep PlanJson x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlanJson x -> PlanJson
$cfrom :: forall x. PlanJson -> Rep PlanJson x
Generic)

data Package = Package
  { Package -> CompilerId
packageType   :: Text
  , Package -> CompilerId
id            :: PackageId
  , Package -> CompilerId
name          :: Text
  , Package -> CompilerId
version       :: Text
  , Package -> Maybe CompilerId
style         :: Maybe Text
  , Package -> Maybe CompilerId
componentName :: Maybe Text
  , Package -> Maybe Components
components    :: Maybe Components
  , Package -> [CompilerId]
depends       :: [Text]
  , Package -> [CompilerId]
exeDepends    :: [Text]
  } deriving (Package -> Package -> Bool
(Package -> Package -> Bool)
-> (Package -> Package -> Bool) -> Eq Package
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Package -> Package -> Bool
$c/= :: Package -> Package -> Bool
== :: Package -> Package -> Bool
$c== :: Package -> Package -> Bool
Eq, Int -> Package -> ShowS
[Package] -> ShowS
Package -> String
(Int -> Package -> ShowS)
-> (Package -> String) -> ([Package] -> ShowS) -> Show Package
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Package] -> ShowS
$cshowList :: [Package] -> ShowS
show :: Package -> String
$cshow :: Package -> String
showsPrec :: Int -> Package -> ShowS
$cshowsPrec :: Int -> Package -> ShowS
Show, (forall x. Package -> Rep Package x)
-> (forall x. Rep Package x -> Package) -> Generic Package
forall x. Rep Package x -> Package
forall x. Package -> Rep Package x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Package x -> Package
$cfrom :: forall x. Package -> Rep Package x
Generic)

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

data Lib = Lib
  { Lib -> [CompilerId]
depends    :: [Text]
  , Lib -> [CompilerId]
exeDepends :: [Text]
  } deriving (Lib -> Lib -> Bool
(Lib -> Lib -> Bool) -> (Lib -> Lib -> Bool) -> Eq Lib
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Lib -> Lib -> Bool
$c/= :: Lib -> Lib -> Bool
== :: Lib -> Lib -> Bool
$c== :: Lib -> Lib -> Bool
Eq, Int -> Lib -> ShowS
[Lib] -> ShowS
Lib -> String
(Int -> Lib -> ShowS)
-> (Lib -> String) -> ([Lib] -> ShowS) -> Show Lib
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Lib] -> ShowS
$cshowList :: [Lib] -> ShowS
show :: Lib -> String
$cshow :: Lib -> String
showsPrec :: Int -> Lib -> ShowS
$cshowsPrec :: Int -> Lib -> ShowS
Show, (forall x. Lib -> Rep Lib x)
-> (forall x. Rep Lib x -> Lib) -> Generic Lib
forall x. Rep Lib x -> Lib
forall x. Lib -> Rep Lib x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Lib x -> Lib
$cfrom :: forall x. Lib -> Rep Lib x
Generic)

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

instance FromJSON PlanJson where
  parseJSON :: Value -> Parser PlanJson
parseJSON = String -> (Object -> Parser PlanJson) -> Value -> Parser PlanJson
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PlanJson" ((Object -> Parser PlanJson) -> Value -> Parser PlanJson)
-> (Object -> Parser PlanJson) -> Value -> Parser PlanJson
forall a b. (a -> b) -> a -> b
$ \Object
v -> CompilerId -> [Package] -> PlanJson
PlanJson
    (CompilerId -> [Package] -> PlanJson)
-> Parser CompilerId -> Parser ([Package] -> PlanJson)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> CompilerId -> Parser CompilerId
forall a. FromJSON a => Object -> CompilerId -> Parser a
.: CompilerId
"compiler-id"
    Parser ([Package] -> PlanJson)
-> Parser [Package] -> Parser PlanJson
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> CompilerId -> Parser [Package]
forall a. FromJSON a => Object -> CompilerId -> Parser a
.: CompilerId
"install-plan"

instance FromJSON Package where
  parseJSON :: Value -> Parser Package
parseJSON = String -> (Object -> Parser Package) -> Value -> Parser Package
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Package" ((Object -> Parser Package) -> Value -> Parser Package)
-> (Object -> Parser Package) -> Value -> Parser Package
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
    CompilerId
packageType   <- Object
v Object -> CompilerId -> Parser CompilerId
forall a. FromJSON a => Object -> CompilerId -> Parser a
.:  CompilerId
"type"
    CompilerId
id            <- Object
v Object -> CompilerId -> Parser CompilerId
forall a. FromJSON a => Object -> CompilerId -> Parser a
.:  CompilerId
"id"
    CompilerId
name          <- Object
v Object -> CompilerId -> Parser CompilerId
forall a. FromJSON a => Object -> CompilerId -> Parser a
.:  CompilerId
"pkg-name"
    CompilerId
version       <- Object
v Object -> CompilerId -> Parser CompilerId
forall a. FromJSON a => Object -> CompilerId -> Parser a
.:  CompilerId
"pkg-version"
    Maybe CompilerId
style         <- Object
v Object -> CompilerId -> Parser (Maybe CompilerId)
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"style"
    Maybe CompilerId
componentName <- Object
v Object -> CompilerId -> Parser (Maybe CompilerId)
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"component-name"
    Maybe Components
components    <- Object
v Object -> CompilerId -> Parser (Maybe Components)
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"components"
    [CompilerId]
depends       <- Object
v Object -> CompilerId -> Parser (Maybe [CompilerId])
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"depends"     Parser (Maybe [CompilerId]) -> [CompilerId] -> Parser [CompilerId]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [CompilerId]
exeDepends    <- Object
v Object -> CompilerId -> Parser (Maybe [CompilerId])
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"exe-depends" Parser (Maybe [CompilerId]) -> [CompilerId] -> Parser [CompilerId]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    return Package :: CompilerId
-> CompilerId
-> CompilerId
-> CompilerId
-> Maybe CompilerId
-> Maybe CompilerId
-> Maybe Components
-> [CompilerId]
-> [CompilerId]
-> Package
Package {[CompilerId]
Maybe CompilerId
Maybe Components
CompilerId
exeDepends :: [CompilerId]
depends :: [CompilerId]
components :: Maybe Components
componentName :: Maybe CompilerId
style :: Maybe CompilerId
version :: CompilerId
name :: CompilerId
id :: CompilerId
packageType :: CompilerId
$sel:exeDepends:Package :: [CompilerId]
$sel:depends:Package :: [CompilerId]
$sel:components:Package :: Maybe Components
$sel:componentName:Package :: Maybe CompilerId
$sel:style:Package :: Maybe CompilerId
$sel:version:Package :: CompilerId
$sel:name:Package :: CompilerId
$sel:id:Package :: CompilerId
$sel:packageType:Package :: CompilerId
..}

instance FromJSON Components where
  parseJSON :: Value -> Parser Components
parseJSON = String
-> (Object -> Parser Components) -> Value -> Parser Components
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Components" ((Object -> Parser Components) -> Value -> Parser Components)
-> (Object -> Parser Components) -> Value -> Parser Components
forall a b. (a -> b) -> a -> b
$ \Object
v -> Maybe Lib -> Components
Components
    (Maybe Lib -> Components)
-> Parser (Maybe Lib) -> Parser Components
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> CompilerId -> Parser (Maybe Lib)
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"lib"

instance FromJSON Lib where
  parseJSON :: Value -> Parser Lib
parseJSON = String -> (Object -> Parser Lib) -> Value -> Parser Lib
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Lib" ((Object -> Parser Lib) -> Value -> Parser Lib)
-> (Object -> Parser Lib) -> Value -> Parser Lib
forall a b. (a -> b) -> a -> b
$ \Object
v -> [CompilerId] -> [CompilerId] -> Lib
Lib
    ([CompilerId] -> [CompilerId] -> Lib)
-> Parser [CompilerId] -> Parser ([CompilerId] -> Lib)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> CompilerId -> Parser (Maybe [CompilerId])
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"depends"     Parser (Maybe [CompilerId]) -> [CompilerId] -> Parser [CompilerId]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    Parser ([CompilerId] -> Lib) -> Parser [CompilerId] -> Parser Lib
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> CompilerId -> Parser (Maybe [CompilerId])
forall a. FromJSON a => Object -> CompilerId -> Parser (Maybe a)
.:? CompilerId
"exe-depends" Parser (Maybe [CompilerId]) -> [CompilerId] -> Parser [CompilerId]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []