module IdeSession.Types.Public (
    
    IdNameSpace(..)
  , Type
  , Name
  , IdInfo(..)
  , IdProp(..)
  , IdScope(..)
  , SourceSpan(..)
  , EitherSpan(..)
  , SourceError(..)
  , SourceErrorKind(..)
  , ModuleName
  , ModuleId(..)
  , PackageId(..)
  , ImportEntities(..)
  , Import(..)
  , SpanInfo(..)
  , RunBufferMode(..)
  , RunResult(..)
  , BreakInfo(..)
  , Value
  , VariableEnv
  , Targets(..)
  , UpdateStatus(..)
    
  , idInfoQN
  , haddockLink
  ) where
import Prelude hiding (span)
import Control.Applicative ((<$>), (<*>))
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Binary (Binary(..), getWord8, putWord8)
import Data.Aeson.TH (deriveJSON, defaultOptions)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import IdeSession.Util () 
import IdeSession.Util.PrettyVal
import IdeSession.Types.Progress
data IdNameSpace =
    VarName    
  | DataName   
  | TvName     
  | TcClsName  
  deriving (Show, Eq, Generic)
data IdInfo = IdInfo {
    idProp  ::  !IdProp
  , idScope :: !IdScope
  }
  deriving (Eq, Generic)
type Name = Text
type Type = Text
data IdProp = IdProp {
    
    
    idName  :: !Name
    
  , idSpace :: !IdNameSpace
    
    
    
  , idType  :: !(Maybe Type)
    
  , idDefinedIn ::  !ModuleId
    
  , idDefSpan :: !EitherSpan
    
  , idHomeModule :: !(Maybe ModuleId)
  }
  deriving (Eq, Generic)
data IdScope =
    
    Binder
    
  | Local
    
  | Imported {
        idImportedFrom ::  !ModuleId
      , idImportSpan   :: !EitherSpan
        
        
        
        
        
        
      , idImportQual   :: !Text
      }
    
  | WiredIn
  deriving (Eq, Generic)
data SourceSpan = SourceSpan
  { spanFilePath   :: !FilePath
  , spanFromLine   ::  !Int
  , spanFromColumn ::  !Int
  , spanToLine     ::  !Int
  , spanToColumn   ::  !Int
  }
  deriving (Eq, Ord, Generic)
data EitherSpan =
    ProperSpan  !SourceSpan
  | TextSpan !Text
  deriving (Eq, Generic)
data SourceError = SourceError
  { errorKind :: !SourceErrorKind
  , errorSpan :: !EitherSpan
  , errorMsg  :: !Text
  }
  deriving (Show, Eq, Generic)
data SourceErrorKind = KindError | KindWarning | KindServerDied
  deriving (Show, Eq, Generic)
type ModuleName = Text
data ModuleId = ModuleId
  { moduleName    :: !ModuleName
  , modulePackage ::  !PackageId
  }
  deriving (Eq, Ord, Generic)
data PackageId = PackageId
  { packageName    :: !Text
  , packageVersion :: !(Maybe Text)
  , packageKey     :: !Text
  }
  deriving (Eq, Ord, Generic)
data ImportEntities =
    ImportOnly   ![Text]
  | ImportHiding ![Text]
  | ImportAll
  deriving (Show, Eq, Ord, Generic)
data Import = Import {
    importModule    :: !ModuleId
  
  , importPackage   :: !(Maybe Text)
  , importQualified :: !Bool
  , importImplicit  :: !Bool
  , importAs        :: !(Maybe ModuleName)
  , importEntities  :: !ImportEntities
  }
  deriving (Show, Eq, Ord, Generic)
data SpanInfo =
    
    SpanId IdInfo
    
  | SpanQQ IdInfo
  deriving (Eq, Generic)
data RunBufferMode =
    RunNoBuffering
  | RunLineBuffering  { runBufferTimeout   :: Maybe Int }
  | RunBlockBuffering { runBufferBlockSize :: Maybe Int
                      , runBufferTimeout   :: Maybe Int
                      }
  deriving (Typeable, Show, Generic, Eq)
data RunResult =
    
    RunOk
    
  | RunProgException String
    
  | RunGhcException String
    
  | RunForceCancelled
    
  | RunBreak
  deriving (Typeable, Show, Eq, Generic)
data BreakInfo = BreakInfo {
    
    breakInfoModule :: ModuleName
    
  , breakInfoSpan :: SourceSpan
    
  , breakInfoResultType :: Type
    
  , breakInfoVariableEnv :: VariableEnv
  }
  deriving (Typeable, Show, Eq, Generic)
type Value = Text
type VariableEnv = [(Name, Type, Value)]
data Targets = TargetsInclude [FilePath] | TargetsExclude [FilePath]
  deriving (Typeable, Generic, Eq, Show)
data UpdateStatus =
    UpdateStatusFailed Text
  | UpdateStatusRequiredRestart
  | UpdateStatusCrashRestart Text
  | UpdateStatusServerDied Text
  | UpdateStatusProgress Progress
  | UpdateStatusDone
  deriving (Typeable, Generic, Eq, Show)
instance Show SourceSpan where
  show (SourceSpan{..}) =
       spanFilePath ++ "@"
    ++ show spanFromLine ++ ":" ++ show spanFromColumn ++ "-"
    ++ show spanToLine   ++ ":" ++ show spanToColumn
instance Show IdProp where
  show (IdProp {..}) =
       Text.unpack idName ++ " "
    ++ "(" ++ show idSpace ++ ")"
    ++ (case idType of Just typ -> " :: " ++ Text.unpack typ; Nothing -> [])
    ++ " defined in "
    ++ show idDefinedIn
    ++ " at " ++ show idDefSpan
    ++ (case idHomeModule of Just home -> " (home " ++ show home ++ ")"
                             Nothing   -> "")
instance Show IdScope where
  show Binder          = "binding occurrence"
  show Local           = "defined locally"
  show WiredIn         = "wired in to the compiler"
  show (Imported {..}) =
           "imported from " ++ show idImportedFrom
        ++ (if Text.null idImportQual
              then []
              else " as '" ++ Text.unpack idImportQual ++ "'")
        ++ " at "++ show idImportSpan
instance Show EitherSpan where
  show (ProperSpan srcSpan) = show srcSpan
  show (TextSpan str)       = Text.unpack str
instance Show ModuleId where
  show (ModuleId mo pkg) = show pkg ++ ":" ++ Text.unpack mo
instance Show PackageId where
  show (PackageId name (Just version) _pkey) =
    Text.unpack name ++ "-" ++ Text.unpack version
  show (PackageId name Nothing _pkey) =
    Text.unpack name
instance Show IdInfo where
  show IdInfo{..} = show idProp ++ " (" ++ show idScope ++ ")"
instance Show SpanInfo where
  show (SpanId idInfo) = show idInfo
  show (SpanQQ idInfo) = "quasi-quote with quoter " ++ show idInfo
instance Binary IdNameSpace where
  put VarName   = putWord8 0
  put DataName  = putWord8 1
  put TvName    = putWord8 2
  put TcClsName = putWord8 3
  get = do
    header <- getWord8
    case header of
      0 -> return VarName
      1 -> return DataName
      2 -> return TvName
      3 -> return TcClsName
      _ -> fail "IdNameSpace.get: invalid header"
instance Binary SourceErrorKind where
  put KindError      = putWord8 0
  put KindWarning    = putWord8 1
  put KindServerDied = putWord8 2
  get = do
    header <- getWord8
    case header of
      0 -> return KindError
      1 -> return KindWarning
      2 -> return KindServerDied
      _ -> fail "SourceErrorKind.get: invalid header"
instance Binary ImportEntities where
  put (ImportOnly names)   = putWord8 0 >> put names
  put (ImportHiding names) = putWord8 1 >> put names
  put ImportAll            = putWord8 2
  get = do
    header <- getWord8
    case header of
      0 -> ImportOnly   <$> get
      1 -> ImportHiding <$> get
      2 -> return ImportAll
      _ -> fail "ImportEntities.get: invalid header"
instance Binary Import where
  put Import{..} = do
    put importModule
    put importPackage
    put importQualified
    put importImplicit
    put importAs
    put importEntities
  get = Import <$> get <*> get <*> get <*> get <*> get <*> get
instance Binary SourceError where
  put SourceError{..} = do
    put errorKind
    put errorSpan
    put errorMsg
  get = SourceError <$> get <*> get <*> get
instance Binary IdProp where
  put IdProp{..} = do
    put idName
    put idSpace
    put idType
    put idDefinedIn
    put idDefSpan
    put idHomeModule
  get = IdProp <$> get <*> get <*> get <*> get <*> get <*> get
instance Binary IdScope where
  put Binder       = putWord8 0
  put Local        = putWord8 1
  put Imported{..} = do putWord8 2
                        put idImportedFrom
                        put idImportSpan
                        put idImportQual
  put WiredIn      = putWord8 3
  get = do
    header <- getWord8
    case header of
      0 -> return Binder
      1 -> return Local
      2 -> Imported <$> get <*> get <*> get
      3 -> return WiredIn
      _ -> fail "IdScope.get: invalid header"
instance Binary SourceSpan where
  put (SourceSpan{..}) = do
    put spanFilePath
    put spanFromLine
    put spanFromColumn
    put spanToLine
    put spanToColumn
  get = SourceSpan <$> get <*> get <*> get <*> get <*> get
instance Binary EitherSpan where
  put (ProperSpan span) = putWord8 0 >> put span
  put (TextSpan text)   = putWord8 1 >> put text
  get = do
    header <- getWord8
    case header of
      0 -> ProperSpan <$> get
      1 -> TextSpan <$> get
      _ -> fail "EitherSpan.get: invalid header"
instance Binary ModuleId where
  put ModuleId{..} = put moduleName >> put modulePackage
  get = ModuleId <$> get <*> get
instance Binary PackageId where
  put PackageId{..} = do
    put packageName
    put packageVersion
    put packageKey
  get = PackageId <$> get <*> get <*> get
instance Binary IdInfo where
  put IdInfo{..} = put idProp >> put idScope
  get = IdInfo <$> get <*> get
instance Binary RunBufferMode where
  put RunNoBuffering        = putWord8 0
  put RunLineBuffering{..}  = do putWord8 1
                                 put runBufferTimeout
  put RunBlockBuffering{..} = do putWord8 2
                                 put runBufferBlockSize
                                 put runBufferTimeout
  get = do
    header <- getWord8
    case header of
      0 -> return RunNoBuffering
      1 -> RunLineBuffering <$> get
      2 -> RunBlockBuffering <$> get <*> get
      _ -> fail "RunBufferMode.get: invalid header"
instance Binary Targets where
  put (TargetsInclude l) = do
    putWord8 0
    put l
  put (TargetsExclude l) = do
    putWord8 1
    put l
  get = do
    header <- getWord8
    case header of
      0 -> TargetsInclude <$> get
      1 -> TargetsExclude <$> get
      _ -> fail "Targets.get: invalid header"
$(concat <$> mapM (deriveJSON defaultOptions)
  [ ''BreakInfo
  , ''EitherSpan
  , ''IdInfo
  , ''IdNameSpace
  , ''IdProp
  , ''IdScope
  , ''Import
  , ''ImportEntities
  , ''ModuleId
  , ''PackageId
  , ''RunBufferMode
  , ''RunResult
  , ''SourceError
  , ''SourceErrorKind
  , ''SourceSpan
  , ''SpanInfo
  , ''UpdateStatus
  ])
instance PrettyVal IdNameSpace
instance PrettyVal IdInfo
instance PrettyVal IdProp
instance PrettyVal IdScope
instance PrettyVal SourceSpan
instance PrettyVal EitherSpan
instance PrettyVal SourceError
instance PrettyVal SourceErrorKind
instance PrettyVal ModuleId
instance PrettyVal PackageId
instance PrettyVal ImportEntities
instance PrettyVal Import
instance PrettyVal SpanInfo
instance PrettyVal RunBufferMode
instance PrettyVal RunResult
instance PrettyVal BreakInfo
instance PrettyVal Targets
instance PrettyVal UpdateStatus
idInfoQN :: IdInfo -> String
idInfoQN IdInfo{idProp = IdProp{idName}, idScope} =
  case idScope of
    Binder                 -> Text.unpack idName
    Local{}                -> Text.unpack idName
    Imported{idImportQual} -> Text.unpack idImportQual ++ Text.unpack idName
    WiredIn                -> Text.unpack idName
haddockSpaceMarks :: IdNameSpace -> String
haddockSpaceMarks VarName   = "v"
haddockSpaceMarks DataName  = "v"
haddockSpaceMarks TvName    = "t"
haddockSpaceMarks TcClsName = "t"
haddockLink :: IdProp -> IdScope -> String
haddockLink IdProp{..} idScope =
  case idScope of
    Imported{idImportedFrom} ->
         dashToSlash (modulePackage idImportedFrom)
      ++ "/doc/html/"
      ++ dotToDash (Text.unpack $ moduleName idImportedFrom) ++ ".html#"
      ++ haddockSpaceMarks idSpace ++ ":"
      ++ Text.unpack idName
    _ -> "<local identifier>"
 where
   dotToDash = map (\c -> if c == '.' then '-' else c)
   dashToSlash p = case packageVersion p of
     Nothing      -> Text.unpack (packageName p) ++ "/latest"
     Just version -> Text.unpack (packageName p) ++ "/" ++ Text.unpack version