| Safe Haskell | None |
|---|
FP.API.Types
- data FayProjectId = FayProjectId {}
- data ProjectState
- = Workspaces
- | UserState
- data MergeModifyKind
- = Modified
- | Added
- | Deleted
- | TypeChanged
- data MergeModifyPair = MergeModifyPair MergeModifyKind MergeModifyKind
- data FayModuleId = FayModuleId (Maybe FayFileName) FayModuleName PackageId
- data FayRunConfigId = FayRunConfigId {}
- data CanFail a
- type Returns' a = Returns (CanFail a)
- data IdeCommand
- = SaveProfile Theme Int Bool (Returns' ())
- | GetInitialProjectInfo FayProjectId (Returns' InitialProjectInfo)
- | ReparseProjectSettings FayProjectId (Returns' ReparseSettingsOutput)
- | GetSettings FayProjectId (Returns' GetSettingsOutput)
- | SetSettings SetSettingsInput FayProjectId (Returns' (Maybe CompileId))
- | GetKeterYaml FayDeploymentId FayModuleName FayProjectId (Returns' KeterYaml)
- | SetRunConfigs [(FayRunConfigId, RunConfig)] FayProjectId (Returns' ())
- | SetDeployments [(FayDeploymentId, Deployment)] FayProjectId (Returns' ())
- | GetNewRunConfig FayProjectId (Returns' NewRunConfig)
- | GetNewDeployment FayProjectId (Returns' NewDeployment)
- | GetNewWebApp FayDeploymentId FayProjectId (Returns' NewWebApp)
- | GetNewBgJob FayDeploymentId FayProjectId (Returns' NewBgJob)
- | SetPublic Publicize FayProjectId (Returns' (Maybe GitHistoryItem))
- | SetProjectMetadata Text Text FayProjectId (Returns' ())
- | DeleteProject Text FayProjectId (Returns' ())
- | CheckHostName Text FayProjectId (Returns' UseHostName)
- | GetRandomHostName FayProjectId (Returns' RandomHostName)
- | GetDeploymentManagerInfo FayProjectId (Returns' DeploymentManagerInfo)
- | SaveProjectState ProjectState Text FayProjectId (Returns' ())
- | LoadProjectState ProjectState FayProjectId (Returns' MaybeText)
- | AddFile FileInfo FayProjectId (Returns' SaveFileOutput)
- | SaveFile FayFileName Text FayTutorialToken FayProjectId (Returns' SaveFileOutput)
- | DeleteFile FayFileName FayProjectId (Returns' CompileChanged)
- | RenameFile FayFileName FileInfo RenameType FayProjectId (Returns' RenameFileOutput)
- | GetFile FayFileName FayProjectId (Returns' FileContent)
- | GetFileToken FayFileName FayProjectId (Returns' FayTutorialToken)
- | GetAllFiles FayProjectId (Returns' [(FayFileName, ModuleIncluded)])
- | SetModuleExclusion FayFileName Bool FayProjectId (Returns' CompileChanged)
- | GetTypeInfo SourceSpan Int FayProjectId (Returns' ())
- | GetDefinitionSource SourceSpan FayProjectId (Returns' ())
- | GetAutocompletions AutoCompleteInput FayProjectId (Returns' ())
- | IdeHoogleSearch (Maybe FayFileName) Bool Int Int Int Text FayProjectId (Returns' HoogleId)
- | GetProjectMessages ProjectMessagesRequest FayProjectId (Returns' ProjectMessagesOutput)
- | SetTarget (Maybe (Either FayFileName FayRunConfigId)) FayProjectId (Returns' CompileChanged)
- | GetTarget FayProjectId (Returns' (Maybe (Either FayFileName FayRunConfigId)))
- | RunTarget FayProjectId (Returns' ProcId)
- | CompileBinary FayFileName [(Text, Text)] FayProjectId (Returns' BuildId)
- | UploadBuild BuildResult FayProjectId (Returns' UploadedBuild)
- | CommitToGit Text FayProjectId (Returns' ())
- | GetGitHistory Int Int FayProjectId (Returns' GitHistory)
- | IsProjectDirty FayProjectId (Returns' Bool)
- | ResetProject FayProjectId (Returns' InitialProjectInfo)
- | SetRoot Text Text FayProjectId (Returns' InitialProjectInfo)
- | GitPush Text FayProjectId (Returns' ())
- | GitPull Text FayProjectId (Returns' GitPullResult)
- | GitMergeAbort Text FayProjectId (Returns' InitialProjectInfo)
- | GitMergeDone Text MaybeText FayProjectId (Returns' GitResolvedResult)
- | GitResolveFile FayFileName FayProjectId (Returns' ())
- | GitDiff FayProjectId (Returns' Text)
- | SetRemotes RemotesList FayProjectId (Returns' ())
- | CheckoutBranch Text FayProjectId (Returns' GitCheckoutResult)
- | CreateBranch Text Text FayProjectId (Returns' ())
- | DeleteBranch Text FayProjectId (Returns' ())
- | BranchFromCommit Text Text FayProjectId (Returns' ())
- | UserAuthedGithub (Returns (CanFail Bool))
- | RevokeGithub (Returns (CanFail ()))
- | GetGithubUrl Text (Returns (CanFail Text))
- | SshPublicKey (Returns (CanFail Text))
- | ReformatModule FayFileName FayProjectId (Returns' CompileChanged)
- | GetConfigurationProject (Returns' Text)
- | GenerateConfiguration (Returns' ())
- | SetConfigurationJavascript Text (Returns' ())
- | RenderFileMarkdown FayFileName FayProjectId (Returns' HtmlReply)
- | GetTrialExpiry (Returns' ExpiryTime)
- | ShowTrialSignup (Returns' Bool)
- | RestartBackend FayProjectId (Returns' ())
- | SearchProject SearchQuery Int Int Bool FayProjectId (Returns' ())
- | CloseAllProjects (Returns' ())
- | SdistTarball FayProjectId (Returns' ())
- | GetProjectId Text (Returns' FayProjectId)
- data InitialProjectInfo = InitialProjectInfo {
- ipiTitle :: Text
- ipiDesc :: Text
- ipiGitUrl :: Maybe Text
- ipiMergeConflicts :: Maybe [MergeConflict]
- ipiInvalidSettings :: Bool
- ipiState :: [(ProjectState, Text)]
- ipiFiles :: [(FayFileName, ModuleIncluded)]
- ipiTarget :: Maybe (Either FayFileName FayRunConfigId)
- ipiPublished :: Maybe GitHistoryItem
- ipiBranches :: BranchesList
- ipiRemotes :: RemotesList
- ipiRunConfigs :: [(FayRunConfigId, RunConfig)]
- ipiDeployments :: [(FayDeploymentId, Deployment)]
- ipiTheme :: Theme
- ipiFontSize :: Int
- ipiSearchWithRegex :: Bool
- ipiLicense :: IdeLicense
- ipiCanPublish :: Bool
- data IdeLicense
- data TypeInfo = TypeInfo SourceSpan Text Text
- data MaybeText
- data GitCheckoutResult
- = GCRDirty
- | GCROk (Maybe InitialProjectInfo)
- data GitPullResult
- data GitResolvedResult
- data GitMergeConflictsResult = GitMergeConflictsResult [MergeConflict]
- data MergeConflict = MergeConflict {}
- data GitHistory = GitHistory [GitHistoryItem]
- data GitHistoryItem = GitHistoryItem {}
- data RemotesList = RemotesList [(Text, Text)]
- data BranchesList = BranchesList Text [Text]
- data ReparseSettingsOutput
- data GetSettingsOutput = GetSettingsOutput {
- gsoModuleTemplate :: Text
- gsoExtensions :: [(Text, Maybe Bool)]
- gsoEnvironment :: Environment
- gsoEnvironments :: [Environment]
- gsoGhcArgs :: [Text]
- gsoExtraPackages :: Text
- gsoHiddenPackages :: Text
- gsoCabalName :: Text
- gsoCabalVersion :: Text
- gsoRoot :: Text
- gsoFilters :: Text
- data SetExtension = SetExtension Text Bool
- data SetSettingsInput = SetSettingsInput {}
- data Environment = Environment {}
- data RunGhciOutput = RunGhciOutput ProcId FayProjectId
- data TopLevelIdentifiers = TopLevelIdentifiers [TopLevelIdentifier]
- data TopLevelIdentifier = TopLevelIdentifier {}
- data SourceSpan = SourceSpan {}
- data EitherSpan
- data SourceInfo = SourceInfo {}
- data SourceInfoKind
- = KindError
- | KindWarning
- | KindHint
- data IsWebResult
- = IsWeb
- | NotSureIfWeb
- data TextReply = TextReply {
- unTextReply :: Text
- data HtmlReply = HtmlReply {
- unHtmlReply :: Text
- data ProjectStartStatus
- data MaybeStartToken
- data RunConfig = RunConfig {
- rcTitle :: Text
- rcMainFile :: Maybe FayFileName
- rcArgs :: [Text]
- rcEnv :: [(Text, Text)]
- data NewRunConfig = NewRunConfig (FayRunConfigId, RunConfig)
- data Deployment = Deployment {
- depTitle :: Text
- depStanzas :: [Stanza]
- data Stanza
- data NewDeployment = NewDeployment (FayDeploymentId, Deployment)
- data WebApp = WebApp {
- wapTitle :: Text
- wapHostname :: Maybe Text
- wapFileName :: Maybe FayFileName
- wapArgs :: [Text]
- wapEnv :: [(Text, Text)]
- wapSsl :: Bool
- data NewWebApp = NewWebApp (FayWebAppId, WebApp)
- data BgJob = BgJob {
- bgTitle :: Text
- bgFileName :: Maybe FayFileName
- bgArgs :: [Text]
- bgEnv :: [(Text, Text)]
- bgRestartLimit :: Maybe Int
- bgRestartDelay :: Int
- data NewBgJob = NewBgJob (FayBgJobId, BgJob)
- data UseHostName
- data KeterYaml = KeterYaml {
- keterYaml :: Text
- deployYaml :: Text
- data RandomHostName = RandomHostName {}
- data ExpiryTime = ExpiryTime (Maybe Integer)
- data DeploymentManagerInfo = DeploymentManagerInfo {
- dmiHostname :: Text
- data FayManualMergeId = FayManualMergeId {}
- data FayDeploymentId = FayDeploymentId {}
- data FayBgJobId = FayBgJobId {
- unFayBgJobId :: Text
- data FayWebAppId = FayWebAppId {}
- data Theme
- data SearchQuery
- data Publicize
- data FayFileName = FayFileName {}
- data FayModuleName = FayModuleName {}
- data FileInfo = FileInfo {}
- data FileChanged = FileChanged {}
- data ModuleIncluded
- data RenameType
- data CompileChanged = CompileChanged {
- ccCompileId :: Maybe CompileId
- ccFiles :: [FileChanged]
- data RenameFileOutput
- data SaveFileOutput = SaveFileOutput FayTutorialToken CompileChanged
- data FileContent = FileContent {}
- type FayTutorialToken = TutorialConcurrentToken
- newtype TutorialConcurrentToken = TutorialConcurrentToken' {}
- data CompileId = CompileId {
- unCompileId :: Int
- data ProcId = ProcId {}
- data BuildId = BuildId {}
- data HoogleId = HoogleId {
- unHoogleId :: Int
- data SearchId = SearchId {
- unSearchId :: Int
- data ProjectMessagesRequest
- data ProjectMessagesOutput = ProjectMessagesOutput ProjectMessagesFilter [(Maybe Int, RunnerMessage)]
- data StatusHash = StatusHash Text
- data ProjectMessagesFilter
- data MessageTag = MessageTag {}
- data RunnerMessageEnvelope = RunnerMessageEnvelope {}
- data RunnerMessage
- = ProjectMessage {
- rmPsLevel :: LogLevel
- rmPsMessage :: Text
- | ProcessOutput Text
- | ProcessOutputError Text
- | StatusSnapshot ProjectStatusSnapshot StatusHash
- | IdInfoResults IdInfo
- | SubExprsResults SourceSpan [[TypeInfo]]
- | AutoCompleteResults (Maybe AutoCompleteInput) [Text]
- | ImportedPackagesResults [PackageId]
- | SearchResults [SearchResult]
- | HoogleResults Text [HoogleResult] (Maybe Int)
- | ProjectHasClosed
- | FayCompileResults Text
- = ProjectMessage {
- data LogLevel
- = LevelDebug
- | LevelInfo
- | LevelWarn
- | LevelError
- | LevelOther Text
- data ProjectStatusSnapshot = ProjectStatusSnapshot {}
- data IdInfo
- data DefinitionSource
- 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 ProcessStatusSnapshot
- = SnapshotNoProcess
- | SnapshotProcessQueued ProcId
- | SnapshotProcessRunning ProcId LaunchInfoSnapshot PortListeningResult
- | SnapshotProcessExited ProcId LaunchInfoSnapshot
- | SnapshotProcessLoadFailed ProcId Text
- | SnapshotProcessRunFailed ProcId Text
- | SnapshotProcessUserException ProcId Text
- | SnapshotProcessGhcException ProcId Text
- | SnapshotProcessForceCanceled ProcId
- data RunnerBuildStatus
- = RunnerNotBuilding
- | RunnerBuildQueued { }
- | RunnerBuilding {
- rbsId :: BuildId
- rbsProgress :: Progress
- | RunnerBuildFailed { }
- | RunnerBuildDone {
- rbsId :: BuildId
- rbsResult :: BuildResult
- data BuildResult = BuildResult {
- brPathName :: Text
- brMainModule :: Text
- brFileSize :: Int
- data UploadedBuild = UploadedBuild {}
- data Progress = Progress {}
- data LaunchInfoSnapshot = LaunchInfoSnapshot {}
- data PortListeningResult
Documentation
data FayProjectId Source
Constructors
| FayProjectId | |
Fields | |
data ProjectState Source
Constructors
| Workspaces | |
| UserState |
data MergeModifyKind Source
Constructors
| Modified | |
| Added | |
| Deleted | |
| TypeChanged |
data MergeModifyPair Source
Constructors
| MergeModifyPair MergeModifyKind MergeModifyKind |
data FayModuleId Source
Constructors
| FayModuleId (Maybe FayFileName) FayModuleName PackageId |
data FayRunConfigId Source
Constructors
| FayRunConfigId | |
Fields | |
data IdeCommand Source
Constructors
Instances
data InitialProjectInfo Source
Values passed to the client when initially loading the IDE.
Constructors
| InitialProjectInfo | |
Fields
| |
Constructors
| TypeInfo SourceSpan Text Text |
data GitCheckoutResult Source
Result of checking out a branch (or ref, in future).
Constructors
| GCRDirty | |
| GCROk (Maybe InitialProjectInfo) |
data GitPullResult Source
data GitResolvedResult Source
Constructors
| GRRSuccess | |
| GRRStillUnresolved [MergeConflict] |
data GitMergeConflictsResult Source
Constructors
| GitMergeConflictsResult [MergeConflict] |
data MergeConflict Source
Constructors
| MergeConflict | |
Fields | |
data GitHistoryItem Source
data RemotesList Source
Constructors
| RemotesList [(Text, Text)] |
data BranchesList Source
Constructors
| BranchesList Text [Text] |
data ReparseSettingsOutput Source
Constructors
| SettingsAlreadyValid | |
| ReparseSuccessful InitialProjectInfo |
data GetSettingsOutput Source
Constructors
| GetSettingsOutput | |
Fields
| |
data SetExtension Source
Constructors
| SetExtension Text Bool |
data SetSettingsInput Source
Constructors
| SetSettingsInput | |
Fields
| |
data Environment Source
A GHC environment.
data RunGhciOutput Source
Constructors
| RunGhciOutput ProcId FayProjectId |
data TopLevelIdentifiers Source
Constructors
| TopLevelIdentifiers [TopLevelIdentifier] |
data TopLevelIdentifier Source
data SourceSpan Source
Constructors
| SourceSpan | |
Fields
| |
data EitherSpan Source
Constructors
| ProperSpan SourceSpan | |
| TextSpan String |
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.
Constructors
| SourceInfo | |
Fields
| |
data IsWebResult Source
Is a target that we're running a web service? We're not sure that it's not, but if the port is open, we're confident that it is.
Constructors
| IsWeb | |
| NotSureIfWeb |
A simple text reply.
Constructors
| TextReply | |
Fields
| |
An html reply.
Constructors
| HtmlReply | |
Fields
| |
data ProjectStartStatus Source
Indicates the state of a starting project. Each request can either indicate that there is more data coming, or that this is the final status.
data MaybeStartToken Source
Constructors
| NoStartToken | |
| StartToken Int |
A run configuration for a project.
data NewRunConfig Source
Make a new run configuration.
Constructors
| NewRunConfig (FayRunConfigId, RunConfig) |
data Deployment Source
A deployment configuration.
Constructors
| Deployment | |
Fields
| |
Instances
Possible stanza types.
Constructors
| WebAppStanza FayWebAppId WebApp | |
| BgJobStanza FayBgJobId BgJob |
data NewDeployment Source
Constructors
| NewDeployment (FayDeploymentId, Deployment) |
A web app stanza.
Constructors
| NewWebApp (FayWebAppId, WebApp) |
A background job stanza.
Constructors
| BgJob | |
Fields
| |
Make a new background job.
Constructors
| NewBgJob (FayBgJobId, BgJob) |
data UseHostName Source
Result of trying to use a hostname.
Constructors
| HostnameInUse | Host name is in use by someone else, can't be used. |
| HostnameOK | Host name was already or has now been registered and is now in use. |
| HostnameQuotaExcess | Couldn't register the hostname due to quota. |
| HostnameInvalid | Invalid hostname. |
Yaml text for a Keter config.
Constructors
| KeterYaml | |
Fields
| |
data ExpiryTime Source
A date of expiration, if any.
Constructors
| ExpiryTime (Maybe Integer) |
Instances
data DeploymentManagerInfo Source
Constructors
| DeploymentManagerInfo | |
Fields
| |
data FayManualMergeId Source
Constructors
| FayManualMergeId | |
Fields | |
data FayDeploymentId Source
Constructors
| FayDeploymentId | |
Fields | |
data FayWebAppId Source
Constructors
| FayWebAppId | |
Fields | |
Themes supported by the IDE.
data SearchQuery Source
Constructors
| SearchQueryRegex Text | |
| SearchQueryPlain Text |
data FayFileName Source
Constructors
| FayFileName | |
Fields | |
data FayModuleName Source
Constructors
| FayModuleName | |
Fields | |
Constructors
| FileInfo | |
Fields | |
data FileChanged Source
Constructors
| FileChanged | |
Fields | |
data ModuleIncluded Source
data RenameType Source
Instances
data CompileChanged Source
Constructors
| CompileChanged | |
Fields
| |
data RenameFileOutput Source
Constructors
| RenameFileOutput (Maybe Text) CompileChanged | |
| WarnImportRenaming [FayFileName] |
data SaveFileOutput Source
Constructors
| SaveFileOutput FayTutorialToken CompileChanged |
data FileContent Source
Constructors
| FileContent | |
Fields | |
type FayTutorialToken = TutorialConcurrentTokenSource
A token for the tutorial.
newtype TutorialConcurrentToken Source
Token for a tutorial.
Constructors
| TutorialConcurrentToken' | |
Fields | |
Instances
Constructors
| CompileId | |
Fields
| |
Constructors
| HoogleId | |
Fields
| |
Constructors
| SearchId | |
Fields
| |
data ProjectMessagesOutput Source
Constructors
| ProjectMessagesOutput ProjectMessagesFilter [(Maybe Int, RunnerMessage)] |
data ProjectMessagesFilter Source
Constructors
| PMFilterNone | |
| PMFilterAll | |
| PMFilterOnOrBefore Integer |
data MessageTag Source
Constructors
| MessageTag | |
Fields
| |
Instances
data RunnerMessageEnvelope Source
Constructors
| RunnerMessageEnvelope | |
Fields | |
data RunnerMessage Source
Constructors
Constructors
| LevelDebug | |
| LevelInfo | |
| LevelWarn | |
| LevelError | |
| LevelOther Text |
data ProjectStatusSnapshot Source
Constructors
| ProjectStatusSnapshot | |
Constructors
| NoIdInfo SourceSpan | query span |
| IdInfo SourceSpan SourceSpan DefinitionSource | query span, result span, source info |
data DefinitionSource Source
data AutoCompleteInput Source
Constructors
| AutoCompleteInput | |
Fields | |
Constructors
| PackageId | |
Fields
| |
data SearchResult Source
Constructors
| SearchResult SourceSpan [Either Text Text] |
data HoogleResult Source
Constructors
| HoogleResult | |
Fields
| |
data PackageLink Source
Constructors
| PackageLink | |
data ModuleLink Source
Constructors
| ModuleLink | |
data RunnerOpeningStatus Source
Constructors
| RunnerProjectOpening Text | |
| RunnerProjectOpen |
data ProcessStatusSnapshot Source
Constructors
data RunnerBuildStatus Source
Constructors
| RunnerNotBuilding | |
| RunnerBuildQueued | |
| RunnerBuilding | |
Fields
| |
| RunnerBuildFailed | |
| RunnerBuildDone | |
Fields
| |
data BuildResult Source
Constructors
| BuildResult | |
Fields
| |
data UploadedBuild Source
Constructors
| UploadedBuild | |
This type represents intermediate progress information during compilation.
Constructors
| Progress | |
Fields
| |
data LaunchInfoSnapshot Source
Constructors
| LaunchInfoSnapshot | |
Fields
| |