scion-0.1.0.1: Haskell IDE librarySource codeContentsIndex
Scion.Types
Portabilityportable
Stabilityexperimental
Maintainernominolo@gmail.com
Contents
The Scion Monad and Session State
Verbosity Levels
Reflection into IO
Compilation Results
Exceptions
Others / Helpers
Go To Definition
Description
Types used throughout Scion.
Synopsis
data SessionState = SessionState {
scionVerbosity :: Verbosity
initialDynFlags :: DynFlags
localBuildInfo :: Maybe LocalBuildInfo
activeComponent :: Maybe Component
lastCompResult :: CompilationResult
focusedModule :: Maybe ModSummary
bgTcCache :: Maybe BgTcCache
defSiteDB :: DefSiteDB
client :: String
}
mkSessionState :: DynFlags -> IO (IORef SessionState)
newtype ScionM a = ScionM {
unScionM :: IORef SessionState -> Ghc a
}
liftScionM :: Ghc a -> ScionM a
modifySessionState :: (SessionState -> SessionState) -> ScionM ()
getSessionState :: ScionM SessionState
gets :: (SessionState -> a) -> ScionM a
setSessionState :: SessionState -> ScionM ()
data Verbosity
= Silent
| Normal
| Verbose
| Deafening
intToVerbosity :: Int -> Verbosity
verbosityToInt :: Verbosity -> Int
silent :: Verbosity
normal :: Verbosity
verbose :: Verbosity
deafening :: Verbosity
getVerbosity :: ScionM Verbosity
setVerbosity :: Verbosity -> ScionM ()
message :: Verbosity -> String -> ScionM ()
reflectScionM :: ScionM a -> (IORef SessionState, Session) -> IO a
reifyScionM :: ((IORef SessionState, Session) -> IO a) -> ScionM a
data BgTcCache
= Parsed ParsedModule
| Typechecked TypecheckedModule
data CompilationResult = CompilationResult {
compilationSucceeded :: Bool
compilationNotes :: MultiSet Note
compilationTime :: NominalDiffTime
}
data SomeScionException = forall e . Exception e => SomeScionException e
scionToException :: Exception e => e -> SomeException
scionFromException :: Exception e => SomeException -> Maybe e
dieHard :: String -> a
data Component
= Library
| Executable String
| File FilePath
__ :: a
newtype DefSiteDB = DefSiteDB (Map String [(Location, TyThing)])
emptyDefSiteDB :: DefSiteDB
unionDefSiteDB :: DefSiteDB -> DefSiteDB -> DefSiteDB
definedNames :: DefSiteDB -> [String]
lookupDefSite :: DefSiteDB -> String -> [(Location, TyThing)]
data ScionError = ScionError String
scionError :: String -> ScionM a
data CabalConfiguration = CabalConfiguration {
distDir :: FilePath
extraArgs :: [String]
}
type FileComponentConfiguration = (FilePath, [String])
data ScionProjectConfig = ScionProjectConfig {
buildConfigurations :: [CabalConfiguration]
fileComponentExtraFlags :: [FileComponentConfiguration]
scionDefaultCabalConfig :: Maybe String
}
emptyScionProjectConfig :: ScionProjectConfig
liftIO
MonadIO (liftIO)
The Scion Monad and Session State
data SessionState Source
Constructors
SessionState
scionVerbosity :: Verbosity
initialDynFlags :: DynFlagsThe DynFlags as they were when Scion was started. This is used to reset flags when opening a new project. Arguably, the GHC API should provide calls to reset a session.
localBuildInfo :: Maybe LocalBuildInfoBuild info from current Cabal project.
activeComponent :: Maybe ComponentThe current active Cabal component. This affects DynFlags and targets. ATM, we don't support multiple active components.
lastCompResult :: CompilationResult
focusedModule :: Maybe ModSummaryThe currently focused module for background typechecking.
bgTcCache :: Maybe BgTcCacheCached state of the background typechecker.
defSiteDB :: DefSiteDBSource code locations.
client :: Stringcan be set by the client. Only used by vim to enable special hack
mkSessionState :: DynFlags -> IO (IORef SessionState)Source
newtype ScionM a Source
Constructors
ScionM
unScionM :: IORef SessionState -> Ghc a
show/hide Instances
liftScionM :: Ghc a -> ScionM aSource
modifySessionState :: (SessionState -> SessionState) -> ScionM ()Source
getSessionState :: ScionM SessionStateSource
gets :: (SessionState -> a) -> ScionM aSource
setSessionState :: SessionState -> ScionM ()Source
Verbosity Levels
data Verbosity Source
Constructors
Silent
Normal
Verbose
Deafening
show/hide Instances
intToVerbosity :: Int -> VerbositySource
verbosityToInt :: Verbosity -> IntSource
silent :: VerbositySource
normal :: VerbositySource
verbose :: VerbositySource
deafening :: VerbositySource
getVerbosity :: ScionM VerbositySource
setVerbosity :: Verbosity -> ScionM ()Source
message :: Verbosity -> String -> ScionM ()Source
Reflection into IO
reflectScionM :: ScionM a -> (IORef SessionState, Session) -> IO aSource
Reflect a computation in the ScionM monad into the IO monad.
reifyScionM :: ((IORef SessionState, Session) -> IO a) -> ScionM aSource
Dual to reflectScionM. See its documentation.
Compilation Results
data BgTcCache Source
Constructors
Parsed ParsedModule
Typechecked TypecheckedModule
data CompilationResult Source
Constructors
CompilationResult
compilationSucceeded :: Bool
compilationNotes :: MultiSet Note
compilationTime :: NominalDiffTime
show/hide Instances
Exceptions
data SomeScionException Source
Any exception raised inside Scion is a subtype of this exception.
Constructors
forall e . Exception e => SomeScionException e
show/hide Instances
scionToException :: Exception e => e -> SomeExceptionSource
scionFromException :: Exception e => SomeException -> Maybe eSource
dieHard :: String -> aSource
A fatal error. Like error but suggests submitting a bug report.
Others / Helpers
data Component Source
Constructors
Library
Executable String
File FilePath
show/hide Instances
__ :: aSource
Shorthand for undefined.
Go To Definition
newtype DefSiteDB Source

A definition site database.

This is a map from names to the location of their definition and information about the defined entity. Note that a name may refer to multiple entities.

XXX: Currently we use GHC's TyThing data type. However, this probably holds on to a lot of stuff we don't need. It also cannot be serialised directly. The reason it's done this way is that wrapping TyThing leads to a lot of duplicated code. Using a custom type might be useful to have fewer dependencies on the GHC API; however it also creates problems mapping things back into GHC API data structures. If we do this, we should at least remember the Unique in order to quickly look up the original thing.

Constructors
DefSiteDB (Map String [(Location, TyThing)])
show/hide Instances
emptyDefSiteDB :: DefSiteDBSource
The empty DefSiteDB.
unionDefSiteDB :: DefSiteDB -> DefSiteDB -> DefSiteDBSource
Combine two DefSiteDBs. XXX: check for duplicates?
definedNames :: DefSiteDB -> [String]Source
Return the list of defined names (the domain) of the DefSiteDB. The result is, in fact, ordered.
lookupDefSite :: DefSiteDB -> String -> [(Location, TyThing)]Source
Returns all the entities that the given name may refer to.
data ScionError Source
Constructors
ScionError String
show/hide Instances
scionError :: String -> ScionM aSource
data CabalConfiguration Source
Constructors
CabalConfiguration
distDir :: FilePath
extraArgs :: [String]
show/hide Instances
type FileComponentConfiguration = (FilePath, [String])Source
data ScionProjectConfig Source
Constructors
ScionProjectConfig
buildConfigurations :: [CabalConfiguration]
fileComponentExtraFlags :: [FileComponentConfiguration]
scionDefaultCabalConfig :: Maybe String
emptyScionProjectConfig :: ScionProjectConfigSource
liftIO
MonadIO (liftIO)
Produced by Haddock version 2.4.2