{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.BuildType (
    BuildType(..),
    knownBuildTypes,
) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.CabalSpecVersion (CabalSpecVersion (..))
import Distribution.Pretty
import Distribution.Parsec

import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp

-- | The type of build system used by this package.
data BuildType
  = Simple      -- ^ calls @Distribution.Simple.defaultMain@
  | Configure   -- ^ calls @Distribution.Simple.defaultMainWithHooks defaultUserHooks@,
                -- which invokes @configure@ to generate additional build
                -- information used by later phases.
  | Make        -- ^ calls @Distribution.Make.defaultMain@
  | Custom      -- ^ uses user-supplied @Setup.hs@ or @Setup.lhs@ (default)
                deriving ((forall x. BuildType -> Rep BuildType x)
-> (forall x. Rep BuildType x -> BuildType) -> Generic BuildType
forall x. Rep BuildType x -> BuildType
forall x. BuildType -> Rep BuildType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildType x -> BuildType
$cfrom :: forall x. BuildType -> Rep BuildType x
Generic, Int -> BuildType -> ShowS
[BuildType] -> ShowS
BuildType -> String
(Int -> BuildType -> ShowS)
-> (BuildType -> String)
-> ([BuildType] -> ShowS)
-> Show BuildType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildType] -> ShowS
$cshowList :: [BuildType] -> ShowS
show :: BuildType -> String
$cshow :: BuildType -> String
showsPrec :: Int -> BuildType -> ShowS
$cshowsPrec :: Int -> BuildType -> ShowS
Show, ReadPrec [BuildType]
ReadPrec BuildType
Int -> ReadS BuildType
ReadS [BuildType]
(Int -> ReadS BuildType)
-> ReadS [BuildType]
-> ReadPrec BuildType
-> ReadPrec [BuildType]
-> Read BuildType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BuildType]
$creadListPrec :: ReadPrec [BuildType]
readPrec :: ReadPrec BuildType
$creadPrec :: ReadPrec BuildType
readList :: ReadS [BuildType]
$creadList :: ReadS [BuildType]
readsPrec :: Int -> ReadS BuildType
$creadsPrec :: Int -> ReadS BuildType
Read, BuildType -> BuildType -> Bool
(BuildType -> BuildType -> Bool)
-> (BuildType -> BuildType -> Bool) -> Eq BuildType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildType -> BuildType -> Bool
$c/= :: BuildType -> BuildType -> Bool
== :: BuildType -> BuildType -> Bool
$c== :: BuildType -> BuildType -> Bool
Eq, Typeable, Typeable BuildType
DataType
Constr
Typeable BuildType
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> BuildType -> c BuildType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c BuildType)
-> (BuildType -> Constr)
-> (BuildType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c BuildType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildType))
-> ((forall b. Data b => b -> b) -> BuildType -> BuildType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> BuildType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> BuildType -> r)
-> (forall u. (forall d. Data d => d -> u) -> BuildType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> BuildType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> BuildType -> m BuildType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> BuildType -> m BuildType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> BuildType -> m BuildType)
-> Data BuildType
BuildType -> DataType
BuildType -> Constr
(forall b. Data b => b -> b) -> BuildType -> BuildType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildType -> c BuildType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildType
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> BuildType -> u
forall u. (forall d. Data d => d -> u) -> BuildType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BuildType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BuildType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BuildType -> m BuildType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BuildType -> m BuildType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildType -> c BuildType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BuildType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildType)
$cCustom :: Constr
$cMake :: Constr
$cConfigure :: Constr
$cSimple :: Constr
$tBuildType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> BuildType -> m BuildType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BuildType -> m BuildType
gmapMp :: (forall d. Data d => d -> m d) -> BuildType -> m BuildType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BuildType -> m BuildType
gmapM :: (forall d. Data d => d -> m d) -> BuildType -> m BuildType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BuildType -> m BuildType
gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BuildType -> u
gmapQ :: (forall d. Data d => d -> u) -> BuildType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BuildType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BuildType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BuildType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BuildType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BuildType -> r
gmapT :: (forall b. Data b => b -> b) -> BuildType -> BuildType
$cgmapT :: (forall b. Data b => b -> b) -> BuildType -> BuildType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c BuildType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BuildType)
dataTypeOf :: BuildType -> DataType
$cdataTypeOf :: BuildType -> DataType
toConstr :: BuildType -> Constr
$ctoConstr :: BuildType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BuildType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildType -> c BuildType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BuildType -> c BuildType
$cp1Data :: Typeable BuildType
Data)

instance Binary BuildType
instance Structured BuildType
instance NFData BuildType where rnf :: BuildType -> ()
rnf = BuildType -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

knownBuildTypes :: [BuildType]
knownBuildTypes :: [BuildType]
knownBuildTypes = [BuildType
Simple, BuildType
Configure, BuildType
Make, BuildType
Custom]

instance Pretty BuildType where
  pretty :: BuildType -> Doc
pretty = String -> Doc
Disp.text (String -> Doc) -> (BuildType -> String) -> BuildType -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildType -> String
forall a. Show a => a -> String
show

instance Parsec BuildType where
  parsec :: m BuildType
parsec = do
    String
name <- (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 Char -> Bool
isAlphaNum
    case String
name of
      String
"Simple"    -> BuildType -> m BuildType
forall (m :: * -> *) a. Monad m => a -> m a
return BuildType
Simple
      String
"Configure" -> BuildType -> m BuildType
forall (m :: * -> *) a. Monad m => a -> m a
return BuildType
Configure
      String
"Custom"    -> BuildType -> m BuildType
forall (m :: * -> *) a. Monad m => a -> m a
return BuildType
Custom
      String
"Make"      -> BuildType -> m BuildType
forall (m :: * -> *) a. Monad m => a -> m a
return BuildType
Make
      String
"Default"   -> do
          CabalSpecVersion
v <- m CabalSpecVersion
forall (m :: * -> *). CabalParsing m => m CabalSpecVersion
askCabalSpecVersion
          if CabalSpecVersion
v CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
<= CabalSpecVersion
CabalSpecV1_18 -- oldest version needing this, based on hackage-tests
          then do
              PWarnType -> String -> m ()
forall (m :: * -> *). CabalParsing m => PWarnType -> String -> m ()
parsecWarning PWarnType
PWTBuildTypeDefault String
"build-type: Default is parsed as Custom for legacy reasons. See https://github.com/haskell/cabal/issues/5020"
              BuildType -> m BuildType
forall (m :: * -> *) a. Monad m => a -> m a
return BuildType
Custom
          else String -> m BuildType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"unknown build-type: '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'")
      String
_           -> String -> m BuildType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"unknown build-type: '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'")