Add some Binary & Structured instances
[cabal.git] / Cabal / src / Distribution / Simple / Setup / Repl.hs
blob2fae5bffcd4f26c2f06deaa4c16cd5ea45d37c29
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE RankNTypes #-}
7 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Simple.Setup.Repl
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 repl command-line options.
19 -- See: @Distribution.Simple.Setup@
20 module Distribution.Simple.Setup.Repl
21 ( ReplFlags (..)
22 , defaultReplFlags
23 , replCommand
24 , ReplOptions (..)
25 , replOptions
26 ) where
28 import Distribution.Compat.Prelude hiding (get)
29 import Prelude ()
31 import Distribution.ReadE
32 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
33 import Distribution.Simple.Flag
34 import Distribution.Simple.Program
35 import Distribution.Simple.Utils
36 import Distribution.Verbosity
38 import Distribution.Simple.Setup.Common
40 -- ------------------------------------------------------------
42 -- * REPL Flags
44 -- ------------------------------------------------------------
46 data ReplOptions = ReplOptions
47 { replOptionsFlags :: [String]
48 , replOptionsNoLoad :: Flag Bool
49 , replOptionsFlagOutput :: Flag FilePath
51 deriving (Show, Generic, Typeable)
53 instance Binary ReplOptions
54 instance Structured ReplOptions
56 instance Monoid ReplOptions where
57 mempty = ReplOptions mempty (Flag False) NoFlag
58 mappend = (<>)
60 instance Semigroup ReplOptions where
61 (<>) = gmappend
63 data ReplFlags = ReplFlags
64 { replProgramPaths :: [(String, FilePath)]
65 , replProgramArgs :: [(String, [String])]
66 , replDistPref :: Flag FilePath
67 , replVerbosity :: Flag Verbosity
68 , replReload :: Flag Bool
69 , replReplOptions :: ReplOptions
71 deriving (Show, Generic, Typeable)
73 instance Binary ReplFlags
74 instance Structured ReplFlags
76 defaultReplFlags :: ReplFlags
77 defaultReplFlags =
78 ReplFlags
79 { replProgramPaths = mempty
80 , replProgramArgs = []
81 , replDistPref = NoFlag
82 , replVerbosity = Flag normal
83 , replReload = Flag False
84 , replReplOptions = mempty
87 instance Monoid ReplFlags where
88 mempty = gmempty
89 mappend = (<>)
91 instance Semigroup ReplFlags where
92 (<>) = gmappend
94 replCommand :: ProgramDb -> CommandUI ReplFlags
95 replCommand progDb =
96 CommandUI
97 { commandName = "repl"
98 , commandSynopsis =
99 "Open an interpreter session for the given component."
100 , commandDescription = Just $ \pname ->
101 wrapText $
102 "If the current directory contains no package, ignores COMPONENT "
103 ++ "parameters and opens an interactive interpreter session; if a "
104 ++ "sandbox is present, its package database will be used.\n"
105 ++ "\n"
106 ++ "Otherwise, (re)configures with the given or default flags, and "
107 ++ "loads the interpreter with the relevant modules. For executables, "
108 ++ "tests and benchmarks, loads the main module (and its "
109 ++ "dependencies); for libraries all exposed/other modules.\n"
110 ++ "\n"
111 ++ "The default component is the library itself, or the executable "
112 ++ "if that is the only component.\n"
113 ++ "\n"
114 ++ "Support for loading specific modules is planned but not "
115 ++ "implemented yet. For certain scenarios, `"
116 ++ pname
117 ++ " exec -- ghci :l Foo` may be used instead. Note that `exec` will "
118 ++ "not (re)configure and you will have to specify the location of "
119 ++ "other modules, if required.\n"
120 , commandNotes = Just $ \pname ->
121 "Examples:\n"
122 ++ " "
123 ++ pname
124 ++ " repl "
125 ++ " The first component in the package\n"
126 ++ " "
127 ++ pname
128 ++ " repl foo "
129 ++ " A named component (i.e. lib, exe, test suite)\n"
130 ++ " "
131 ++ pname
132 ++ " repl --repl-options=\"-lstdc++\""
133 ++ " Specifying flags for interpreter\n"
134 , -- TODO: re-enable once we have support for module/file targets
135 -- ++ " " ++ pname ++ " repl Foo.Bar "
136 -- ++ " A module\n"
137 -- ++ " " ++ pname ++ " repl Foo/Bar.hs"
138 -- ++ " A file\n\n"
139 -- ++ "If a target is ambiguous it can be qualified with the component "
140 -- ++ "name, e.g.\n"
141 -- ++ " " ++ pname ++ " repl foo:Foo.Bar\n"
142 -- ++ " " ++ pname ++ " repl testsuite1:Foo/Bar.hs\n"
143 commandUsage = \pname -> "Usage: " ++ pname ++ " repl [COMPONENT] [FLAGS]\n"
144 , commandDefaultFlags = defaultReplFlags
145 , commandOptions = \showOrParseArgs ->
146 optionVerbosity replVerbosity (\v flags -> flags{replVerbosity = v})
147 : optionDistPref
148 replDistPref
149 (\d flags -> flags{replDistPref = d})
150 showOrParseArgs
151 : programDbPaths
152 progDb
153 showOrParseArgs
154 replProgramPaths
155 (\v flags -> flags{replProgramPaths = v})
156 ++ programDbOption
157 progDb
158 showOrParseArgs
159 replProgramArgs
160 (\v flags -> flags{replProgramArgs = v})
161 ++ programDbOptions
162 progDb
163 showOrParseArgs
164 replProgramArgs
165 (\v flags -> flags{replProgramArgs = v})
166 ++ case showOrParseArgs of
167 ParseArgs ->
168 [ option
170 ["reload"]
171 "Used from within an interpreter to update files."
172 replReload
173 (\v flags -> flags{replReload = v})
174 trueArg
176 _ -> []
177 ++ map liftReplOption (replOptions showOrParseArgs)
179 where
180 liftReplOption = liftOption replReplOptions (\v flags -> flags{replReplOptions = v})
182 replOptions :: ShowOrParseArgs -> [OptionField ReplOptions]
183 replOptions _ =
184 [ option
186 ["repl-no-load"]
187 "Disable loading of project modules at REPL startup."
188 replOptionsNoLoad
189 (\p flags -> flags{replOptionsNoLoad = p})
190 trueArg
191 , option
193 ["repl-options"]
194 "Use the option(s) for the repl"
195 replOptionsFlags
196 (\p flags -> flags{replOptionsFlags = p})
197 (reqArg "FLAG" (succeedReadE words) id)
198 , option
200 ["repl-multi-file"]
201 "Write repl options to this directory rather than starting repl mode"
202 replOptionsFlagOutput
203 (\p flags -> flags{replOptionsFlagOutput = p})
204 (reqArg "DIR" (succeedReadE Flag) flagToList)