Safe Haskell | None |
---|---|
Language | Haskell98 |
The core state of ide. This module is imported from every other module, | and all data structures of the state are declared here, to avoid circular | module dependencies.
- data IDE = IDE {
- frameState :: FrameState IDEM
- recentPanes :: [PaneName]
- specialKeys :: SpecialKeyTable IDERef
- specialKey :: SpecialKeyCons IDERef
- candy :: CandyTable
- prefs :: Prefs
- workspace :: Maybe Workspace
- activePack :: Maybe IDEPackage
- activeExe :: Maybe Text
- bufferProjCache :: Map FilePath [IDEPackage]
- allLogRefs :: [LogRef]
- currentEBC :: (Maybe LogRef, Maybe LogRef, Maybe LogRef)
- currentHist :: Int
- systemInfo :: Maybe GenScope
- packageInfo :: Maybe (GenScope, GenScope)
- workspaceInfo :: Maybe (GenScope, GenScope)
- workspInfoCache :: PackageDescrCache
- handlers :: Map Text [(Unique, IDEEvent -> IDEM IDEEvent)]
- currentState :: IDEState
- guiHistory :: (Bool, [GUIHistory], Int)
- findbar :: (Bool, Maybe (Toolbar, ListStore Text))
- toolbar :: (Bool, Maybe Toolbar)
- recentFiles :: [FilePath]
- recentWorkspaces :: [FilePath]
- runningTool :: Maybe ProcessHandle
- debugState :: Maybe (IDEPackage, ToolState)
- completion :: ((Int, Int), Maybe CompletionWindow)
- yiControl :: Control
- serverQueue :: Maybe (MVar (ServerCommand, ServerAnswer -> IDEM ()))
- server :: Maybe Handle
- vcsData :: (Map FilePath MenuItem, Maybe (Maybe Text))
- logLaunches :: Map Text LogLaunchData
- autoCommand :: IDEAction
- autoURI :: Maybe Text
- data IDEState
- type IDERef = IORef IDE
- type IDEM = ReaderT IDERef IO
- type IDEEventM t = ReaderT IDERef (ReaderT (Ptr t) IO)
- type IDEAction = IDEM ()
- data IDEEvent
- = InfoChanged Bool
- | UpdateWorkspaceInfo
- | SelectInfo Text Bool
- | SelectIdent Descr
- | LogMessage Text LogTag
- | RecordHistory GUIHistory
- | Sensitivity [(SensitivityMask, Bool)]
- | SearchMeta Text
- | StartFindInitial
- | GotoDefinition Descr
- | LoadSession FilePath
- | SaveSession FilePath
- | UpdateRecent
- | VariablesChanged
- | ErrorChanged
- | CurrentErrorChanged (Maybe LogRef)
- | BreakpointChanged
- | CurrentBreakChanged (Maybe LogRef)
- | TraceChanged
- | GetTextPopup (Maybe (IDERef -> Menu -> IO ()))
- | StatusbarChanged [StatusbarCompartment]
- | WorkspaceChanged Bool Bool
- class (Functor m, Monad m, MonadIO m) => MonadIDE m where
- (?>>=) :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
- type WorkspaceM = ReaderT Workspace IDEM
- type WorkspaceAction = WorkspaceM ()
- runWorkspace :: WorkspaceM a -> Workspace -> IDEM a
- type PackageM = ReaderT IDEPackage WorkspaceM
- type PackageAction = PackageM ()
- runPackage :: PackageM a -> IDEPackage -> WorkspaceM a
- type DebugM = ReaderT (IDEPackage, ToolState) IDEM
- type DebugAction = DebugM ()
- runDebug :: DebugM a -> (IDEPackage, ToolState) -> IDEM a
- data IDEPackage = IDEPackage {
- ipdPackageId :: PackageIdentifier
- ipdCabalFile :: FilePath
- ipdDepends :: [Dependency]
- ipdModules :: Map ModuleName BuildInfo
- ipdHasLibs :: Bool
- ipdExes :: [Text]
- ipdTests :: [Text]
- ipdBenchmarks :: [Text]
- ipdMain :: [(FilePath, BuildInfo, Bool)]
- ipdExtraSrcs :: Set FilePath
- ipdSrcDirs :: [FilePath]
- ipdExtensions :: [Extension]
- ipdConfigFlags :: [Text]
- ipdBuildFlags :: [Text]
- ipdTestFlags :: [Text]
- ipdHaddockFlags :: [Text]
- ipdExeFlags :: [Text]
- ipdInstallFlags :: [Text]
- ipdRegisterFlags :: [Text]
- ipdUnregisterFlags :: [Text]
- ipdSdistFlags :: [Text]
- ipdSandboxSources :: [IDEPackage]
- ipdBuildDir :: IDEPackage -> FilePath
- ipdAllDirs :: IDEPackage -> [FilePath]
- data Workspace = Workspace {
- wsVersion :: Int
- wsSaveTime :: Text
- wsName :: Text
- wsFile :: FilePath
- wsPackages :: [IDEPackage]
- wsPackagesFiles :: [FilePath]
- wsActivePackFile :: Maybe FilePath
- wsActiveExe :: Maybe Text
- wsNobuildPack :: [IDEPackage]
- packageVcsConf :: Map FilePath VCSConf
- wsAllPackages :: Workspace -> [IDEPackage]
- type VCSConf = (VCSType, Config, Maybe MergeTool)
- data ActionDescr alpha = AD {}
- type ActionString = Text
- type KeyString = Text
- data Prefs = Prefs {
- prefsFormat :: Int
- prefsSaveTime :: Text
- showLineNumbers :: Bool
- rightMargin :: (Bool, Int)
- tabWidth :: Int
- wrapLines :: Bool
- sourceCandy :: (Bool, Text)
- keymapName :: Text
- forceLineEnds :: Bool
- removeTBlanks :: Bool
- textviewFont :: Maybe Text
- sourceStyle :: (Bool, Text)
- foundBackground :: Color
- matchBackground :: Color
- contextBackground :: Color
- breakpointBackground :: Color
- autoLoad :: Bool
- textEditorType :: Text
- logviewFont :: Maybe Text
- defaultSize :: (Int, Int)
- browser :: Text
- pathForCategory :: [(Text, PanePath)]
- defaultPath :: PanePath
- categoryForPane :: [(Text, Text)]
- packageBlacklist :: [Dependency]
- collectAtStart :: Bool
- useCtrlTabFlipping :: Bool
- docuSearchURL :: Text
- completeRestricted :: Bool
- saveAllBeforeBuild :: Bool
- jumpToWarnings :: Bool
- useVado :: Bool
- useCabalDev :: Bool
- backgroundBuild :: Bool
- runUnitTests :: Bool
- makeMode :: Bool
- singleBuildWithoutLinking :: Bool
- dontInstallLast :: Bool
- printEvldWithShow :: Bool
- breakOnException :: Bool
- breakOnError :: Bool
- printBindResult :: Bool
- serverIP :: Text
- serverPort :: Int
- sourceDirectories :: [FilePath]
- unpackDirectory :: Maybe FilePath
- retrieveURL :: Text
- retrieveStrategy :: RetrieveStrategy
- endWithLastConn :: Bool
- cabalCommand :: Prefs -> FilePath
- data LogRefType
- data LogRef = LogRef {
- logRefSrcSpan :: SrcSpan
- logRefPackage :: IDEPackage
- refDescription :: Text
- logLines :: (Int, Int)
- logRefType :: LogRefType
- logRefFilePath :: LogRef -> FilePath
- logRefFullFilePath :: LogRef -> FilePath
- isError :: LogRef -> Bool
- isBreakpoint :: LogRef -> Bool
- displaySrcSpan :: SrcSpan -> [Char]
- colorHexString :: Color -> [Char]
- data SearchHint
- newtype CandyTable = CT (CandyTableForth, CandyTableBack)
- type CandyTableForth = [(Bool, Text, Text)]
- type CandyTableBack = [(Text, Text, Int)]
- newtype KeymapI = KM (Map ActionString [(Maybe (Either KeyString (KeyString, KeyString)), Maybe Text)])
- type SpecialKeyTable alpha = Map (KeyVal, [Modifier]) (Map (KeyVal, [Modifier]) (ActionDescr alpha))
- type SpecialKeyCons alpha = Maybe (Map (KeyVal, [Modifier]) (ActionDescr alpha), Text)
- type PackageDescrCache = Map PackageIdentifier ModuleDescrCache
- type ModuleDescrCache = Map ModuleName (UTCTime, Maybe FilePath, ModuleDescr)
- data CompletionWindow = CompletionWindow {}
- data LogLaunch = LogLaunch {}
- data LogLaunchData = LogLaunchData {}
- data LogTag
- type GUIHistory = (GUIHistory', GUIHistory')
- data GUIHistory'
- = ModuleSelected { }
- | ScopeSelected { }
- | InfoElementSelected { }
- | PaneSelected { }
- data SensitivityMask
- data SearchMode
- data StatusbarCompartment
Documentation
The IDE state
IsStartingUp | Leksah is in startup mode |
IsShuttingDown | Leksah is about to go down |
IsRunning | Leksah is running |
IsFlipping TreeView | The flipper is used to switch between sources |
IsCompleting Connections | The completion feature is used |
type IDEAction = IDEM () Source
A shorthand for a reader monad for a mutable reference to the IDE state which does not return a value
type WorkspaceM = ReaderT Workspace IDEM Source
type WorkspaceAction = WorkspaceM () Source
runWorkspace :: WorkspaceM a -> Workspace -> IDEM a Source
type PackageM = ReaderT IDEPackage WorkspaceM Source
type PackageAction = PackageM () Source
runPackage :: PackageM a -> IDEPackage -> WorkspaceM a Source
type DebugAction = DebugM () Source
data IDEPackage Source
IDEPackage | |
|
ipdBuildDir :: IDEPackage -> FilePath Source
ipdAllDirs :: IDEPackage -> [FilePath] Source
Workspace | |
|
wsAllPackages :: Workspace -> [IDEPackage] Source
Includes sandbox sources
data ActionDescr alpha Source
ActionDescr is a data structure from which GtkActions are build, which are used for menus, toolbars, and accelerator keystrokes
type ActionString = Text Source
Preferences is a data structure to hold configuration data
cabalCommand :: Prefs -> FilePath Source
LogRef | |
|
logRefFilePath :: LogRef -> FilePath Source
isBreakpoint :: LogRef -> Bool Source
displaySrcSpan :: SrcSpan -> [Char] Source
colorHexString :: Color -> [Char] Source
newtype CandyTable Source
type CandyTableForth = [(Bool, Text, Text)] Source
type CandyTableBack = [(Text, Text, Int)] Source
type SpecialKeyTable alpha = Map (KeyVal, [Modifier]) (Map (KeyVal, [Modifier]) (ActionDescr alpha)) Source
type SpecialKeyCons alpha = Maybe (Map (KeyVal, [Modifier]) (ActionDescr alpha), Text) Source
type ModuleDescrCache = Map ModuleName (UTCTime, Maybe FilePath, ModuleDescr) Source
data CompletionWindow Source
data LogLaunchData Source
Other types
type GUIHistory = (GUIHistory', GUIHistory') Source
the first one is the new and the second the old state
data SensitivityMask Source
data SearchMode Source