Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data RunnerException = RunnerException Text
- fromString :: String -> Text
- toString :: Text -> String
- decodeBytes :: ByteString -> Text
- encodeBytes :: Text -> ByteString
- data Filters = Filters {
- filtersRoot :: Text
- filtersBlacklist :: [Text]
- newtype ByteString64 = ByteString64 {}
- newtype WrappedUTCTime = WrappedUTCTime {}
- toPicoSeconds :: UTCTime -> Integer
- fromPicoSeconds :: Integer -> UTCTime
- newtype ProjectId = ProjectId {
- unProjectId :: Int
- unProjectIdString :: ProjectId -> String
- unProjectIdText :: ProjectId -> Text
- newtype RunConfigId = RunConfigId {
- unRunConfigId :: Int
- newtype JobId = JobId {}
- newtype CompileId = CompileId {
- unCompileId :: Int
- newtype ProcId = ProcId {}
- newtype GitShellId = GitShellId {
- unGitShellId :: Int
- newtype FormattedTime = FormattedTime {}
- newtype ModuleName = ModuleName {
- unModuleName :: Text
- moduleNameString :: ModuleName -> String
- data ModuleStatus
- newtype FileName = FileName {}
- unFileNameText :: FileName -> Text
- unFileNameString :: FileName -> String
- fileNameFromText :: Text -> FileName
- fileNameFromString :: String -> FileName
- data EncFileName
- = EncFileNameText { }
- | EncFileNameBase64 { }
- encodeBase64FileName :: FileName -> Text
- decodeBase64FileName :: Text -> FileName
- encFileName :: FileName -> EncFileName
- unEncFileName :: EncFileName -> FileName
- encFileNameFromByteString :: ByteString -> EncFileName
- encFileNameFromText :: Text -> EncFileName
- encFileNameFromString :: String -> EncFileName
- unEncFileNameString :: EncFileName -> String
- data FileType
- data FileDesc = FileDesc {}
- data FileUpdate
- data TargetUpdate
- data UpdateActions = UpdateActions {
- _uaUpdates :: [(EncFileName, FileUpdate)]
- _uaNewTarget :: Maybe TargetUpdate
- data CompileDesc = CompileDesc {}
- data CompileIdent = CompileIdent {}
- newtype SessionId = SessionId Text
- newtype MailboxId = MailboxId Text
- data NewFileInfo = NewFileInfo {
- fiPath :: Text
- fiModule :: Maybe ModuleName
- data RenameType
- data RenameFileOutput
- data SaveFileOutput = SaveFileOutput FayTutorialToken (Maybe CompileDesc)
- data FayFileContent = FayFileContent {}
- type FayTutorialToken = TutorialConcurrentToken
- newtype TutorialConcurrentToken = TutorialConcurrentToken' {}
- incrToken :: TutorialConcurrentToken -> TutorialConcurrentToken
- data TypeInfo = TypeInfo SourceSpan Text [Text]
- data SourceSpan = SourceSpan {}
- data EitherSpan
- jobStillRunningTimeoutSeconds :: Int
- data ProjectMessagesOutput = ProjectMessagesOutput {}
- newtype StatusHash = StatusHash {
- unStatusHash :: Text
- data CompileResult
- data ProcessResult
- displayProcessResult :: ProcessResult -> Text
- data GitShellOutput
- data RunnerMessage
- = ProjectMessage LogLevel Text
- | ProcessOutput ProcId Text
- | ProcessStopped ProcId ProcessResult
- | GitShellOutput GitShellId GitShellOutput
- | CompileComplete CompileId CompileResult
- | ProjectHasOpened SessionId
- | ProjectHasClosed SessionId Bool Text
- | IdeCommandOutput JobId Text
- | JobException JobId Text
- | JobStillRunning JobId
- data LogLevel
- data SdistTarballInfo = SdistTarballInfo {
- stiPackageName :: !Text
- stiVersion :: !Text
- data GitHistoryItem = GitHistoryItem {}
- data GitRepositoryStatus
- data ProjectStatusSnapshot = ProjectStatusSnapshot {}
- data IdInfo
- data DefinitionSource
- definitionIdName :: DefinitionSource -> Text
- data ModuleId = ModuleId (Maybe EncFileName) ModuleName PackageId
- data AutoCompleteInput = AutoCompleteInput {}
- data PackageId = PackageId {}
- data SearchResult = SearchResult SourceSpan [Either Text Text]
- data HoogleResult = HoogleResult {
- hrURL :: String
- hrSources :: [(PackageLink, [ModuleLink])]
- hrTitle :: String
- hrBody :: String
- data PackageLink = PackageLink {}
- data ModuleLink = ModuleLink {}
- data RunnerOpeningStatus
- data RunnerCompileStatus
- data SourceInfo = SourceInfo {
- infoKind :: SourceInfoKind
- infoSpan :: EitherSpan
- infoMsg :: [(InfoChunkTag, Text)]
- data SourceInfoKind
- data InfoChunkTag
- = ICTPlain
- | ICTModule
- | ICTCode
- | ICTRefactor Text [(SourceSpan, Text)]
- | ICTCollapse
- | ICTOriginal
- data ProcessStatusSnapshot
- data RunnerPictureStatus = RunnerPictureStatus [PictureStatus]
- data PictureStatus = PictureStatus {
- pictureName :: Text
- pictureUrl :: Text
- pictureHash :: Text
- data RunnerBuildStatus
- data UploadedBuild = UploadedBuild {}
- data Progress = Progress {}
- newtype Approot = Approot {}
- newtype VirtualHost = VirtualHost {}
- approotString :: Approot -> String
- data ApprootPid = ApprootPid Approot ProcId
- newtype Port = Port {}
- data ErrorsAnd x = ErrorsAnd [String] (Maybe (Automatic x))
- data ModuleIncluded
- fileDescToModuleIncluded :: FileDesc -> ModuleIncluded
- data MergeModifyKind
- = Modified
- | Added
- | Deleted
- | TypeChanged
- data MergeModifyPair = MergeModifyPair MergeModifyKind MergeModifyKind
- newtype BlobSHA = BlobSHA {}
- newtype CommitSHA = CommitSHA {
- unCommitSHA :: Text
- newtype BranchName = BranchName {
- unBranchName :: Text
- branchToRef :: BranchName -> Text
- branchFromRef :: Text -> BranchName
- isMergeBranch :: BranchName -> Bool
- mergeBranch :: BranchName -> BranchName
- mergeBranchOrigin :: BranchName -> Maybe BranchName
- data CommitName
Documentation
data RunnerException Source
fromString :: String -> Text Source
decodeBytes :: ByteString -> Text Source
encodeBytes :: Text -> ByteString Source
Filters | |
|
newtype ByteString64 Source
The standard ByteString instances in aeson are broken: they assume UTF8 encoding. This type instead uses base64 for proper round-tripping.
newtype WrappedUTCTime Source
toPicoSeconds :: UTCTime -> Integer Source
fromPicoSeconds :: Integer -> UTCTime Source
unProjectIdText :: ProjectId -> Text Source
newtype RunConfigId Source
newtype GitShellId Source
newtype FormattedTime Source
newtype ModuleName Source
data ModuleStatus Source
WrongExtension | |
NotTextual | |
CFile | |
BootFile ModuleName | |
HeaderFilenameMismatch ModuleName | |
ModuleOk ModuleName | This can also be valid for data files, if the user has manually excluded them. |
unFileNameText :: FileName -> Text Source
unFileNameString :: FileName -> String Source
fileNameFromText :: Text -> FileName Source
encFileName :: FileName -> EncFileName Source
data FileUpdate Source
When a file in the project representation is changed by a ProjectUpdate
request, it often results in a change reflected in what we know about the
file. This change is reported in the UpdateActions
structure using
this FileUpdate
type.
data TargetUpdate Source
A project's target is a single module containing a function named main
.
This type reflects if any change in the current target has been made.
data UpdateActions Source
After a ProjectUpdate
request is processed, a set of UpdateActions
will result to reflect what changes have been made to the project
representation (and subsequently, what changes may need to be reflected
in the ide-backend, the database, and other caches).
data CompileDesc Source
Describe a compilation which has been accepted by the isolation-runner. This includes sufficient information to tell what is "in" the compilation, and to distinguish it from any other compilation.
data CompileIdent Source
Backend session ID.
data NewFileInfo Source
NewFileInfo | |
|
data RenameType Source
data RenameFileOutput Source
data SaveFileOutput Source
data FayFileContent Source
type FayTutorialToken = TutorialConcurrentToken Source
A token for the tutorial.
newtype TutorialConcurrentToken Source
Token for a tutorial.
data SourceSpan Source
SourceSpan | |
|
data EitherSpan Source
jobStillRunningTimeoutSeconds :: Int Source
The timing separation between JobStillRunning
messages. Note
that the actual interval will always be larger than this due to
network overhead, etc.
data ProjectMessagesOutput Source
ProjectMessagesOutput | |
|
newtype StatusHash Source
data CompileResult Source
data ProcessResult Source
data GitShellOutput Source
data RunnerMessage Source
ProjectMessage LogLevel Text | |
ProcessOutput ProcId Text | |
ProcessStopped ProcId ProcessResult | |
GitShellOutput GitShellId GitShellOutput | |
CompileComplete CompileId CompileResult | |
ProjectHasOpened SessionId | |
ProjectHasClosed SessionId Bool Text | If the Bool is True, it indicates that the client should resume polling for project messages from a newly created project. If False, there is some more severe problem initiating the project, and the client should let the user know that the project may require manual recovery. |
IdeCommandOutput JobId Text | FIXME At some point in the future, it would be nice to replace the second Text with a Value, to make it clear that we're encoding arbitrary JSON values. This is semantically more correct, and more efficient, but requires changes to the Fay encode/decode code, and therefore is not trivial to implement. |
JobException JobId Text | |
JobStillRunning JobId | Indicates to the client that a job is still being actively worked on. |
data SdistTarballInfo Source
SdistTarballInfo | |
|
data GitHistoryItem Source
data GitRepositoryStatus Source
data ProjectStatusSnapshot Source
data DefinitionSource Source
DefinitionLocal Text SourceSpan | |
DefinitionTextSpan Text Text | |
DefinitionImported Text ModuleId ModuleId EitherSpan EitherSpan | |
DefinitionWiredIn Text | |
DefinitionBinder Text |
data AutoCompleteInput Source
data SearchResult Source
data HoogleResult Source
HoogleResult | |
|
data RunnerOpeningStatus Source
data RunnerCompileStatus Source
RunnerNotCompiling | |
RunnerCompiling CompileIdent Progress | |
RunnerCompileDone CompileIdent [SourceInfo] |
data SourceInfo Source
An error or warning in a source module.
Most errors are associated with a span of text, but some have only a location point.
SourceInfo | |
|
data SourceInfoKind Source
Severity of a piece of info.
data InfoChunkTag Source
ICTPlain | |
ICTModule | |
ICTCode | Note: Ideally we'd distinguish identifiers, types, exprs, etc |
ICTRefactor Text [(SourceSpan, Text)] | The |
ICTCollapse | |
ICTOriginal |
data ProcessStatusSnapshot Source
SnapshotNoProcess | |
SnapshotProcessRunning ProcId (Maybe Text) | URL to visit project |
data RunnerPictureStatus Source
Status for the pictures directory.
data PictureStatus Source
Status of a picture.
PictureStatus | |
|
data RunnerBuildStatus Source
This type represents intermediate progress information during compilation.
Progress | |
|
newtype VirtualHost Source
approotString :: Approot -> String Source
data ApprootPid Source
data ModuleIncluded Source
data MergeModifyKind Source
data MergeModifyPair Source
A Git blob SHA in textual form.
A Git commit SHA in textual form.
newtype BranchName Source
A Git branch name, such as "master", or "merge/master".
branchToRef :: BranchName -> Text Source
branchFromRef :: Text -> BranchName Source
isMergeBranch :: BranchName -> Bool Source
data CommitName Source
A reference to a specific commit, which can be done by several different means.