Safe Haskell | None |
---|---|
Language | Haskell98 |
- type ParseResult = TypecheckedModule
- data VerboseLevel
- data RefactSettings = RefSet {
- rsetVerboseLevel :: !VerboseLevel
- rsetEnabledTargets :: (Bool, Bool, Bool, Bool)
- data RefactState = RefSt {
- rsSettings :: !RefactSettings
- rsUniqState :: !Int
- rsSrcSpanCol :: !Int
- rsFlags :: !RefactFlags
- rsStorage :: !StateStorage
- rsCurrentTarget :: !(Maybe TargetModule)
- rsModule :: !(Maybe RefactModule)
- data RefactModule = RefMod {}
- data RefacSource
- type TargetModule = ModulePath
- type Targets = [Either FilePath ModuleName]
- type CabalGraph = Map ChComponentName (GmComponent GMCResolved (Set ModulePath))
- data RefactStashId = Stash !String
- data RefactFlags = RefFlags {}
- data StateStorage
- newtype RefactGhc a = RefactGhc {
- unRefactGhc :: GhcModT (StateT RefactState IO) a
- runRefactGhc :: RefactGhc a -> RefactState -> Options -> IO (a, RefactState)
- getRefacSettings :: RefactGhc RefactSettings
- defaultSettings :: RefactSettings
- logSettings :: RefactSettings
- cabalModuleGraphs :: RefactGhc [GmModuleGraph]
- canonicalizeGraph :: [ModSummary] -> RefactGhc [(Maybe FilePath, ModSummary)]
- canonicalizeModSummary :: MonadIO m => ModSummary -> m (Maybe FilePath, ModSummary)
- logm :: String -> RefactGhc ()
Documentation
type ParseResult = TypecheckedModule Source #
Result of parsing a Haskell source file. It is simply the TypeCheckedModule produced by GHC.
data RefactSettings Source #
RefSet | |
|
data RefactState Source #
State for refactoring a single file. Holds/hides the ghc-exactprint annotations, which get updated transparently at key points.
RefSt | |
|
data RefactModule Source #
RefMod | |
|
type TargetModule = ModulePath Source #
type CabalGraph = Map ChComponentName (GmComponent GMCResolved (Set ModulePath)) Source #
data RefactStashId Source #
data RefactFlags Source #
data StateStorage Source #
Provide some temporary storage while the refactoring is taking place
RefactGhc | |
|
runRefactGhc :: RefactGhc a -> RefactState -> Options -> IO (a, RefactState) Source #
canonicalizeGraph :: [ModSummary] -> RefactGhc [(Maybe FilePath, ModSummary)] Source #
canonicalizeModSummary :: MonadIO m => ModSummary -> m (Maybe FilePath, ModSummary) Source #