| Safe Haskell | None | 
|---|
Language.Haskell.Refact.Utils.Monad
- type ParseResult = TypecheckedModule
 - data VerboseLevel
 - data  RefactSettings  = RefSet {
- rsetGhcOpts :: ![String]
 - rsetImportPaths :: ![FilePath]
 - rsetExpandSplice :: Bool
 - rsetLineSeparator :: LineSeparator
 - rsetMainFile :: Maybe [FilePath]
 - rsetCheckTokenUtilsInvariant :: !Bool
 - rsetVerboseLevel :: !VerboseLevel
 - rsetEnabledTargets :: (Bool, Bool, Bool, Bool)
 
 - data  RefactState  = RefSt {
- rsSettings :: !RefactSettings
 - rsUniqState :: !Int
 - rsFlags :: !RefactFlags
 - rsStorage :: !StateStorage
 - rsGraph :: [TargetGraph]
 - rsModuleGraph :: [([FilePath], ModuleGraph)]
 - rsCurrentTarget :: Maybe [FilePath]
 - rsModule :: !(Maybe RefactModule)
 
 - data  RefactModule  = RefMod {
- rsTypecheckedMod :: !TypecheckedModule
 - rsOrigTokenStream :: ![PosToken]
 - rsTokenCache :: !(TokenCache PosToken)
 - rsStreamModified :: !Bool
 
 - type TargetModule = ([FilePath], ModSummary)
 - data RefactStashId = Stash !String
 - data  RefactFlags  = RefFlags {
- rsDone :: !Bool
 
 - data  StateStorage 
- = StorageNone
 - | StorageBind (LHsBind Name)
 - | StorageSig (LSig Name)
 
 - type RefactGhc a = GhcT (StateT RefactState IO) a
 - runRefactGhc :: RefactGhc a -> RefactState -> IO (a, RefactState)
 - getRefacSettings :: RefactGhc RefactSettings
 - defaultSettings :: RefactSettings
 - logSettings :: RefactSettings
 - initGhcSession :: Cradle -> [FilePath] -> RefactGhc ()
 - loadModuleGraphGhc :: Maybe [FilePath] -> RefactGhc ()
 - ensureTargetLoaded :: TargetModule -> RefactGhc ModSummary
 - canonicalizeGraph :: [ModSummary] -> IO [(Maybe FilePath, ModSummary)]
 - logm :: String -> RefactGhc ()
 
Documentation
type ParseResult = TypecheckedModuleSource
Result of parsing a Haskell source file. It is simply the TypeCheckedModule produced by GHC.
data RefactSettings Source
Constructors
| RefSet | |
Fields 
  | |
Instances
| Show RefactSettings | 
data RefactState Source
State for refactoring a single file. Holds/hides the token stream, which gets updated transparently at key points.
Constructors
| RefSt | |
Fields 
  | |
Instances
| MonadState RefactState (GhcT (StateT RefactState IO)) | |
| MonadIO (GhcT (StateT RefactState IO)) | |
| MonadIO (StateT RefactState IO) | 
data RefactModule Source
Constructors
| RefMod | |
Fields 
  | |
type TargetModule = ([FilePath], ModSummary)Source
data RefactStashId Source
Constructors
| Stash !String | 
Instances
| Eq RefactStashId | |
| Ord RefactStashId | |
| Show RefactStashId | 
data RefactFlags Source
data StateStorage Source
Provide some temporary storage while the refactoring is taking place
Constructors
| StorageNone | |
| StorageBind (LHsBind Name) | |
| StorageSig (LSig Name) | 
Instances
| Show StateStorage | 
type RefactGhc a = GhcT (StateT RefactState IO) aSource
runRefactGhc :: RefactGhc a -> RefactState -> IO (a, RefactState)Source
initGhcSession :: Cradle -> [FilePath] -> RefactGhc ()Source
Initialise the GHC session, when starting a refactoring. This should never be called directly.
loadModuleGraphGhc :: Maybe [FilePath] -> RefactGhc ()Source
Load a module graph into the GHC session, starting from main
ensureTargetLoaded :: TargetModule -> RefactGhc ModSummarySource
Make sure the given file is the currently loaded target, and load it if not. Assumes that all the module graphs had been generated before, so these are not updated.
canonicalizeGraph :: [ModSummary] -> IO [(Maybe FilePath, ModSummary)]Source