Support GHC 9.12
[cabal.git] / Cabal / src / Distribution / Simple / UserHooks.hs
blobb27cd0b875f43a9c2ec6baffbfadf0166f8d74a9
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE RankNTypes #-}
4 -----------------------------------------------------------------------------
6 -- |
7 -- Module : Distribution.Simple.UserHooks
8 -- Copyright : Isaac Jones 2003-2005
9 -- License : BSD3
11 -- Maintainer : cabal-devel@haskell.org
12 -- Portability : portable
14 -- This defines the API that @Setup.hs@ scripts can use to customise the way
15 -- the build works. This module just defines the 'UserHooks' type. The
16 -- predefined sets of hooks that implement the @Simple@, @Make@ and @Configure@
17 -- build systems are defined in "Distribution.Simple". The 'UserHooks' is a big
18 -- record of functions. There are 3 for each action, a pre, post and the action
19 -- itself. There are few other miscellaneous hooks, ones to extend the set of
20 -- programs and preprocessors and one to override the function used to read the
21 -- @.cabal@ file.
23 -- This hooks type is widely agreed to not be the right solution. Partly this
24 -- is because changes to it usually break custom @Setup.hs@ files and yet many
25 -- internal code changes do require changes to the hooks. For example we cannot
26 -- pass any extra parameters to most of the functions that implement the
27 -- various phases because it would involve changing the types of the
28 -- corresponding hook. At some point it will have to be replaced.
29 module Distribution.Simple.UserHooks
30 ( UserHooks (..)
31 , Args
32 , emptyUserHooks
33 ) where
35 import Distribution.Compat.Prelude
36 import Prelude ()
38 import Distribution.PackageDescription
39 import Distribution.Simple.Command
40 import Distribution.Simple.LocalBuildInfo
41 import Distribution.Simple.PreProcess
42 import Distribution.Simple.Program
43 import Distribution.Simple.Setup
45 type Args = [String]
47 -- | Hooks allow authors to add specific functionality before and after a
48 -- command is run, and also to specify additional preprocessors.
50 -- * WARNING: The hooks interface is under rather constant flux as we try to
51 -- understand users needs. Setup files that depend on this interface may
52 -- break in future releases.
53 data UserHooks = UserHooks
54 { readDesc :: IO (Maybe GenericPackageDescription)
55 -- ^ Read the description file
56 , hookedPreProcessors :: [PPSuffixHandler]
57 -- ^ Custom preprocessors in addition to and overriding 'knownSuffixHandlers'.
58 , hookedPrograms :: [Program]
59 -- ^ These programs are detected at configure time. Arguments for them are
60 -- added to the configure command.
61 , preConf :: Args -> ConfigFlags -> IO HookedBuildInfo
62 -- ^ Hook to run before configure command
63 , confHook
64 :: (GenericPackageDescription, HookedBuildInfo)
65 -> ConfigFlags
66 -> IO LocalBuildInfo
67 -- ^ Over-ride this hook to get different behavior during configure.
68 , postConf :: Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
69 -- ^ Hook to run after configure command
70 , preBuild :: Args -> BuildFlags -> IO HookedBuildInfo
71 -- ^ Hook to run before build command. Second arg indicates verbosity level.
72 , buildHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
73 -- ^ Over-ride this hook to get different behavior during build.
74 , postBuild :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
75 -- ^ Hook to run after build command. Second arg indicates verbosity level.
76 , preRepl :: Args -> ReplFlags -> IO HookedBuildInfo
77 -- ^ Hook to run before repl command. Second arg indicates verbosity level.
78 , replHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
79 -- ^ Over-ride this hook to get different behavior during interpretation.
80 , postRepl :: Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO ()
81 -- ^ Hook to run after repl command. Second arg indicates verbosity level.
82 , preClean :: Args -> CleanFlags -> IO HookedBuildInfo
83 -- ^ Hook to run before clean command. Second arg indicates verbosity level.
84 , cleanHook :: PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()
85 -- ^ Over-ride this hook to get different behavior during clean.
86 , postClean :: Args -> CleanFlags -> PackageDescription -> () -> IO ()
87 -- ^ Hook to run after clean command. Second arg indicates verbosity level.
88 , preCopy :: Args -> CopyFlags -> IO HookedBuildInfo
89 -- ^ Hook to run before copy command
90 , copyHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
91 -- ^ Over-ride this hook to get different behavior during copy.
92 , postCopy :: Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO ()
93 -- ^ Hook to run after copy command
94 , preInst :: Args -> InstallFlags -> IO HookedBuildInfo
95 -- ^ Hook to run before install command
96 , instHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
97 -- ^ Over-ride this hook to get different behavior during install.
98 , postInst :: Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO ()
99 -- ^ Hook to run after install command. postInst should be run
100 -- on the target, not on the build machine.
101 , preReg :: Args -> RegisterFlags -> IO HookedBuildInfo
102 -- ^ Hook to run before register command
103 , regHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
104 -- ^ Over-ride this hook to get different behavior during registration.
105 , postReg :: Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()
106 -- ^ Hook to run after register command
107 , preUnreg :: Args -> RegisterFlags -> IO HookedBuildInfo
108 -- ^ Hook to run before unregister command
109 , unregHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
110 -- ^ Over-ride this hook to get different behavior during unregistration.
111 , postUnreg :: Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()
112 -- ^ Hook to run after unregister command
113 , preHscolour :: Args -> HscolourFlags -> IO HookedBuildInfo
114 -- ^ Hook to run before hscolour command. Second arg indicates verbosity level.
115 , hscolourHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
116 -- ^ Over-ride this hook to get different behavior during hscolour.
117 , postHscolour :: Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO ()
118 -- ^ Hook to run after hscolour command. Second arg indicates verbosity level.
119 , preHaddock :: Args -> HaddockFlags -> IO HookedBuildInfo
120 -- ^ Hook to run before haddock command. Second arg indicates verbosity level.
121 , haddockHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
122 -- ^ Over-ride this hook to get different behavior during haddock.
123 , postHaddock :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ()
124 -- ^ Hook to run after haddock command. Second arg indicates verbosity level.
125 , preTest :: Args -> TestFlags -> IO HookedBuildInfo
126 -- ^ Hook to run before test command.
127 , testHook :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO ()
128 -- ^ Over-ride this hook to get different behavior during test.
129 , postTest :: Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO ()
130 -- ^ Hook to run after test command.
131 , preBench :: Args -> BenchmarkFlags -> IO HookedBuildInfo
132 -- ^ Hook to run before bench command.
133 , benchHook :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO ()
134 -- ^ Over-ride this hook to get different behavior during bench.
135 , postBench :: Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO ()
136 -- ^ Hook to run after bench command.
139 -- | Empty 'UserHooks' which do nothing.
140 emptyUserHooks :: UserHooks
141 emptyUserHooks =
142 UserHooks
143 { readDesc = return Nothing
144 , hookedPreProcessors = []
145 , hookedPrograms = []
146 , preConf = rn'
147 , confHook = (\_ _ -> return (error "No local build info generated during configure. Over-ride empty configure hook."))
148 , postConf = ru
149 , preBuild = rn'
150 , buildHook = ru
151 , postBuild = ru
152 , preRepl = \_ _ -> return emptyHookedBuildInfo
153 , replHook = \_ _ _ _ _ -> return ()
154 , postRepl = ru
155 , preClean = rn
156 , cleanHook = ru
157 , postClean = ru
158 , preCopy = rn'
159 , copyHook = ru
160 , postCopy = ru
161 , preInst = rn
162 , instHook = ru
163 , postInst = ru
164 , preReg = rn'
165 , regHook = ru
166 , postReg = ru
167 , preUnreg = rn
168 , unregHook = ru
169 , postUnreg = ru
170 , preHscolour = rn
171 , hscolourHook = ru
172 , postHscolour = ru
173 , preHaddock = rn'
174 , haddockHook = ru
175 , postHaddock = ru
176 , preTest = rn'
177 , testHook = \_ -> ru
178 , postTest = ru
179 , preBench = rn'
180 , benchHook = \_ -> ru
181 , postBench = ru
183 where
184 rn args _ = noExtraFlags args >> return emptyHookedBuildInfo
185 rn' _ _ = return emptyHookedBuildInfo
186 ru _ _ _ _ = return ()