module Fay.Types
  ( JsStmt(..)
  , JsExp(..)
  , JsLit(..)
  , JsName(..)
  , CompileError(..)
  , Compile(..)
  , CompileModule
  , Printable(..)
  , Fay
  , CompileReader(..)
  , CompileResult(..)
  , CompileWriter(..)
  , Config(..)
  , CompileState(..)
  , FundamentalType(..)
  , PrintState(..)
  , defaultPrintState
  , PrintReader(..)
  , defaultPrintReader
  , PrintWriter(..)
  , pwOutputString
  , Printer(..)
  , execPrinter
  , indented
  , askIf
  , newline
  , write
  , mapping
  , SerializeContext(..)
  , ModulePath (unModulePath)
  , mkModulePath
  , mkModulePaths
  , mkModulePathFromQName
  ) where
import           Fay.Compiler.ModuleT
import           Fay.Config
import qualified Fay.Exts.NoAnnotation   as N
import qualified Fay.Exts.Scoped         as S
import           Fay.Types.CompileError
import           Fay.Types.CompileResult
import           Fay.Types.FFI
import           Fay.Types.Js
import           Fay.Types.ModulePath
import           Fay.Types.Printer
#if __GLASGOW_HASKELL__ < 710
import           Control.Applicative
#endif
import           Control.Monad.Except    (ExceptT, MonadError)
import           Control.Monad.Identity  (Identity)
import           Control.Monad.RWS
import           Data.Map                (Map)
import           Data.Set                (Set)
import           Language.Haskell.Names  (Symbols)
data CompileState = CompileState
  
  { stateInterfaces    :: Map N.ModuleName Symbols           
  , stateRecordTypes   :: [(N.QName,[N.QName])]              
  , stateRecords       :: [(N.QName,[N.Name])]               
  , stateNewtypes      :: [(N.QName, Maybe N.QName, N.Type)] 
  , stateImported      :: [(N.ModuleName,FilePath)]          
  , stateNameDepth     :: Integer                            
  , stateModuleName    :: N.ModuleName                       
  , stateJsModulePaths :: Set ModulePath                     
  , stateUseFromString :: Bool                               
  , stateTypeSigs      :: Map N.QName N.Type                 
  } deriving (Show)
data CompileWriter = CompileWriter
  { writerCons    :: [JsStmt]         
  , writerFayToJs :: [(String,JsExp)] 
  , writerJsToFay :: [(String,JsExp)] 
  } deriving (Show)
instance Monoid CompileWriter where
  mempty = CompileWriter [] [] []
  mappend (CompileWriter a b c) (CompileWriter x y z) =
    CompileWriter (a++x) (b++y) (c++z)
data CompileReader = CompileReader
  { readerConfig       :: Config 
  , readerCompileLit   :: S.Sign -> S.Literal -> Compile JsExp
  , readerCompileDecls :: Bool -> [S.Decl] -> Compile [JsStmt]
  }
newtype Compile a = Compile
  { unCompile :: RWST CompileReader CompileWriter CompileState
                      (ExceptT CompileError (ModuleT (ModuleInfo Compile) IO))
                      a 
  } deriving
    ( Applicative
    , Functor
    , Monad
    , MonadError CompileError
    , MonadIO
    , MonadReader CompileReader
    , MonadState CompileState
    , MonadWriter CompileWriter
    )
type CompileModule a = ModuleT Symbols IO (Either CompileError (a, CompileState, CompileWriter))
instance MonadModule Compile where
  type ModuleInfo Compile = Symbols
  lookupInCache        = liftModuleT . lookupInCache
  insertInCache n m    = liftModuleT $ insertInCache n m
  readModuleInfo fps n = liftModuleT $ readModuleInfo fps n
liftModuleT :: ModuleT Symbols IO a -> Compile a
liftModuleT = Compile . lift . lift
newtype Fay a = Fay (Identity a)
  deriving
    ( Applicative
    , Functor
    , Monad
    )