{-# LANGUAGE DeriveAnyClass  #-}
{-# LANGUAGE DeriveGeneric   #-}
{-# LANGUAGE PatternSynonyms #-}


-- gcc -c -o lib1.o lib1.c
-- gcc ats-src/libnumbertheory.o -shared -o ats-src/libnumbertheory.so
-- gcc number-theory-ffi_dats.c -c -fPIC -o ats-src/libnumbertheory.o -IATS2-Postiats-include-0.3.8/ -IATS2-Postiats-include-0.3.8/ccomp/runtime/

module Development.Shake.ATS.Type ( ForeignCabal (..)
                                  , Version (..)
                                  , BinaryTarget (..)
                                  , ArtifactType (..)
                                  , ATSToolConfig (..)
                                  , CCompiler (GCC, Clang, Other, GCCStd)
                                  ) where

import           Data.Binary     (Binary (..))
import           Data.Dependency (Version (..))
import qualified Data.Text.Lazy  as TL
import           GHC.Generics    (Generic)

pattern GCCStd :: CCompiler
pattern GCCStd = GCC Nothing Nothing

-- We should have four build types:
--
-- 1. Static library
--
-- 2. Dynamic library
--
-- 3. Binary
--
-- 4. C sources
--
-- AND variations on these where a Haskell library is to be built
-- Or a C library.
--
-- Also they should account for whatever `atspkg` installs.

-- Package management idea:
--
-- * One big index
--
-- * Versions resolved from that
--
-- * Then we temporarily set the dependencies
--
-- * Ideally something with C dependencies included.
--
-- * Also binary caches are good.

data ArtifactType = StaticLibrary
                  | DynamicLibrary
                  | Binary Bool

data CCompiler = GCC { _prefix :: Maybe String, _suffix :: Maybe String }
               | Clang
               | Other String
               deriving (Eq)

-- | Information about where to find @patscc@ and @patsopt@.
data ATSToolConfig = ATSToolConfig { libVersion  :: Version
                                   , compilerVer :: Version
                                   , hasPretty   :: Bool -- ^ Whether to display errors via @pats-filter@
                                   } deriving (Generic, Binary)

data BinaryTarget = BinaryTarget { cc         :: String -- ^ C compiler to be used.
                                 , cFlags     :: [String] -- ^ Flags to be passed to the C compiler
                                 , toolConfig :: ATSToolConfig
                                 , gc         :: Bool -- ^ Whether to configure build for use with the garbage collector.
                                 , libs       :: [String] -- ^ Libraries against which to link
                                 , src        :: String -- ^ Source file for binary.
                                 , hsLibs     :: [ForeignCabal] -- ^ Cabal-based Haskell libraries
                                 , genTargets :: [(String, String)] -- ^ Files to be run through @hs2ats@.
                                 , binTarget  :: String -- ^ Binary target
                                 , cDeps      :: [String] -- ^ Any C files necessary to compile the target
                                 } deriving (Generic, Binary)

-- | Data type containing information about Haskell components of a build.
data ForeignCabal = ForeignCabal { cabalFile  :: TL.Text -- ^ @.cabal@ file associated with the library
                                 , objectFile :: TL.Text -- ^ Object file to be generated
                                 } deriving (Eq, Show, Generic, Binary)