{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}

module FP.API.Types where

import Data.Data
import Language.Fay.Yesod
import Prelude
import FFI

#ifndef FAY
import Data.Default (Default(..))
import Database.Persist.Sql (PersistField, PersistFieldSql)
import Database.Persist.TH (derivePersistField)
import System.Random (Random)
#endif

data FayProjectId = FayProjectId { unFayProjectId :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data ProjectState = Workspaces | UserState
#ifdef FAY
    deriving (Read, Typeable, Data, Show, Eq)
#else
    deriving (Show, Eq, Read, Data, Typeable, Enum, Bounded, Ord)
derivePersistField "ProjectState"
#endif

data MergeModifyKind = Modified | Added | Deleted | TypeChanged
#ifdef FAY
    deriving (Read, Typeable, Data, Show, Eq)
#else
    deriving (Show, Eq, Read, Data, Typeable, Enum, Bounded, Ord)
derivePersistField "MergeModifyKind"
#endif

data MergeModifyPair = MergeModifyPair MergeModifyKind MergeModifyKind
#ifdef FAY
    deriving (Read, Typeable, Data, Show, Eq)
#else
    deriving (Show, Eq, Read, Data, Typeable, Bounded)
derivePersistField "MergeModifyPair"
#endif

data FayModuleId = FayModuleId (Maybe FayFileName)
                               FayModuleName
                               PackageId
    deriving (Read, Typeable, Data, Show, Eq)

data FayRunConfigId = FayRunConfigId { unFayRunConfigId :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data CanFail a = Success (Automatic a) | Failure Text
    deriving (Read, Typeable, Data, Show, Eq)
#ifndef FAY
deriving instance Functor CanFail
#endif

type Returns' a = Returns (CanFail a)

data IdeCommand
    -- User profile
    = SaveProfile            Theme Int Bool                                    (Returns' ())

    -- Project global
    | 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' ())

    -- Host names
    | CheckHostName          Text                                              FayProjectId (Returns' UseHostName)
    | GetRandomHostName                                                        FayProjectId (Returns' RandomHostName)
    | GetDeploymentManagerInfo                                                 FayProjectId (Returns' DeploymentManagerInfo)

    -- User State
    | SaveProjectState       ProjectState Text                                 FayProjectId (Returns' ())
    | LoadProjectState       ProjectState                                      FayProjectId (Returns' MaybeText)

    -- Files
    | 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)

    -- Info
    | GetTypeInfo            SourceSpan Int                                    FayProjectId (Returns' ())
    | GetDefinitionSource    SourceSpan                                        FayProjectId (Returns' ())
    | GetAutocompletions     AutoCompleteInput                                 FayProjectId (Returns' ())
--    | GetTopLevelIdentifiers FayFileName                                     FayProjectId (Returns' TopLevelIdentifiers)
    | IdeHoogleSearch        (Maybe FayFileName) Bool Int Int Int Text         FayProjectId (Returns' HoogleId)
        -- ^ module context, is it exact?, number to query, offset in result, number to yield, query contents
    | GetProjectMessages     ProjectMessagesRequest                            FayProjectId (Returns' ProjectMessagesOutput)

    -- Compilation
    | SetTarget              (Maybe (Either FayFileName FayRunConfigId))       FayProjectId (Returns' CompileChanged)
    | GetTarget                                                                FayProjectId (Returns' (Maybe (Either FayFileName FayRunConfigId)))
    | RunTarget                                                                FayProjectId (Returns' ProcId)
    --TODO: Make these use the current target.
    | CompileBinary          FayFileName [(Text, Text)]                        FayProjectId (Returns' BuildId)
    | UploadBuild            BuildResult                                       FayProjectId (Returns' UploadedBuild)

    -- Git
    | 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' ()) -- ^ Text == URL
    | GitPull                Text                                              FayProjectId (Returns' GitPullResult) -- ^ Text == URL
    | GitMergeAbort          Text                                              FayProjectId (Returns' InitialProjectInfo) -- ^ Text == URL
    | GitMergeDone           Text MaybeText                                    FayProjectId (Returns' GitResolvedResult) -- ^ Text == URL, Msg
    | GitResolveFile         FayFileName                                       FayProjectId (Returns' ())

    | GitDiff                                                                  FayProjectId (Returns' Text)

    -- Git Remotes
    | SetRemotes             RemotesList                                       FayProjectId (Returns' ())

    -- Git Branches
    | CheckoutBranch         Text                                              FayProjectId (Returns' GitCheckoutResult)
    | CreateBranch           Text Text                                         FayProjectId (Returns' ())
    | DeleteBranch           Text                                              FayProjectId (Returns' ())
    | BranchFromCommit       Text Text                                         FayProjectId (Returns' ())

    -- Github
    | UserAuthedGithub (Returns (CanFail Bool))
    | RevokeGithub (Returns (CanFail ()))
    | GetGithubUrl Text (Returns (CanFail Text))
    | SshPublicKey (Returns (CanFail Text))

    -- Module manipulation
    | ReformatModule         FayFileName                                       FayProjectId (Returns' CompileChanged)

    -- Configuration
    | GetConfigurationProject                                                               (Returns' Text)
    | GenerateConfiguration                                                                 (Returns' ())
    | SetConfigurationJavascript Text                                                       (Returns' ())

    -- Misc
    | RenderFileMarkdown     FayFileName                                       FayProjectId (Returns' HtmlReply)
    | GetTrialExpiry                                                                        (Returns' ExpiryTime)
    | ShowTrialSignup                                                                       (Returns' Bool)
    | RestartBackend                                                           FayProjectId (Returns' ())
--    | RunGhci Bool                                                             FayProjectId (Returns' RunGhciOutput)
    | SearchProject          SearchQuery Int Int Bool                          FayProjectId (Returns' ())
    | CloseAllProjects                                                                      (Returns' ())
    | SdistTarball                                                             FayProjectId (Returns' ())
    | GetProjectId           Text                                                           (Returns' FayProjectId)
    deriving (Read, Typeable, Data, Show, Eq)


-- | Values passed to the client when initially loading the IDE.
data InitialProjectInfo = InitialProjectInfo
    { ipiTitle :: Text
    , ipiDesc :: Text
    , ipiGitUrl :: Maybe Text -- ^ URL originally cloned from
    , 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
    }
    deriving (Read, Typeable, Data, Show, Eq)

data IdeLicense = ILCommunity | ILPersonal | ILProfessional
    deriving (Read, Typeable, Data, Show, Eq)

-- TODO: middle text should be the code that the type comes from.
data TypeInfo = TypeInfo SourceSpan Text Text
    deriving (Read, Typeable, Data, Show, Eq)

data MaybeText = NoText | JustText Text -- FAY BUG
    deriving (Read, Typeable, Data, Show, Eq)

-- | Result of checking out a branch (or ref, in future).
data GitCheckoutResult
  = GCRDirty
  | GCROk (Maybe InitialProjectInfo)
    deriving (Read, Typeable, Data, Show, Eq)

data GitPullResult = GPRSuccess InitialProjectInfo
                   | GPRDirtyTree
                   | GPRManualMerge Text InitialProjectInfo
    deriving (Read, Typeable, Data, Show, Eq)

data GitResolvedResult = GRRSuccess
                       | GRRStillUnresolved [MergeConflict]
    deriving (Read, Typeable, Data, Show, Eq)

data GitMergeConflictsResult = GitMergeConflictsResult [MergeConflict]
    deriving (Read, Typeable, Data, Show, Eq)

data MergeConflict = MergeConflict
    { mergeFile :: FayFileName
    , mergeState :: MergeModifyPair
    }
    deriving (Read, Typeable, Data, Show, Eq)

data GitHistory = GitHistory [GitHistoryItem] -- FAY BUG
    deriving (Read, Typeable, Data, Show, Eq)

data GitHistoryItem = GitHistoryItem
    { ghiDate :: Text
    , ghiAuthor :: Text
    , ghiLog :: Text
    , ghiHash :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

data RemotesList = RemotesList [(Text,Text)]
  deriving (Read, Typeable, Data, Show, Eq)

data BranchesList = BranchesList Text [Text]
  deriving (Read, Typeable, Data, Show, Eq)

data ReparseSettingsOutput
    = SettingsAlreadyValid
    | ReparseSuccessful InitialProjectInfo
    deriving (Read, Typeable, Data, Show, Eq)

data GetSettingsOutput = GetSettingsOutput
    { gsoModuleTemplate :: Text
    , gsoExtensions     :: [(Text, Maybe Bool)] -- ^ three states: on, off, or default (== Nothing)
    , gsoEnvironment    :: Environment
    , gsoEnvironments   :: [Environment]
    , gsoGhcArgs        :: [Text]
    , gsoExtraPackages  :: Text
    , gsoHiddenPackages :: Text
    , gsoCabalName      :: Text
    , gsoCabalVersion   :: Text
    , gsoRoot           :: Text
    , gsoFilters        :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

data SetExtension = SetExtension Text Bool
    deriving (Read, Typeable, Data, Show, Eq)

data SetSettingsInput = SetSettingsInput
    { ssiModuleTemplate :: Text
    , ssiExtensions     :: [SetExtension]
    , ssiEnvironment    :: Text
    , ssiGhcArgs        :: [Text]
    , ssiExtraPackages  :: Text
    , ssiHiddenPackages :: Text
    , ssiCabalName      :: Text
    , ssiCabalVersion   :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

-- | A GHC environment.
data Environment = Environment
  { envName :: Text
  , envTitle :: Text
  , envURL :: Text
  }
  deriving (Read, Typeable, Data, Show, Eq)

data RunGhciOutput = RunGhciOutput ProcId FayProjectId
    deriving (Read, Typeable, Data, Show, Eq)

data TopLevelIdentifiers = TopLevelIdentifiers [TopLevelIdentifier]
    deriving (Read, Typeable, Data, Show, Eq)

data TopLevelIdentifier = TopLevelIdentifier
    { tliLine :: Int
    , tliColumn :: Int
    , tliName :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

-- Copied from ide-backend/Common.hs
--  + Different deriving list
--  + 'Show' instances made into functions

data SourceSpan = SourceSpan
  { spanFilePath   :: FayFileName
  , spanFromLine   :: Int
  , spanFromColumn :: Int
  , spanToLine     :: Int
  , spanToColumn   :: Int }
  deriving (Read, Typeable, Data, Show, Eq)

data EitherSpan =
    ProperSpan SourceSpan
  | TextSpan String
  deriving (Read, Typeable, Data, Show, Eq)

-- | An error or warning in a source module.
--
-- Most errors are associated with a span of text, but some have only a
-- location point.
--
data SourceInfo = SourceInfo
  { infoKind :: SourceInfoKind
  , infoSpan :: EitherSpan
  , infoMsg  :: Text
  }
  deriving (Read, Typeable, Data, Show, Eq)

-- | Severity of a piece of info.
data SourceInfoKind = KindError | KindWarning | KindHint
  deriving (Read, Typeable, Data, Show, Eq)

-- | 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.
data IsWebResult
  = IsWeb
  | NotSureIfWeb
  deriving (Read, Typeable, Data, Show, Eq)

-- | A simple text reply.
data TextReply
  = TextReply { unTextReply :: Text }
  deriving (Read, Typeable, Data, Show, Eq)

-- | An html reply.
data HtmlReply
  = HtmlReply { unHtmlReply :: Text }
  deriving (Read, Typeable, Data, Show, Eq)

-- | 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 ProjectStartStatus = PSSUpdate Text Int | PSSFinal Text
  deriving (Read, Typeable, Data, Show, Eq)

data MaybeStartToken = NoStartToken | StartToken Int
  deriving (Read, Typeable, Data, Show, Eq)

-- | A run configuration for a project.
data RunConfig = RunConfig
  { rcTitle :: Text
  , rcMainFile :: Maybe FayFileName
  , rcArgs :: [Text]
  , rcEnv :: [(Text,Text)]
  } deriving (Read, Typeable, Data, Show, Eq)

-- | Make a new run configuration.
data NewRunConfig = NewRunConfig (FayRunConfigId,RunConfig)
  deriving (Read, Typeable, Data, Show, Eq)

-- | A deployment configuration.
data Deployment = Deployment
  { depTitle :: Text
  , depStanzas :: [Stanza]
  } deriving (Read, Typeable, Data, Show, Eq)

-- | Possible stanza types.
data Stanza = WebAppStanza FayWebAppId WebApp
            | BgJobStanza FayBgJobId BgJob
  deriving (Read, Typeable, Data, Show, Eq)

data NewDeployment = NewDeployment (FayDeploymentId,Deployment)
  deriving (Read, Typeable, Data, Show, Eq)

-- | A web app stanza.
data WebApp = WebApp
  { wapTitle    :: Text
  , wapHostname :: Maybe Text
  , wapFileName :: Maybe FayFileName
  , wapArgs     :: [Text]
  , wapEnv      :: [(Text,Text)]
  , wapSsl      :: Bool
  } deriving (Read, Typeable, Data, Show, Eq)

data NewWebApp = NewWebApp (FayWebAppId,WebApp)
  deriving (Read, Typeable, Data, Show, Eq)

-- | A background job stanza.
data BgJob = BgJob
  { bgTitle        :: Text
  , bgFileName     :: Maybe FayFileName
  , bgArgs         :: [Text]
  , bgEnv          :: [(Text,Text)]
  , bgRestartLimit :: Maybe Int
  , bgRestartDelay :: Int
  } deriving (Read, Typeable, Data, Show, Eq)

-- | Make a new background job.
data NewBgJob = NewBgJob (FayBgJobId,BgJob)
  deriving (Read, Typeable, Data, Show, Eq)

-- | Result of trying to use a hostname.
data UseHostName = 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.
  deriving (Read, Typeable, Data, Show, Eq)

-- | Yaml text for a Keter config.
data KeterYaml = KeterYaml
    { keterYaml :: Text
    , deployYaml :: Text
    }
  deriving (Read,Typeable,Data,Show,Eq)

-- | A randomly generated host name.
data RandomHostName = RandomHostName { unRandomHostname :: Text }
  deriving (Read,Typeable,Data,Show,Eq)

-- | A date of expiration, if any.
data ExpiryTime = ExpiryTime (Maybe Integer)
  deriving (Read,Typeable,Data,Show,Eq)

data DeploymentManagerInfo = DeploymentManagerInfo
  { dmiHostname :: Text }
  deriving (Read,Typeable,Data,Show,Eq)

data FayManualMergeId = FayManualMergeId { unFayManualMergeId :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data FayDeploymentId = FayDeploymentId { unFayDeploymentId :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data FayBgJobId = FayBgJobId { unFayBgJobId :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data FayWebAppId = FayWebAppId { unFayWebAppId :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

--------------------------------------------------------------------------------
-- Themes

-- | Themes supported by the IDE.
data Theme = Panda | Zenburn | Monokai
#ifdef FAY
  deriving (Read,Typeable,Data,Show,Eq)
#else
  deriving (Show, Eq, Read, Data, Typeable, Bounded, Enum)
#endif

--------------------------------------------------------------------------------
-- Search

data SearchQuery
  = SearchQueryRegex Text
  | SearchQueryPlain Text
  deriving (Read,Typeable,Data,Show,Eq)

--------------------------------------------------------------------------------
-- Publication

data Publicize = NotPublic
               | Publicize Text
  deriving (Read,Typeable,Data,Show,Eq)

--------------------------------------------------------------------------------
-- Files / Modules

data FayFileName = FayFileName { unFayFileName :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data FayModuleName = FayModuleName { unFayModuleName :: Text }
    deriving (Read, Typeable, Data, Show, Eq)

data FileInfo = FileInfo
    { fiPath :: FayFileName
    , fiModule :: Maybe FayModuleName
    }
    deriving (Read, Typeable, Data, Show, Eq)

data FileChanged = FileChanged
    { fcPath :: FayFileName
    , fcModule :: Maybe ModuleIncluded
    }
    deriving (Read, Typeable, Data, Show, Eq)

data ModuleIncluded
    = ModuleExcluded
    | ModuleWrongExtension
    | ModuleNotTextual
    | ModuleHeaderFilenameMismatch FayModuleName
    | ModuleNameAmbiguous FayModuleName
    | ModuleIncluded FayModuleName
    deriving (Read, Typeable, Data, Show, Eq)

data RenameType = RenamePlain | RenameHeader | RenameHeaderAndImports | RenameHeaderAndImportsForce
    deriving (Read, Typeable, Data, Show, Eq)

data CompileChanged = CompileChanged
    { ccCompileId :: Maybe CompileId
    , ccFiles :: [FileChanged] -- ^ All of the 'FileChanged's that have a
                                 -- 'fiModule' that's changed.
    }
    deriving (Read, Typeable, Data, Show, Eq)

data RenameFileOutput
    = RenameFileOutput (Maybe Text) CompileChanged
    | WarnImportRenaming [FayFileName]
    deriving (Read, Typeable, Data, Show, Eq)

data SaveFileOutput = SaveFileOutput FayTutorialToken CompileChanged
    deriving (Read, Typeable, Data, Show, Eq)

data FileContent = FileContent
    { dfcContent :: Maybe Text
    , dfcToken :: FayTutorialToken
    }
    deriving (Read, Typeable, Data, Show, Eq)

--------------------------------------------------------------------------------
-- Version token

-- | A token for the tutorial.
type FayTutorialToken = TutorialConcurrentToken

#ifdef FAY
data TutorialConcurrentToken = TutorialConcurrentToken'
    { unTutorialConcurrentToken :: Int }
    deriving (Eq, Show, Data, Read, Typeable)
#else
-- | Token for a tutorial.
newtype TutorialConcurrentToken = TutorialConcurrentToken'
    { unTutorialConcurrentToken :: Int }
    deriving (Eq, Show, Data, Read, Typeable, PersistField, PersistFieldSql, Random, Num)

instance Default TutorialConcurrentToken where
    def = TutorialConcurrentToken' 1
#endif

--------------------------------------------------------------------------------
-- Isolation-runner ids

data CompileId = CompileId { unCompileId :: Int }
    deriving (Read, Typeable, Data, Show, Eq)

data ProcId = ProcId { unProcId :: Int }
    deriving (Read, Typeable, Data, Show, Eq)

data BuildId = BuildId { unBuildId :: Int }
    deriving (Read, Typeable, Data, Show, Eq)

data HoogleId = HoogleId { unHoogleId :: Int }
    deriving (Read, Typeable, Data, Show, Eq)

data SearchId = SearchId { unSearchId :: Int }
    deriving (Read, Typeable, Data, Show, Eq)

--------------------------------------------------------------------------------
-- Isolation-runner messages

data ProjectMessagesRequest
    = PMRImmediateStatusNoMessages
    | PMRImmediateStatusWithMessages ProjectMessagesFilter
    | PMRNextStatusWithMessages ProjectMessagesFilter StatusHash
    deriving (Read, Typeable, Data, Show, Eq)

data ProjectMessagesOutput
    = ProjectMessagesOutput ProjectMessagesFilter [(Maybe Int, RunnerMessage)]
    deriving (Read, Typeable, Data, Show, Eq)

data StatusHash = StatusHash Text
    deriving (Read, Typeable, Data, Show, Eq)

data ProjectMessagesFilter
    = PMFilterNone
    | PMFilterAll
    | PMFilterOnOrBefore Integer
    deriving (Read, Typeable, Data, Show, Eq)

data MessageTag = MessageTag
    { mtProjectId :: Maybe FayProjectId
    --TODO: use a better type than Int.
    , mtJobId     :: Maybe Int
    }
    deriving (Read, Typeable, Data, Show, Eq)

data RunnerMessageEnvelope = RunnerMessageEnvelope
    { rmeSeqNumber  :: Integer
    , rmeMessageTag :: MessageTag
    , rmeMessage    :: RunnerMessage
    }
    deriving (Read, Typeable, Data, Show, Eq)

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
    deriving (Read, Typeable, Data, Show, Eq)

data LogLevel
    = LevelDebug
    | LevelInfo
    | LevelWarn
    | LevelError
    | LevelOther Text
    deriving (Read, Typeable, Data, Show, Eq)

data ProjectStatusSnapshot = ProjectStatusSnapshot
    { snapOpeningStatus :: RunnerOpeningStatus
    , snapCompileStatus :: RunnerCompileStatus
    , snapProcessStatus :: ProcessStatusSnapshot
    , snapBuildStatus   :: RunnerBuildStatus
    }
    deriving (Read, Typeable, Data, Show, Eq)

data IdInfo
    = NoIdInfo SourceSpan -- ^ query span
    | IdInfo SourceSpan SourceSpan DefinitionSource -- ^ query span, result span, source info
    deriving (Read, Typeable, Data, Show, Eq)

data DefinitionSource = DefinitionLocal SourceSpan
                      | DefinitionTextSpan Text Text
                      | DefinitionImported Text FayModuleId FayModuleId EitherSpan EitherSpan
                      | DefinitionWiredIn Text
                      | DefinitionBinder Text
    deriving (Read, Typeable, Data, Show, Eq)

data AutoCompleteInput = AutoCompleteInput
    { aciModuleName :: FayFileName
    , aciPrefix     :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

data PackageId = PackageId
    { packageName    :: Text
    , packageVersion :: Maybe Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

data SearchResult = SearchResult SourceSpan [Either Text Text]
    deriving (Read, Typeable, Data, Show, Eq)

data HoogleResult = HoogleResult
    { hrURL     :: String
    , hrSources :: [(PackageLink, [ModuleLink])]
    , hrTitle   :: String -- ^ HTML
    , hrBody    :: String -- ^ plain text
    }
    deriving (Read, Typeable, Data, Show, Eq)

data PackageLink = PackageLink
    { plName :: String
    , plURL :: String
    }
    deriving (Read, Typeable, Data, Show, Eq)

data ModuleLink = ModuleLink
    { mlName :: String
    , mlURL :: String
    }
    deriving (Read, Typeable, Data, Show, Eq)

data RunnerOpeningStatus
    = RunnerProjectOpening Text
    | RunnerProjectOpen
    deriving (Read, Typeable, Data, Show, Eq)

data RunnerCompileStatus
    = RunnerNotCompiling
    | RunnerCompiling CompileId Progress
    | RunnerCompileDone CompileId [SourceInfo]
    deriving (Read, Typeable, Data, Show, Eq)

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
    deriving (Read, Typeable, Data, Show, Eq)

data RunnerBuildStatus
    = RunnerNotBuilding
    | RunnerBuildQueued
        { rbsId :: BuildId
        }
    | RunnerBuilding
        { rbsId :: BuildId
        , rbsProgress :: Progress
        }
    | RunnerBuildFailed
        { rbsId :: BuildId
        , rbsMsg :: Text
        }
    | RunnerBuildDone
        { rbsId :: BuildId
        , rbsResult :: BuildResult
        }
    deriving (Read, Typeable, Data, Show, Eq)

data BuildResult = BuildResult
    { brPathName   :: Text
    , brMainModule :: Text
    , brFileSize   :: Int
    }
    deriving (Read, Typeable, Data, Show, Eq)

data UploadedBuild = UploadedBuild
    { ubUrl :: Text
    , ubExe :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

-- | This type represents intermediate progress information during compilation.
data Progress = Progress
    {
      -- | The current step number
      --
      -- When these Progress messages are generated from progress updates from
      -- ghc, it is entirely possible that we might get step 4/26, 16/26, 3/26;
      -- the steps may not be continuous, might even be out of order, and may
      -- not finish at X/X.
      progressStep :: Int

      -- | The total number of steps
    , progressNumSteps :: Int

      -- | The parsed message. For instance, in the case of progress messages
      -- during compilation, 'progressOrigMsg' might be
      --
      -- > [1 of 2] Compiling M (some/path/to/file.hs, some/other/path/to/file.o)
      --
      -- while 'progressMsg' will just be 'Compiling M'
    , progressMsg :: Text
    }
    deriving (Read, Typeable, Data, Show, Eq)

data LaunchInfoSnapshot = LaunchInfoSnapshot
    { liSnapApproot  :: Maybe Text
    , liSnapPort     :: Maybe Int
    , liSnapLaunched :: Text -- ^ Timestamp
    }
    deriving (Read, Typeable, Data, Show, Eq)

data PortListeningResult
    = ProcessNotRunning
    | PortNotListening
    | PortIsListening
    | PortNotAllocated
    deriving (Read, Typeable, Data, Show, Eq)