Make “sublibrary” standard terminology in docs
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Install.hs
bloba0502693ec47c2b3f6a961edd27368199f9ffbdf
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Simple.Setup.Install
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 install command-line options.
19 -- See: @Distribution.Simple.Setup@
20 module Distribution.Simple.Setup.Install
21 ( InstallFlags (..)
22 , emptyInstallFlags
23 , defaultInstallFlags
24 , installCommand
25 ) where
27 import Distribution.Compat.Prelude hiding (get)
28 import Prelude ()
30 import Distribution.ReadE
31 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
32 import Distribution.Simple.Compiler
33 import Distribution.Simple.Flag
34 import Distribution.Simple.InstallDirs
35 import Distribution.Simple.Utils
36 import Distribution.Verbosity
38 import Distribution.Simple.Setup.Common
40 -- ------------------------------------------------------------
42 -- * Install flags
44 -- ------------------------------------------------------------
46 -- | Flags to @install@: (package db, verbosity)
47 data InstallFlags = InstallFlags
48 { installPackageDB :: Flag PackageDB
49 , installDest :: Flag CopyDest
50 , installDistPref :: Flag FilePath
51 , installUseWrapper :: Flag Bool
52 , installInPlace :: Flag Bool
53 , installVerbosity :: Flag Verbosity
54 , -- this is only here, because we can not
55 -- change the hooks API.
56 installCabalFilePath :: Flag FilePath
58 deriving (Show, Generic)
60 defaultInstallFlags :: InstallFlags
61 defaultInstallFlags =
62 InstallFlags
63 { installPackageDB = NoFlag
64 , installDest = Flag NoCopyDest
65 , installDistPref = NoFlag
66 , installUseWrapper = Flag False
67 , installInPlace = Flag False
68 , installVerbosity = Flag normal
69 , installCabalFilePath = mempty
72 installCommand :: CommandUI InstallFlags
73 installCommand =
74 CommandUI
75 { commandName = "install"
76 , commandSynopsis =
77 "Copy the files into the install locations. Run register."
78 , commandDescription = Just $ \_ ->
79 wrapText $
80 "Unlike the copy command, install calls the register command. "
81 ++ "If you want to install into a location that is not what was "
82 ++ "specified in the configure step, use the copy command.\n"
83 , commandNotes = Nothing
84 , commandUsage = \pname ->
85 "Usage: " ++ pname ++ " install [FLAGS]\n"
86 , commandDefaultFlags = defaultInstallFlags
87 , commandOptions = \showOrParseArgs -> case showOrParseArgs of
88 ShowArgs ->
89 filter
90 ( (`notElem` ["target-package-db"])
91 . optionName
93 $ installOptions ShowArgs
94 ParseArgs -> installOptions ParseArgs
97 installOptions :: ShowOrParseArgs -> [OptionField InstallFlags]
98 installOptions showOrParseArgs =
99 [ optionVerbosity installVerbosity (\v flags -> flags{installVerbosity = v})
100 , optionDistPref
101 installDistPref
102 (\d flags -> flags{installDistPref = d})
103 showOrParseArgs
104 , option
106 ["inplace"]
107 "install the package in the install subdirectory of the dist prefix, so it can be used without being installed"
108 installInPlace
109 (\v flags -> flags{installInPlace = v})
110 trueArg
111 , option
113 ["shell-wrappers"]
114 "using shell script wrappers around executables"
115 installUseWrapper
116 (\v flags -> flags{installUseWrapper = v})
117 (boolOpt [] [])
118 , option
120 ["package-db"]
122 installPackageDB
123 (\v flags -> flags{installPackageDB = v})
124 ( choiceOpt
126 ( Flag UserPackageDB
127 , ([], ["user"])
128 , "upon configuration register this package in the user's local package database"
131 ( Flag GlobalPackageDB
132 , ([], ["global"])
133 , "(default) upon configuration register this package in the system-wide package database"
137 , option
139 ["target-package-db"]
140 "package database to install into. Required when using ${pkgroot} prefix."
141 installDest
142 (\v flags -> flags{installDest = v})
143 ( reqArg
144 "DATABASE"
145 (succeedReadE (Flag . CopyToDb))
146 (\f -> case f of Flag (CopyToDb p) -> [p]; _ -> [])
150 emptyInstallFlags :: InstallFlags
151 emptyInstallFlags = mempty
153 instance Monoid InstallFlags where
154 mempty = gmempty
155 mappend = (<>)
157 instance Semigroup InstallFlags where
158 (<>) = gmappend