Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Options = Options_ [Rewrite Universe] AnnotatedImports
- data Options_ rewrites imports = Options {
- additionalImports :: imports
- colorise :: ColoriseFun
- elaborations :: rewrites
- executionMode :: ExecutionMode
- extraIgnores :: [FilePath]
- fixityEnv :: FixityEnv
- iterateN :: Int
- noDefaultElaborations :: Bool
- randomOrder :: Bool
- rewrites :: rewrites
- roundtrips :: [RoundTrip]
- singleThreaded :: Bool
- targetDir :: FilePath
- targetFiles :: [FilePath]
- verbosity :: Verbosity
- data ExecutionMode
- defaultOptions :: (Default rewrites, Default imports) => FilePath -> Options_ rewrites imports
- parseOptions :: FixityEnv -> IO Options
- buildGrepChain :: FilePath -> HashSet String -> [FilePath] -> GrepCommands
- forFn :: Options_ x y -> [a] -> (a -> IO b) -> IO [b]
- getOptionsParser :: FixityEnv -> IO (Parser ProtoOptions)
- getTargetFiles :: Options_ a b -> [GroundTerms] -> IO [FilePath]
- parseRewritesInternal :: Options_ a b -> [RewriteSpec] -> IO [Rewrite Universe]
- parseVerbosity :: Verbosity -> Parser Verbosity
- type ProtoOptions = Options_ [RewriteSpec] [String]
- resolveOptions :: ProtoOptions -> IO Options
- data GrepCommands = GrepCommands {
- initialFileSet :: [FilePath]
- commandChain :: [CommandLine]
Options
data Options_ rewrites imports Source #
Options | |
|
data ExecutionMode Source #
Controls the ultimate action taken by apply
. The default action is
ExecRewrite
.
ExecDryRun | Pretend to do rewrites, show diff. |
ExecRewrite | Perform rewrites. |
ExecExtract | Print the resulting expression for each match. |
ExecSearch | Print the matched expressions. |
Instances
Show ExecutionMode Source # | |
Defined in Retrie.Options showsPrec :: Int -> ExecutionMode -> ShowS # show :: ExecutionMode -> String # showList :: [ExecutionMode] -> ShowS # |
defaultOptions :: (Default rewrites, Default imports) => FilePath -> Options_ rewrites imports Source #
Construct default options for the given target directory.
Internal
buildGrepChain :: FilePath -> HashSet String -> [FilePath] -> GrepCommands Source #
Return a chain of grep commands to find files with relevant groundTerms If filesGiven is empty, use all *.hs files under targetDir
getOptionsParser :: FixityEnv -> IO (Parser ProtoOptions) Source #
Get the options parser. The returned ProtoOptions
should be passed
to resolveOptions
to get final Options
.
getTargetFiles :: Options_ a b -> [GroundTerms] -> IO [FilePath] Source #
Find all files to target for rewriting.
parseRewritesInternal :: Options_ a b -> [RewriteSpec] -> IO [Rewrite Universe] Source #
Create Rewrite
s from string specifications of rewrites.
We expose this from Retrie with a nicer type signature as
parseRewrites
. We have it here so we can use it with
ProtoOptions
.
type ProtoOptions = Options_ [RewriteSpec] [String] Source #
Options that have been parsed, but not fully resolved.
resolveOptions :: ProtoOptions -> IO Options Source #
Resolve ProtoOptions
into Options
. Parses rewrites into Rewrite
s,
parses imports, validates options, and extends fixityEnv
with any
declared fixities in the target directory.
data GrepCommands Source #
GrepCommands | |
|
Instances
Eq GrepCommands Source # | |
Defined in Retrie.Options (==) :: GrepCommands -> GrepCommands -> Bool # (/=) :: GrepCommands -> GrepCommands -> Bool # | |
Show GrepCommands Source # | |
Defined in Retrie.Options showsPrec :: Int -> GrepCommands -> ShowS # show :: GrepCommands -> String # showList :: [GrepCommands] -> ShowS # |