module Fay.Types
  (JsStmt(..)
  ,JsExp(..)
  ,JsLit(..)
  ,JsName(..)
  ,CompileError(..)
  ,Compile(..)
  ,CompilesTo(..)
  ,Printable(..)
  ,Fay
  ,CompileReader(..)
  ,CompileWriter(..)
  ,CompileConfig(..)
  ,CompileState(..)
  ,addCurrentExport
  ,getCurrentExports
  ,getNonLocalExports
  ,getCurrentExportsWithoutNewtypes
  ,getExportsFor
  ,faySourceDir
  ,FundamentalType(..)
  ,PrintState(..)
  ,Printer(..)
  ,Mapping(..)
  ,SerializeContext(..)
  ,ModulePath (unModulePath)
  ,mkModulePath
  ,mkModulePaths
  ,mkModulePathFromQName
  ,addModulePath
  ,addedModulePath
  ) where
import           Control.Applicative
import           Control.Monad.Error    (Error, ErrorT, MonadError)
import           Control.Monad.Identity (Identity)
import           Control.Monad.State
import           Control.Monad.RWS
import           Data.Default
import           Data.List
import           Data.List.Split
import           Data.Maybe
import           Data.Map              (Map)
import qualified Data.Map              as M
import           Data.Set              (Set)
import qualified Data.Set              as S
import           Data.String
import           Language.Haskell.Exts
import           Fay.Compiler.ModuleScope (ModuleScope)
import           Fay.Compiler.QName
import           Paths_fay
data CompileConfig = CompileConfig
  { configOptimize           :: Bool                       
  , configFlattenApps        :: Bool                       
  , configExportBuiltins     :: Bool                       
  , configExportRuntime      :: Bool                       
  , configExportStdlib       :: Bool                       
  , configExportStdlibOnly   :: Bool                       
  , configDirectoryIncludes :: [(Maybe String, FilePath)]  
  , configPrettyPrint        :: Bool                       
  , configHtmlWrapper        :: Bool                       
  , configHtmlJSLibs         :: [FilePath]                 
  , configLibrary            :: Bool                       
  , configWarn               :: Bool                       
  , configFilePath           :: Maybe FilePath             
  , configTypecheck          :: Bool                       
  , configWall               :: Bool                       
  , configGClosure           :: Bool                       
  , configPackageConf        :: Maybe FilePath             
  , configPackages           :: [String]                   
  , configBasePath           :: Maybe FilePath             
  } deriving (Show)
newtype ModulePath = ModulePath { unModulePath :: [String] }
  deriving (Eq, Ord, Show)
mkModulePath :: ModuleName -> ModulePath
mkModulePath (ModuleName m) = ModulePath . splitOn "." $ m
mkModulePaths :: ModuleName -> [ModulePath]
mkModulePaths (ModuleName m) = map ModulePath . tail . inits . splitOn "." $ m
mkModulePathFromQName :: QName -> ModulePath
mkModulePathFromQName (Qual (ModuleName m) n) = mkModulePath $ ModuleName $ m ++ "." ++ unname n
mkModulePathFromQName _ = error "mkModulePathFromQName: Not a qualified name"
data CompileState = CompileState
  { _stateExports      :: Map ModuleName (Set QName) 
  , stateRecordTypes   :: [(QName,[QName])]          
  , stateRecords       :: [(QName,[QName])]          
  , stateNewtypes      :: [(QName, Maybe QName, Type)] 
  , stateImported      :: [(ModuleName,FilePath)]    
  , stateNameDepth     :: Integer                    
  , stateLocalScope    :: Set Name                   
  , stateModuleScope   :: ModuleScope                
  , stateModuleScopes  :: Map ModuleName ModuleScope
  , stateModuleName    :: ModuleName                 
  , stateJsModulePaths :: Set ModulePath
  , stateUseFromString :: Bool
  } 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       :: CompileConfig 
  , readerCompileLit   :: Literal -> Compile JsExp
  , readerCompileDecls :: Bool -> [Decl] -> Compile [JsStmt]
  }
faySourceDir :: IO FilePath
faySourceDir = getDataFileName "src/"
addModulePath :: ModulePath -> CompileState -> CompileState
addModulePath mp cs = cs { stateJsModulePaths = mp `S.insert` stateJsModulePaths cs }
addedModulePath :: ModulePath -> CompileState -> Bool
addedModulePath mp CompileState{..} = mp `S.member` stateJsModulePaths
addCurrentExport :: QName -> CompileState -> CompileState
addCurrentExport q cs =
    cs { _stateExports = M.insert (stateModuleName cs) qnames $ _stateExports cs}
  where
    qnames = maybe (S.singleton q) (S.insert q)
           $ M.lookup (stateModuleName cs) (_stateExports cs)
getCurrentExports :: CompileState -> Set QName
getCurrentExports cs = getExportsFor (stateModuleName cs) cs
getNonLocalExports :: CompileState -> Set QName
getNonLocalExports st = S.filter ((/= Just (stateModuleName st)) . qModName) . getCurrentExportsWithoutNewtypes $ st
getCurrentExportsWithoutNewtypes :: CompileState -> Set QName
getCurrentExportsWithoutNewtypes cs = excludeNewtypes cs $ getCurrentExports cs
  where
    excludeNewtypes :: CompileState -> Set QName -> Set QName
    excludeNewtypes cs' names =
      let newtypes = stateNewtypes cs'
          constrs = map (\(c, _, _) -> c) newtypes
          destrs  = map (\(_, d, _) -> fromJust d) . filter (\(_, d, _) -> isJust d) $ newtypes
       in names `S.difference` (S.fromList constrs `S.union` S.fromList destrs)
getExportsFor :: ModuleName -> CompileState -> Set QName
getExportsFor mn cs = fromMaybe S.empty $ M.lookup mn (_stateExports cs)
newtype Compile a = Compile
  { unCompile :: RWST CompileReader CompileWriter CompileState (ErrorT CompileError IO) a 
  }
  deriving (MonadState CompileState
           ,MonadError CompileError
           ,MonadReader CompileReader
           ,MonadWriter CompileWriter
           ,MonadIO
           ,Monad
           ,Functor
           ,Applicative)
class (Parseable from,Printable to) => CompilesTo from to | from -> to where
  compileTo :: from -> Compile to
data Mapping = Mapping
  { mappingName :: String 
  , mappingFrom :: SrcLoc 
  , mappingTo   :: SrcLoc 
  } deriving (Show)
data PrintState = PrintState
  { psPretty       :: Bool      
  , psLine         :: Int       
  , psColumn       :: Int       
  , psMapping      :: [Mapping] 
  , psIndentLevel  :: Int       
  , psOutput       :: [String]  
  , psNewline      :: Bool      
  }
instance Default PrintState where
  def = PrintState False 0 0 [] 0 [] False
newtype Printer a = Printer { runPrinter :: State PrintState a }
  deriving (Monad,Functor,MonadState PrintState)
class Printable a where
  printJS :: a -> Printer ()
data CompileError
  = ParseError SrcLoc String
  | UnsupportedDeclaration Decl
  | UnsupportedExportSpec ExportSpec
  | UnsupportedExpression Exp
  | UnsupportedFieldPattern PatField
  | UnsupportedImport ImportDecl
  | UnsupportedLet
  | UnsupportedLetBinding Decl
  | UnsupportedLiteral Literal
  | UnsupportedModuleSyntax Module
  | UnsupportedPattern Pat
  | UnsupportedQualStmt QualStmt
  | UnsupportedRecursiveDo
  | UnsupportedRhs Rhs
  | UnsupportedWhereInAlt Alt
  | UnsupportedWhereInMatch Match
  | EmptyDoBlock
  | InvalidDoBlock
  | Couldn'tFindImport ModuleName [FilePath]
  | FfiNeedsTypeSig Decl
  | FfiFormatBadChars SrcLoc String
  | FfiFormatNoSuchArg SrcLoc Int
  | FfiFormatIncompleteArg SrcLoc
  | FfiFormatInvalidJavaScript SrcLoc String String
  | UnableResolveQualified QName
  | GHCError String
  deriving (Show)
instance Error CompileError
newtype Fay a = Fay (Identity a)
  deriving Monad
data JsStmt
  = JsVar JsName JsExp
  | JsMappedVar SrcLoc JsName JsExp
  | JsIf JsExp [JsStmt] [JsStmt]
  | JsEarlyReturn JsExp
  | JsThrow JsExp
  | JsWhile JsExp [JsStmt]
  | JsUpdate JsName JsExp
  | JsSetProp JsName JsName JsExp
  | JsSetQName QName JsExp
  | JsSetModule ModulePath JsExp
  | JsSetConstructor QName JsExp
  | JsSetPropExtern JsName JsName JsExp
  | JsContinue
  | JsBlock [JsStmt]
  | JsExpStmt JsExp
  deriving (Show,Eq)
data JsExp
  = JsName JsName
  | JsRawExp String
  | JsSeq [JsExp]
  | JsFun (Maybe JsName) [JsName] [JsStmt] (Maybe JsExp)
  | JsLit JsLit
  | JsApp JsExp [JsExp]
  | JsNegApp JsExp
  | JsTernaryIf JsExp JsExp JsExp
  | JsNull
  | JsParen JsExp
  | JsGetProp JsExp JsName
  | JsLookup JsExp JsExp
  | JsUpdateProp JsExp JsName JsExp
  | JsGetPropExtern JsExp String
  | JsUpdatePropExtern JsExp JsName JsExp
  | JsList [JsExp]
  | JsNew JsName [JsExp]
  | JsThrowExp JsExp
  | JsInstanceOf JsExp JsName
  | JsIndex Int JsExp
  | JsEq JsExp JsExp
  | JsNeq JsExp JsExp
  | JsInfix String JsExp JsExp 
  | JsObj [(String,JsExp)]
  | JsLitObj [(Name,JsExp)]
  | JsUndefined
  | JsAnd JsExp JsExp
  | JsOr  JsExp JsExp
  deriving (Show,Eq)
data JsName
  = JsNameVar QName
  | JsThis
  | JsParametrizedType
  | JsThunk
  | JsForce
  | JsApply
  | JsParam Integer
  | JsTmp Integer
  | JsConstructor QName
  | JsBuiltIn Name
  | JsModuleName ModuleName
  deriving (Eq,Show)
data JsLit
  = JsChar Char
  | JsStr String
  | JsInt Int
  | JsFloating Double
  | JsBool Bool
  deriving (Show,Eq)
instance IsString JsLit where fromString = JsStr
data FundamentalType
   
 = FunctionType [FundamentalType]
 | JsType FundamentalType
 | ListType FundamentalType
 | TupleType [FundamentalType]
 | UserDefined Name [FundamentalType]
 | Defined FundamentalType
 | Nullable FundamentalType
 
 | DateType
 | StringType
 | DoubleType
 | IntType
 | BoolType
 | PtrType
 
 | Automatic
 
 | UnknownType
   deriving (Show)
instance IsString Name where
  fromString = Ident
instance IsString QName where
  fromString = UnQual . Ident
instance IsString ModuleName where
  fromString = ModuleName
data SerializeContext = SerializeAnywhere | SerializeUserArg Int
  deriving (Read,Show,Eq)