Make “sublibrary” standard terminology in docs
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Hscolour.hs
blob6b5e2761133a0a4629db41988ae2a03d86a8cd34
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Simple.Setup.Hscolour
11 -- Copyright : Isaac Jones 2003-2004
12 -- Duncan Coutts 2007
13 -- License : BSD3
15 -- Maintainer : cabal-devel@haskell.org
16 -- Portability : portable
18 -- Definition of the hscolour command-line options.
19 -- See: @Distribution.Simple.Setup@
20 module Distribution.Simple.Setup.Hscolour
21 ( HscolourFlags (..)
22 , emptyHscolourFlags
23 , defaultHscolourFlags
24 , hscolourCommand
25 ) where
27 import Distribution.Compat.Prelude hiding (get)
28 import Prelude ()
30 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
31 import Distribution.Simple.Flag
32 import Distribution.Verbosity
34 import Distribution.Simple.Setup.Common
36 -- ------------------------------------------------------------
38 -- * HsColour flags
40 -- ------------------------------------------------------------
42 data HscolourFlags = HscolourFlags
43 { hscolourCSS :: Flag FilePath
44 , hscolourExecutables :: Flag Bool
45 , hscolourTestSuites :: Flag Bool
46 , hscolourBenchmarks :: Flag Bool
47 , hscolourForeignLibs :: Flag Bool
48 , hscolourDistPref :: Flag FilePath
49 , hscolourVerbosity :: Flag Verbosity
50 , hscolourCabalFilePath :: Flag FilePath
52 deriving (Show, Generic, Typeable)
54 emptyHscolourFlags :: HscolourFlags
55 emptyHscolourFlags = mempty
57 defaultHscolourFlags :: HscolourFlags
58 defaultHscolourFlags =
59 HscolourFlags
60 { hscolourCSS = NoFlag
61 , hscolourExecutables = Flag False
62 , hscolourTestSuites = Flag False
63 , hscolourBenchmarks = Flag False
64 , hscolourDistPref = NoFlag
65 , hscolourForeignLibs = Flag False
66 , hscolourVerbosity = Flag normal
67 , hscolourCabalFilePath = mempty
70 instance Monoid HscolourFlags where
71 mempty = gmempty
72 mappend = (<>)
74 instance Semigroup HscolourFlags where
75 (<>) = gmappend
77 hscolourCommand :: CommandUI HscolourFlags
78 hscolourCommand =
79 CommandUI
80 { commandName = "hscolour"
81 , commandSynopsis =
82 "Generate HsColour colourised code, in HTML format."
83 , commandDescription = Just (\_ -> "Requires the hscolour program.\n")
84 , commandNotes = Just $ \_ ->
85 "Deprecated in favour of 'cabal haddock --hyperlink-source'."
86 , commandUsage = \pname ->
87 "Usage: " ++ pname ++ " hscolour [FLAGS]\n"
88 , commandDefaultFlags = defaultHscolourFlags
89 , commandOptions = \showOrParseArgs ->
90 [ optionVerbosity
91 hscolourVerbosity
92 (\v flags -> flags{hscolourVerbosity = v})
93 , optionDistPref
94 hscolourDistPref
95 (\d flags -> flags{hscolourDistPref = d})
96 showOrParseArgs
97 , option
99 ["executables"]
100 "Run hscolour for Executables targets"
101 hscolourExecutables
102 (\v flags -> flags{hscolourExecutables = v})
103 trueArg
104 , option
106 ["tests"]
107 "Run hscolour for Test Suite targets"
108 hscolourTestSuites
109 (\v flags -> flags{hscolourTestSuites = v})
110 trueArg
111 , option
113 ["benchmarks"]
114 "Run hscolour for Benchmark targets"
115 hscolourBenchmarks
116 (\v flags -> flags{hscolourBenchmarks = v})
117 trueArg
118 , option
120 ["foreign-libraries"]
121 "Run hscolour for Foreign Library targets"
122 hscolourForeignLibs
123 (\v flags -> flags{hscolourForeignLibs = v})
124 trueArg
125 , option
127 ["all"]
128 "Run hscolour for all targets"
129 ( \f ->
130 allFlags
131 [ hscolourExecutables f
132 , hscolourTestSuites f
133 , hscolourBenchmarks f
134 , hscolourForeignLibs f
137 ( \v flags ->
138 flags
139 { hscolourExecutables = v
140 , hscolourTestSuites = v
141 , hscolourBenchmarks = v
142 , hscolourForeignLibs = v
145 trueArg
146 , option
148 ["css"]
149 "Use a cascading style sheet"
150 hscolourCSS
151 (\v flags -> flags{hscolourCSS = v})
152 (reqArgFlag "PATH")