make LTS branch pre-releases
[cabal.git] / Cabal-syntax / src / Distribution / Types / BuildType.hs
blobb94279eaf2e67fbbe0a8a929361d53a61153e02f
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE OverloadedStrings #-}
5 module Distribution.Types.BuildType
6 ( BuildType (..)
7 , knownBuildTypes
8 ) where
10 import Distribution.Compat.Prelude
11 import Prelude ()
13 import Distribution.CabalSpecVersion (CabalSpecVersion (..))
14 import Distribution.Parsec
15 import Distribution.Pretty
17 import qualified Distribution.Compat.CharParsing as P
18 import qualified Text.PrettyPrint as Disp
20 -- | The type of build system used by this package.
21 data BuildType
22 = -- | calls @Distribution.Simple.defaultMain@
23 Simple
24 | -- | calls @Distribution.Simple.defaultMainWithHooks defaultUserHooks@,
25 -- which invokes @configure@ to generate additional build
26 -- information used by later phases.
27 Configure
28 | -- | calls @Distribution.Make.defaultMain@
29 Make
30 | -- | uses user-supplied @Setup.hs@ or @Setup.lhs@ (default)
31 Custom
32 | Hooks
33 deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)
35 instance Binary BuildType
36 instance Structured BuildType
37 instance NFData BuildType where rnf = genericRnf
39 knownBuildTypes :: [BuildType]
40 knownBuildTypes = [Simple, Configure, Make, Custom, Hooks]
42 instance Pretty BuildType where
43 pretty = Disp.text . show
45 instance Parsec BuildType where
46 parsec = do
47 name <- P.munch1 isAlphaNum
48 case name of
49 "Simple" -> return Simple
50 "Configure" -> return Configure
51 "Custom" -> return Custom
52 "Make" -> return Make
53 "Hooks" -> do
54 v <- askCabalSpecVersion
55 if v >= CabalSpecV3_14
56 then return Hooks
57 else fail "build-type: 'Hooks'. This feature requires cabal-version >= 3.14."
58 "Default" -> do
59 v <- askCabalSpecVersion
60 if v <= CabalSpecV1_18 -- oldest version needing this, based on hackage-tests
61 then do
62 parsecWarning PWTBuildTypeDefault "build-type: Default is parsed as Custom for legacy reasons. See https://github.com/haskell/cabal/issues/5020"
63 return Custom
64 else fail ("unknown build-type: '" ++ name ++ "'")
65 _ -> fail ("unknown build-type: '" ++ name ++ "'")