module FP.Server.Types where
import           FP.API.Types
import           FP.Server.Config
import           Control.Concurrent.STM
import           Control.Monad.Logger hiding (Loc)
import           Control.Monad.Reader
import           Data.Aeson
import           Data.Default
import           Data.Map (Map)
import           Data.Text
import           FP.API.Common
import           GHC.Generics
import           Data.IORef
import           Network.HTTP.Conduit
import           Prelude
type ServerM r = ReaderT (ServerState, r) (LoggingT IO)
type Server = ServerM ProjectId
data ServerState = ServerState
  { serverCC :: ClientConfig
  , serverConfig :: Config
  , serverProjects :: TVar (Map ProjectId (ClientInfo Server))
  }
data ClientConfig = CC
  { ccUrl       :: !Text
  , ccToken     :: !Text
  , ccManager   :: !Manager
  , ccCookie    :: !(IORef CookieJar)
  , ccUserAgent :: !Text
  }
data Config = Config
  { configToken :: !Text
  , configUrl   :: !Text
  , configPort  :: !Integer
  , configAgent :: !Text
  , configDebug :: !Bool
  , configStartServer :: !Bool
  } deriving (Show)
instance Default Config where
  def = Config "" defaultUrl defaultPort "fpco-api" True False
data Msg = MsgSaveModule ProjectId FilePath FilePath
         | MsgCheckModule ProjectId FilePath FilePath FilePath
         | MsgTypeInfo ProjectId FilePath Int Int Int Int
         | MsgGetDefinition ProjectId FilePath FilePath Int Int Int Int
         | MsgAutoComplete ProjectId FilePath Text
         | MsgHoogleIdent ProjectId FilePath Text
         | MsgHoogleDb ProjectId Text
         | MsgDownloadFiles (Either Text ProjectId) FilePath
         | MsgWriteEmacsConfig (Either Text ProjectId) FilePath
         | MsgRunTarget ProjectId
  deriving (Generic,Show)
instance FromJSON Msg
instance ToJSON Msg
data ProcessMsg
  = MsgStdin Text
  | MsgKill (Maybe ()) 
  deriving (Generic,Show)
instance FromJSON ProcessMsg
instance ToJSON ProcessMsg
data Reply = ReplyPong ()
           | ReplyOK ()
           | ReplyCompileMessages [CompileMessage]
           | ReplyCompileInfos [SourceInfo]
           | ReplyTypeInfo [SpanType]
           | ReplyLocation DefinitionLoc
           | ReplyCompletions [Text]
           | ReplyHoogleResults [HoogleResult]
           | ReplyHoogleResult HoogleResult
           | ReplySaveStatus Bool
           | ReplyStdout Text
           | ReplyStderr Text
           | ReplyWebUrl Approot
 deriving (Generic,Show)
instance ToJSON Reply
instance FromJSON Reply
data DefinitionLoc = DefinitionLoc Loc
                   | DefinitionUseless Text
                   | DefinitionImport Text          
                                      PackageModule 
                                      PackageModule 
                                      (Maybe Loc)   
                                      (Maybe Loc)   
  deriving (Generic,Show)
instance ToJSON DefinitionLoc
instance FromJSON DefinitionLoc
data PackageModule = PackageModule Text 
                                   Text 
  deriving (Generic,Show)
instance ToJSON PackageModule
instance FromJSON PackageModule
data Loc = Loc FilePath Int Int Int Int
  deriving (Generic,Show)
instance ToJSON Loc
instance FromJSON Loc
data SpanType = SpanType Int Int Int Int 
                         Text            
                         [Text]          
  deriving (Generic,Show)
instance ToJSON SpanType
instance FromJSON SpanType
data CompileMessage = CompileMessage Text Text Text
   deriving (Show,Generic)
instance ToJSON CompileMessage
instance FromJSON CompileMessage