Merge pull request #10625 from cabalism/fix/project-config-path-haddock
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Hscolour.hs
blob1c62c2dedca03a479f866e0d3f4ebab35ca0058b
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE DeriveDataTypeable #-}
4 {-# LANGUAGE DeriveGeneric #-}
5 {-# LANGUAGE FlexibleContexts #-}
6 {-# LANGUAGE PatternSynonyms #-}
7 {-# LANGUAGE RankNTypes #-}
8 {-# LANGUAGE ViewPatterns #-}
10 -----------------------------------------------------------------------------
12 -- |
13 -- Module : Distribution.Simple.Setup.Hscolour
14 -- Copyright : Isaac Jones 2003-2004
15 -- Duncan Coutts 2007
16 -- License : BSD3
18 -- Maintainer : cabal-devel@haskell.org
19 -- Portability : portable
21 -- Definition of the hscolour command-line options.
22 -- See: @Distribution.Simple.Setup@
23 module Distribution.Simple.Setup.Hscolour
24 ( HscolourFlags
25 ( HscolourCommonFlags
26 , hscolourVerbosity
27 , hscolourDistPref
28 , hscolourCabalFilePath
29 , hscolourWorkingDir
30 , hscolourTargets
31 , ..
33 , emptyHscolourFlags
34 , defaultHscolourFlags
35 , hscolourCommand
36 ) where
38 import Distribution.Compat.Prelude hiding (get)
39 import Prelude ()
41 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
42 import Distribution.Simple.Flag
43 import Distribution.Simple.Setup.Common
44 import Distribution.Utils.Path
45 import Distribution.Verbosity
47 -- ------------------------------------------------------------
49 -- * HsColour flags
51 -- ------------------------------------------------------------
53 data HscolourFlags = HscolourFlags
54 { hscolourCommonFlags :: !CommonSetupFlags
55 , hscolourCSS :: Flag FilePath
56 , hscolourExecutables :: Flag Bool
57 , hscolourTestSuites :: Flag Bool
58 , hscolourBenchmarks :: Flag Bool
59 , hscolourForeignLibs :: Flag Bool
61 deriving (Show, Generic, Typeable)
63 pattern HscolourCommonFlags
64 :: Flag Verbosity
65 -> Flag (SymbolicPath Pkg (Dir Dist))
66 -> Flag (SymbolicPath CWD (Dir Pkg))
67 -> Flag (SymbolicPath Pkg File)
68 -> [String]
69 -> HscolourFlags
70 pattern HscolourCommonFlags
71 { hscolourVerbosity
72 , hscolourDistPref
73 , hscolourWorkingDir
74 , hscolourCabalFilePath
75 , hscolourTargets
76 } <-
77 ( hscolourCommonFlags ->
78 CommonSetupFlags
79 { setupVerbosity = hscolourVerbosity
80 , setupDistPref = hscolourDistPref
81 , setupWorkingDir = hscolourWorkingDir
82 , setupCabalFilePath = hscolourCabalFilePath
83 , setupTargets = hscolourTargets
87 instance Binary HscolourFlags
88 instance Structured HscolourFlags
90 emptyHscolourFlags :: HscolourFlags
91 emptyHscolourFlags = mempty
93 defaultHscolourFlags :: HscolourFlags
94 defaultHscolourFlags =
95 HscolourFlags
96 { hscolourCommonFlags = defaultCommonSetupFlags
97 , hscolourCSS = NoFlag
98 , hscolourExecutables = Flag False
99 , hscolourTestSuites = Flag False
100 , hscolourBenchmarks = Flag False
101 , hscolourForeignLibs = Flag False
104 instance Monoid HscolourFlags where
105 mempty = gmempty
106 mappend = (<>)
108 instance Semigroup HscolourFlags where
109 (<>) = gmappend
111 hscolourCommand :: CommandUI HscolourFlags
112 hscolourCommand =
113 CommandUI
114 { commandName = "hscolour"
115 , commandSynopsis =
116 "Generate HsColour colourised code, in HTML format."
117 , commandDescription = Just (\_ -> "Requires the hscolour program.\n")
118 , commandNotes = Just $ \_ ->
119 "Deprecated in favour of 'cabal haddock --hyperlink-source'."
120 , commandUsage = \pname ->
121 "Usage: " ++ pname ++ " hscolour [FLAGS]\n"
122 , commandDefaultFlags = defaultHscolourFlags
123 , commandOptions = \showOrParseArgs ->
124 withCommonSetupOptions
125 hscolourCommonFlags
126 (\c f -> f{hscolourCommonFlags = c})
127 showOrParseArgs
128 [ option
130 ["executables"]
131 "Run hscolour for Executables targets"
132 hscolourExecutables
133 (\v flags -> flags{hscolourExecutables = v})
134 trueArg
135 , option
137 ["tests"]
138 "Run hscolour for Test Suite targets"
139 hscolourTestSuites
140 (\v flags -> flags{hscolourTestSuites = v})
141 trueArg
142 , option
144 ["benchmarks"]
145 "Run hscolour for Benchmark targets"
146 hscolourBenchmarks
147 (\v flags -> flags{hscolourBenchmarks = v})
148 trueArg
149 , option
151 ["foreign-libraries"]
152 "Run hscolour for Foreign Library targets"
153 hscolourForeignLibs
154 (\v flags -> flags{hscolourForeignLibs = v})
155 trueArg
156 , option
158 ["all"]
159 "Run hscolour for all targets"
160 ( \f ->
161 allFlags
162 [ hscolourExecutables f
163 , hscolourTestSuites f
164 , hscolourBenchmarks f
165 , hscolourForeignLibs f
168 ( \v flags ->
169 flags
170 { hscolourExecutables = v
171 , hscolourTestSuites = v
172 , hscolourBenchmarks = v
173 , hscolourForeignLibs = v
176 trueArg
177 , option
179 ["css"]
180 "Use a cascading style sheet"
181 hscolourCSS
182 (\v flags -> flags{hscolourCSS = v})
183 (reqArgFlag "PATH")