{-# LANGUAGE DeriveGeneric #-}

module FFICXX.Generate.Type.Cabal where

import Data.Aeson
  ( FromJSON (..),
    ToJSON (..),
    defaultOptions,
    genericParseJSON,
    genericToJSON,
  )
import Data.Aeson.Types (fieldLabelModifier)
import Data.Text (Text)
import GHC.Generics (Generic)

data AddCInc = AddCInc FilePath String

data AddCSrc = AddCSrc FilePath String

-- TODO: change String to Text
newtype CabalName = CabalName {CabalName -> String
unCabalName :: String}
  deriving (Int -> CabalName -> ShowS
[CabalName] -> ShowS
CabalName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CabalName] -> ShowS
$cshowList :: [CabalName] -> ShowS
show :: CabalName -> String
$cshow :: CabalName -> String
showsPrec :: Int -> CabalName -> ShowS
$cshowsPrec :: Int -> CabalName -> ShowS
Show, CabalName -> CabalName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CabalName -> CabalName -> Bool
$c/= :: CabalName -> CabalName -> Bool
== :: CabalName -> CabalName -> Bool
$c== :: CabalName -> CabalName -> Bool
Eq, Eq CabalName
CabalName -> CabalName -> Bool
CabalName -> CabalName -> Ordering
CabalName -> CabalName -> CabalName
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 :: CabalName -> CabalName -> CabalName
$cmin :: CabalName -> CabalName -> CabalName
max :: CabalName -> CabalName -> CabalName
$cmax :: CabalName -> CabalName -> CabalName
>= :: CabalName -> CabalName -> Bool
$c>= :: CabalName -> CabalName -> Bool
> :: CabalName -> CabalName -> Bool
$c> :: CabalName -> CabalName -> Bool
<= :: CabalName -> CabalName -> Bool
$c<= :: CabalName -> CabalName -> Bool
< :: CabalName -> CabalName -> Bool
$c< :: CabalName -> CabalName -> Bool
compare :: CabalName -> CabalName -> Ordering
$ccompare :: CabalName -> CabalName -> Ordering
Ord)

data BuildType
  = Simple
  | -- | dependencies
    Custom [CabalName]

-- TODO: change String to Text
data Cabal = Cabal
  { Cabal -> CabalName
cabal_pkgname :: CabalName,
    Cabal -> String
cabal_version :: String,
    Cabal -> String
cabal_cheaderprefix :: String,
    Cabal -> String
cabal_moduleprefix :: String,
    Cabal -> [AddCInc]
cabal_additional_c_incs :: [AddCInc],
    Cabal -> [AddCSrc]
cabal_additional_c_srcs :: [AddCSrc],
    Cabal -> [CabalName]
cabal_additional_pkgdeps :: [CabalName],
    Cabal -> Maybe String
cabal_license :: Maybe String,
    Cabal -> Maybe String
cabal_licensefile :: Maybe String,
    Cabal -> [String]
cabal_extraincludedirs :: [FilePath],
    Cabal -> [String]
cabal_extralibdirs :: [FilePath],
    Cabal -> [String]
cabal_extrafiles :: [FilePath],
    Cabal -> [String]
cabal_pkg_config_depends :: [String],
    Cabal -> BuildType
cabal_buildType :: BuildType
  }

data GeneratedCabalInfo = GeneratedCabalInfo
  { GeneratedCabalInfo -> Text
gci_pkgname :: Text,
    GeneratedCabalInfo -> Text
gci_version :: Text,
    GeneratedCabalInfo -> Text
gci_synopsis :: Text,
    GeneratedCabalInfo -> Text
gci_description :: Text,
    GeneratedCabalInfo -> Text
gci_homepage :: Text,
    GeneratedCabalInfo -> Text
gci_license :: Text,
    GeneratedCabalInfo -> Text
gci_licenseFile :: Text,
    GeneratedCabalInfo -> Text
gci_author :: Text,
    GeneratedCabalInfo -> Text
gci_maintainer :: Text,
    GeneratedCabalInfo -> Text
gci_category :: Text,
    GeneratedCabalInfo -> Text
gci_buildtype :: Text,
    GeneratedCabalInfo -> [Text]
gci_extraFiles :: [Text],
    GeneratedCabalInfo -> [Text]
gci_csrcFiles :: [Text],
    GeneratedCabalInfo -> Text
gci_sourcerepository :: Text,
    GeneratedCabalInfo -> [Text]
gci_cxxOptions :: [Text],
    GeneratedCabalInfo -> [Text]
gci_pkgdeps :: [Text],
    GeneratedCabalInfo -> [Text]
gci_exposedModules :: [Text],
    GeneratedCabalInfo -> [Text]
gci_otherModules :: [Text],
    GeneratedCabalInfo -> [Text]
gci_extraLibDirs :: [Text],
    GeneratedCabalInfo -> [Text]
gci_extraLibraries :: [Text],
    GeneratedCabalInfo -> [Text]
gci_extraIncludeDirs :: [Text],
    GeneratedCabalInfo -> [Text]
gci_pkgconfigDepends :: [Text],
    GeneratedCabalInfo -> [Text]
gci_includeFiles :: [Text],
    GeneratedCabalInfo -> [Text]
gci_cppFiles :: [Text]
  }
  deriving (Int -> GeneratedCabalInfo -> ShowS
[GeneratedCabalInfo] -> ShowS
GeneratedCabalInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GeneratedCabalInfo] -> ShowS
$cshowList :: [GeneratedCabalInfo] -> ShowS
show :: GeneratedCabalInfo -> String
$cshow :: GeneratedCabalInfo -> String
showsPrec :: Int -> GeneratedCabalInfo -> ShowS
$cshowsPrec :: Int -> GeneratedCabalInfo -> ShowS
Show, forall x. Rep GeneratedCabalInfo x -> GeneratedCabalInfo
forall x. GeneratedCabalInfo -> Rep GeneratedCabalInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GeneratedCabalInfo x -> GeneratedCabalInfo
$cfrom :: forall x. GeneratedCabalInfo -> Rep GeneratedCabalInfo x
Generic)

instance ToJSON GeneratedCabalInfo where
  toJSON :: GeneratedCabalInfo -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = forall a. Int -> [a] -> [a]
drop Int
4}

instance FromJSON GeneratedCabalInfo where
  parseJSON :: Value -> Parser GeneratedCabalInfo
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = forall a. Int -> [a] -> [a]
drop Int
4}