{-# LANGUAGE CPP #-}

-- | Types used by the runtime interpreter
module GHC.Runtime.Interpreter.Types
   ( Interp(..)
   , InterpInstance(..)
   , InterpProcess (..)
   , ExtInterp (..)
   , ExtInterpStatusVar
   , ExtInterpInstance (..)
   , ExtInterpState (..)
   , InterpStatus(..)
   -- * IServ
   , IServ
   , IServConfig(..)
   -- * JSInterp
   , JSInterp
   , JSInterpExtra (..)
   , JSInterpConfig (..)
   , JSState (..)
   , NodeJsSettings (..)
   , defaultNodeJsSettings
   )
where

import GHC.Prelude
import GHC.Linker.Types

import GHCi.RemoteTypes
import GHCi.Message         ( Pipe )
import GHC.Types.Unique.FM
import GHC.Data.FastString ( FastString )
import Foreign

import GHC.Utils.TmpFs
import GHC.Utils.Logger
import GHC.Unit.Env
import GHC.Unit.Types
import GHC.StgToJS.Types
import GHC.StgToJS.Linker.Types

import Control.Concurrent
import System.Process   ( ProcessHandle, CreateProcess )
import System.IO
import GHC.Unit.Finder.Types (FinderCache, FinderOpts)

-- | Interpreter
data Interp = Interp
  { Interp -> InterpInstance
interpInstance :: !InterpInstance
      -- ^ Interpreter instance (internal, external)

  , Interp -> Loader
interpLoader   :: !Loader
      -- ^ Interpreter loader
  }

data InterpInstance
   = ExternalInterp !ExtInterp -- ^ External interpreter
#if defined(HAVE_INTERNAL_INTERPRETER)
   | InternalInterp            -- ^ Internal interpreter
#endif

data ExtInterp
  = ExtIServ !IServ
  | ExtJS !JSInterp

-- | External interpreter
--
-- The external interpreter is spawned lazily (on first use) to avoid slowing
-- down sessions that don't require it. The contents of the MVar reflects the
-- state of the interpreter (running or not).
data ExtInterpState cfg details = ExtInterpState
  { forall cfg details. ExtInterpState cfg details -> cfg
interpConfig :: !cfg
  , forall cfg details.
ExtInterpState cfg details -> ExtInterpStatusVar details
interpStatus :: !(ExtInterpStatusVar details)
  }

type ExtInterpStatusVar d = MVar (InterpStatus (ExtInterpInstance d))

type IServ    = ExtInterpState IServConfig    ()
type JSInterp = ExtInterpState JSInterpConfig JSInterpExtra

data InterpProcess = InterpProcess
  { InterpProcess -> Pipe
interpPipe   :: !Pipe           -- ^ Pipe to communicate with the server
  , InterpProcess -> ProcessHandle
interpHandle :: !ProcessHandle  -- ^ Process handle of the server
  }

-- | Status of an external interpreter
data InterpStatus inst
   = InterpPending       -- ^ Not spawned yet
   | InterpRunning !inst -- ^ Running

-- | Configuration needed to spawn an external interpreter
data IServConfig = IServConfig
  { IServConfig -> String
iservConfProgram  :: !String   -- ^ External program to run
  , IServConfig -> [String]
iservConfOpts     :: ![String] -- ^ Command-line options
  , IServConfig -> Bool
iservConfProfiled :: !Bool     -- ^ Use Profiling way
  , IServConfig -> Bool
iservConfDynamic  :: !Bool     -- ^ Use Dynamic way
  , IServConfig -> Maybe (CreateProcess -> IO ProcessHandle)
iservConfHook     :: !(Maybe (CreateProcess -> IO ProcessHandle)) -- ^ Hook
  , IServConfig -> IO ()
iservConfTrace    :: IO ()     -- ^ Trace action executed after spawn
  }

-- | Common field between native external interpreter and the JS one
data ExtInterpInstance c = ExtInterpInstance
  { forall c. ExtInterpInstance c -> InterpProcess
instProcess       :: {-# UNPACK #-} !InterpProcess
      -- ^ External interpreter process and its pipe (communication channel)

  , forall c. ExtInterpInstance c -> MVar [HValueRef]
instPendingFrees  :: !(MVar [HValueRef])
      -- ^ Values that need to be freed before the next command is sent.
      -- Finalizers for ForeignRefs can append values to this list
      -- asynchronously.

  , forall c. ExtInterpInstance c -> MVar (UniqFM FastString (Ptr ()))
instLookupSymbolCache :: !(MVar (UniqFM FastString (Ptr ())))
      -- ^ LookupSymbol cache

  , forall c. ExtInterpInstance c -> c
instExtra             :: !c
      -- ^ Instance specific extra fields
  }

------------------------
-- JS Stuff
------------------------

data JSInterpExtra = JSInterpExtra
  { JSInterpExtra -> Handle
instStdIn       :: !Handle         -- ^ Stdin for the process
  , JSInterpExtra -> FinderCache
instFinderCache :: !FinderCache
  , JSInterpExtra -> FinderOpts
instFinderOpts  :: !FinderOpts
  , JSInterpExtra -> MVar JSState
instJSState     :: !(MVar JSState) -- ^ Mutable state
  , JSInterpExtra -> UnitId
instGhciUnitId  :: !UnitId         -- ^ GHCi unit-id
  }

data JSState = JSState
  { JSState -> LinkPlan
jsLinkState     :: !LinkPlan -- ^ Linker state of the interpreter
  , JSState -> Bool
jsServerStarted :: !Bool     -- ^ Is the Haskell server started?
  }

-- | NodeJs configuration
data NodeJsSettings = NodeJsSettings
  { NodeJsSettings -> String
nodeProgram         :: FilePath        -- ^ location of node.js program
  , NodeJsSettings -> Maybe String
nodePath            :: Maybe FilePath  -- ^ value of NODE_PATH environment variable (search path for Node modules; GHCJS used to provide some)
  , NodeJsSettings -> [String]
nodeExtraArgs       :: [String]        -- ^ extra arguments to pass to node.js
  , NodeJsSettings -> Integer
nodeKeepAliveMaxMem :: Integer         -- ^ keep node.js (TH, GHCJSi) processes alive if they don't use more than this
  }

defaultNodeJsSettings :: NodeJsSettings
defaultNodeJsSettings :: NodeJsSettings
defaultNodeJsSettings = NodeJsSettings
  { nodeProgram :: String
nodeProgram         = String
"node"
  , nodePath :: Maybe String
nodePath            = Maybe String
forall a. Maybe a
Nothing
  , nodeExtraArgs :: [String]
nodeExtraArgs       = []
  , nodeKeepAliveMaxMem :: Integer
nodeKeepAliveMaxMem = Integer
536870912
  }


data JSInterpConfig = JSInterpConfig
  { JSInterpConfig -> NodeJsSettings
jsInterpNodeConfig  :: !NodeJsSettings  -- ^ NodeJS settings
  , JSInterpConfig -> String
jsInterpScript      :: !FilePath        -- ^ Path to "ghc-interp.js" script
  , JSInterpConfig -> TmpFs
jsInterpTmpFs       :: !TmpFs
  , JSInterpConfig -> TempDir
jsInterpTmpDir      :: !TempDir
  , JSInterpConfig -> Logger
jsInterpLogger      :: !Logger
  , JSInterpConfig -> StgToJSConfig
jsInterpCodegenCfg  :: !StgToJSConfig
  , JSInterpConfig -> UnitEnv
jsInterpUnitEnv     :: !UnitEnv
  , JSInterpConfig -> FinderOpts
jsInterpFinderOpts  :: !FinderOpts
  , JSInterpConfig -> FinderCache
jsInterpFinderCache :: !FinderCache
  }