| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Language.Haskell.Refact.Utils.Monad
Contents
- 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 VerboseLevel Source #
Instances
data RefactSettings Source #
Constructors
| RefSet | |
Fields 
  | |
Instances
data RefactState Source #
State for refactoring a single file. Holds/hides the ghc-exactprint annotations, which get updated transparently at key points.
Constructors
| RefSt | |
Fields 
  | |
Instances
data RefactModule Source #
Constructors
| RefMod | |
Fields 
  | |
Instances
data RefacSource Source #
Constructors
| RSFile FilePath | |
| RSTarget TargetModule | |
| RSMod ModSummary | |
| RSAlreadyLoaded | 
type TargetModule = ModulePath Source #
type CabalGraph = Map ChComponentName (GmComponent GMCResolved (Set ModulePath)) Source #
data RefactStashId Source #
Instances
data RefactFlags Source #
Instances
data StateStorage Source #
Provide some temporary storage while the refactoring is taking place
Constructors
| StorageNone | |
| StorageBind (LHsBind Name) | |
| StorageSig (LSig Name) | |
| StorageBindRdr (LHsBind RdrName) | |
| StorageDeclRdr (LHsDecl RdrName) | |
| StorageSigRdr (LSig RdrName) | 
Instances
Constructors
| RefactGhc | |
Fields 
  | |
Instances
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 #