module Heist
  (
  
    loadTemplates
  , reloadTemplates
  , addTemplatePathPrefix
  , initHeist
  , initHeistWithCacheTag
  , defaultInterpretedSplices
  , defaultLoadTimeSplices
  , emptyHeistConfig
  
  , SpliceConfig
  , HeistConfig
  , TemplateRepo
  , TemplateLocation
  , Template
  , TPath
  , MIMEType
  , DocumentFile(..)
  , AttrSplice
  , RuntimeSplice
  , Chunk
  , HeistState
  , SpliceError(..)
  , CompileException(..)
  , HeistT
  
  , scInterpretedSplices
  , scLoadTimeSplices
  , scCompiledSplices
  , scAttributeSplices
  , scTemplateLocations
  , scCompiledTemplateFilter
  , hcSpliceConfig
  , hcNamespace
  , hcErrorNotBound
  , hcInterpretedSplices
  , hcLoadTimeSplices
  , hcCompiledSplices
  , hcAttributeSplices
  , hcTemplateLocations
  , hcCompiledTemplateFilter
  
  , templateNames
  , compiledTemplateNames
  , hasTemplate
  , spliceNames
  , compiledSpliceNames
  , evalHeistT
  , getParamNode
  , getContext
  , getTemplateFilePath
  , localParamNode
  , getsHS
  , getHS
  , putHS
  , modifyHS
  , restoreHS
  , localHS
  , getDoc
  , getXMLDoc
  , tellSpliceError
  , spliceErrorText
  , orError
  , Splices
  ) where
import           Control.Exception.Lifted
import           Control.Monad.State
import           Data.ByteString               (ByteString)
import qualified Data.ByteString               as B
import           Data.Either
import qualified Data.Foldable                 as F
import           Data.HashMap.Strict           (HashMap)
import qualified Data.HashMap.Strict           as Map
import qualified Data.HeterogeneousEnvironment as HE
import           Data.Map.Syntax
import           Data.Monoid
import           Data.Text                     (Text)
import qualified Data.Text                     as T
import           System.Directory.Tree
import qualified Text.XmlHtml                  as X
import           Heist.Common
import qualified Heist.Compiled.Internal       as C
import qualified Heist.Interpreted.Internal    as I
import           Heist.Splices
import           Heist.Internal.Types
defaultLoadTimeSplices :: MonadIO m => Splices (I.Splice m)
defaultLoadTimeSplices = do
    
    defaultInterpretedSplices
    "content" #! deprecatedContentCheck
defaultInterpretedSplices :: MonadIO m => Splices (I.Splice m)
defaultInterpretedSplices = do
    applyTag ## applyImpl
    bindTag ## bindImpl
    ignoreTag ## ignoreImpl
    markdownTag ## markdownSplice
emptyHeistConfig :: HeistConfig m
emptyHeistConfig = HeistConfig mempty "h" True
allErrors :: [Either String (TPath, v)]
          -> Either [String] (HashMap TPath v)
allErrors tlist =
    case errs of
        [] -> Right $ Map.fromList $ rights tlist
        _  -> Left errs
  where
    errs = lefts tlist
loadTemplates :: FilePath -> IO (Either [String] TemplateRepo)
loadTemplates dir = do
    d <- readDirectoryWith (loadTemplate dir) dir
#if MIN_VERSION_directory_tree(0,11,0)
    return $ allErrors $ F.fold (dirTree d)
#else
    return $ allErrors $ F.fold (free d)
#endif
reloadTemplates :: TemplateRepo -> IO (Either [String] TemplateRepo)
reloadTemplates repo = do
    tlist <- mapM loadOrKeep $ Map.toList repo
    return $ allErrors tlist
  where
    loadOrKeep (p,df) =
      case dfFile df of
        Nothing -> return $ Right (p, df)
        Just fp -> do
          df' <- loadTemplate' fp
          return $ fmap (p,) $ case df' of
            [t] -> t
            _ -> Left "Template repo has non-templates"
addTemplatePathPrefix :: ByteString -> TemplateRepo -> TemplateRepo
addTemplatePathPrefix dir ts
  | B.null dir = ts
  | otherwise  = Map.fromList $
                 map (\(x,y) -> (f x, y)) $
                 Map.toList ts
  where
    f ps = ps++splitTemplatePath dir
emptyHS :: HE.KeyGen -> HeistState m
emptyHS kg = HeistState Map.empty Map.empty Map.empty Map.empty Map.empty
                        True [] [] 0 [] Nothing kg False Html "" [] False 0
initHeist :: Monad n
          => HeistConfig n
          -> IO (Either [String] (HeistState n))
initHeist hc = do
    keyGen <- HE.newKeyGen
    repos <- sequence $ _scTemplateLocations $ _hcSpliceConfig hc
    case sequence repos of
      Left es -> return $ Left es
      Right rs -> initHeist' keyGen hc (Map.unions rs)
mkSplicePrefix :: Text -> Text
mkSplicePrefix ns
  | T.null ns = ""
  | otherwise = ns `mappend` ":"
initHeist' :: Monad n
           => HE.KeyGen
           -> HeistConfig n
           -> TemplateRepo
           -> IO (Either [String] (HeistState n))
initHeist' keyGen (HeistConfig sc ns enn) repo = do
    let empty = emptyHS keyGen
    let (SpliceConfig i lt c a _ f) = sc
    etmap <- preproc keyGen lt repo ns
    let prefix = mkSplicePrefix ns
    let eis = runHashMap $ mapK (prefix<>) i
        ecs = runHashMap $ mapK (prefix<>) c
        eas = runHashMap $ mapK (prefix<>) a
    let hs1 = do
          tmap <- etmap
          is <- eis
          cs <- ecs
          as <- eas
          return $ empty { _spliceMap = is
                         , _templateMap = tmap
                         , _compiledSpliceMap = cs
                         , _attrSpliceMap = as
                         , _splicePrefix = prefix
                         , _errorNotBound = enn
                         }
    either (return . Left) (C.compileTemplates f) hs1
preproc :: HE.KeyGen
        -> Splices (I.Splice IO)
        -> TemplateRepo
        -> Text
        -> IO (Either [String] TemplateRepo)
preproc keyGen splices templates ns = do
    let esm = runHashMap splices
    case esm of
      Left errs -> return $ Left errs
      Right sm -> do
        let hs = (emptyHS keyGen) { _spliceMap = sm
                                  , _templateMap = templates
                                  , _preprocessingMode = True
                                  , _splicePrefix = mkSplicePrefix ns }
        let eval a = evalHeistT a (X.TextNode "") hs
        tPairs <- mapM (eval . preprocess) $ Map.toList templates
        let bad = lefts tPairs
        return $ if not (null bad)
                   then Left bad
                   else Right $ Map.fromList $ rights tPairs
preprocess :: (TPath, DocumentFile)
           -> HeistT IO IO (Either String (TPath, DocumentFile))
preprocess (tpath, docFile) = do
    let tname = tpathName tpath
    !emdoc <- try $ I.evalWithDoctypes tname
              :: HeistT IO IO (Either SomeException (Maybe X.Document))
    let f !doc = (tpath, docFile { dfDoc = doc })
    return $! either (Left . show) (Right . maybe die f) emdoc
  where
    die = error "Preprocess didn't succeed!  This should never happen."
initHeistWithCacheTag :: MonadIO n
                      => HeistConfig n
                      -> IO (Either [String] (HeistState n, CacheTagState))
initHeistWithCacheTag (HeistConfig sc ns enn) = do
    (ss, cts) <- liftIO mkCacheTag
    let tag = "cache"
    keyGen <- HE.newKeyGen
    erepos <- sequence $ _scTemplateLocations sc
    case sequence erepos of
      Left es -> return $ Left es
      Right repos -> do
        
        
        
        
        eRawWithCache <- preproc keyGen (tag ## ss) (Map.unions repos) ns
        case eRawWithCache of
          Left es -> return $ Left es
          Right rawWithCache -> do
            let sc' = SpliceConfig (tag #! cacheImpl cts) mempty
                                   (tag #! cacheImplCompiled cts)
                                   mempty mempty (const True)
            let hc = HeistConfig (mappend sc sc') ns enn
            hs <- initHeist' keyGen hc rawWithCache
            return $ fmap (,cts) hs