retrie-0.1.0.0: A powerful, easy-to-use codemodding tool for Haskell.

Safe HaskellNone
LanguageHaskell2010

Retrie.Options

Contents

Synopsis

Options

type Options = Options_ [Rewrite Universe] AnnotatedImports Source #

Command-line options.

data Options_ rewrites imports Source #

Constructors

Options 

Fields

  • additionalImports :: imports

    Imports specified by the command-line flag '--import'.

  • colorise :: ColoriseFun

    Function used to colorize results of certain execution modes.

  • executionMode :: ExecutionMode

    Controls behavior of apply. See ExecutionMode.

  • extraIgnores :: [FilePath]

    Specific files that should be ignored. Paths should be relative to targetDir.

  • fixityEnv :: FixityEnv

    Fixity information for operators used during parsing (of rewrites and target modules). Defaults to base fixities.

  • iterateN :: Int

    Iterate the given rewrites or Retrie computation up to this many times. Iteration may stop before the limit if no changes are made during a given iteration.

  • randomOrder :: Bool

    Whether to randomize the order of target modules before rewriting them.

  • rewrites :: rewrites

    Rewrites specified by command-line flags such as '--adhoc'.

  • roundtrips :: [RoundTrip]

    Paths that should be roundtripped through ghc-exactprint to debug. Specified by the '--roundtrip' command-line flag.

  • singleThreaded :: Bool

    Whether to concurrently rewrite target modules. Mostly useful for viewing debugging output without interleaving it.

  • targetDir :: FilePath

    Directory that contains the code being targeted for rewriting.

  • targetFiles :: [FilePath]

    Instead of targeting all Haskell files in targetDir, only target specific files. Paths should be relative to targetDir.

  • verbosity :: Verbosity

    How much should be output on stdout.

data ExecutionMode Source #

Controls the ultimate action taken by apply. The default action is ExecRewrite.

Constructors

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 # 
Instance details

Defined in Retrie.Options

defaultOptions :: (Default rewrites, Default imports) => FilePath -> Options_ rewrites imports Source #

Construct default options for the given target directory.

parseOptions :: FixityEnv -> IO Options Source #

Parse options using the given FixityEnv.

Internal

buildGrepChain :: FilePath -> HashSet String -> [FilePath] -> Either [FilePath] (String, [String]) Source #

Either returns an exact list of target paths, or a command for finding them.

forFn :: Options_ x y -> [a] -> (a -> IO b) -> IO [b] Source #

forM, but concurrency and input order controled by Options.

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 Rewrites 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 Rewrites, parses imports, validates options, and extends fixityEnv with any declared fixities in the target directory.