{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE TypeSynonymInstances       #-}
{-# OPTIONS_GHC -fno-warn-orphans  #-}
module Text.Mustache.Render
  (
  
    substitute, substituteValue
  
  , checkedSubstitute, checkedSubstituteValue, SubstitutionError(..)
  
  , Context(..), search, innerSearch, SubM, substituteNode, substituteAST, catchSubstitute
  
  , toString
  ) where
import           Control.Arrow                (first, second)
import           Control.Monad
import           Data.Foldable                (for_)
import           Data.HashMap.Strict          as HM hiding (keys, map)
import           Data.Maybe                   (fromMaybe)
import           Data.Scientific              (floatingOrInteger)
import           Data.Text                    as T (Text, isSuffixOf, pack,
                                                    replace, stripSuffix)
import qualified Data.Vector                  as V
import           Prelude                      hiding (length, lines, unlines)
import           Control.Monad.Reader
import           Control.Monad.Writer
import qualified Data.Text                    as T
import qualified Data.Text.Lazy               as LT
import           Text.Mustache.Internal
import           Text.Mustache.Internal.Types
import           Text.Mustache.Types
substitute :: ToMustache k => Template -> k -> Text
substitute t = substituteValue t . toMustache
checkedSubstitute :: ToMustache k => Template -> k -> ([SubstitutionError], Text)
checkedSubstitute t = checkedSubstituteValue t . toMustache
substituteValue :: Template -> Value -> Text
substituteValue = (snd .) . checkedSubstituteValue
checkedSubstituteValue :: Template -> Value -> ([SubstitutionError], Text)
checkedSubstituteValue template dataStruct =
  second T.concat $ runSubM (substituteAST (ast template)) (Context mempty dataStruct) (partials template)
catchSubstitute :: SubM a -> SubM (a, Text)
catchSubstitute = fmap (second (T.concat . snd)) . SubM . hideResults . listen . runSubM'
  where
    hideResults = censor (\(errs, _) -> (errs, []))
substituteAST :: STree -> SubM ()
substituteAST = mapM_ substituteNode
substituteNode :: Node Text -> SubM ()
substituteNode (TextBlock t) = tellSuccess t
substituteNode (Section Implicit secSTree) =
  asks fst >>= \case
    Context parents focus@(Array a)
      | V.null a  -> return ()
      | otherwise -> for_ a $ \focus' ->
        let newContext = Context (focus:parents) focus'
        in shiftContext newContext $ substituteAST secSTree
    Context _ (Object _) -> substituteAST secSTree
    Context _ v -> tellError $ InvalidImplicitSectionContextType $ showValueType v
substituteNode (Section (NamedData secName) secSTree) =
  search secName >>= \case
    Just arr@(Array arrCont) ->
      if V.null arrCont
        then return ()
        else do
          Context parents focus <- asks fst
          for_ arrCont $ \focus' ->
            let newContext = Context (arr:focus:parents) focus'
            in shiftContext newContext $ substituteAST secSTree
    Just (Bool False) -> return ()
    Just Null         -> return ()
    Just (Lambda l)   -> substituteAST =<< l secSTree
    Just focus'       -> do
      Context parents focus <- asks fst
      let newContext = Context (focus:parents) focus'
      shiftContext newContext $ substituteAST secSTree
    Nothing -> tellError $ SectionTargetNotFound secName
substituteNode (InvertedSection  Implicit _) = tellError InvertedImplicitSection
substituteNode (InvertedSection (NamedData secName) invSecSTree) =
  search secName >>= \case
    Just (Bool False) -> contents
    Just (Array a)    | V.null a -> contents
    Nothing           -> contents
    _                 -> return ()
  where
    contents = mapM_ substituteNode invSecSTree
substituteNode (Variable _ Implicit) = asks (ctxtFocus . fst) >>= toString >>= tellSuccess
substituteNode (Variable escaped (NamedData varName)) =
  maybe
    (tellError $ VariableNotFound varName)
    (toString >=> tellSuccess . (if escaped then escapeXMLText else id))
    =<< search varName
substituteNode (Partial indent pName) = do
  cPartials <- asks snd
  case HM.lookup pName cPartials of
    Nothing -> tellError $ PartialNotFound pName
    Just t ->
      let ast' = handleIndent indent $ ast t
      in local (second (partials t `HM.union`)) $ substituteAST ast'
showValueType :: Value -> String
showValueType Null       = "Null"
showValueType (Object _) = "Object"
showValueType (Array _)  = "Array"
showValueType (String _) = "String"
showValueType (Lambda _) = "Lambda"
showValueType (Number _) = "Number"
showValueType (Bool _)   = "Bool"
handleIndent :: Maybe Text -> STree -> STree
handleIndent Nothing ast' = ast'
handleIndent (Just indentation) ast' = preface <> content
  where
    preface = if T.null indentation then [] else [TextBlock indentation]
    content = if T.null indentation
      then ast'
      else reverse $ fromMaybe [] (uncurry (:) . first dropper <$> uncons (reverse fullIndented))
      where
        fullIndented = fmap (indentBy indentation) ast'
        dropper (TextBlock t) = TextBlock $
          if ("\n" <> indentation) `isSuffixOf` t
            then fromMaybe t $ stripSuffix indentation t
            else t
        dropper a = a
indentBy :: Text -> Node Text -> Node Text
indentBy indent p@(Partial (Just indent') name')
  | T.null indent = p
  | otherwise = Partial (Just (indent <> indent')) name'
indentBy indent (Partial Nothing name') = Partial (Just indent) name'
indentBy indent (TextBlock t) = TextBlock $ replace "\n" ("\n" <> indent) t
indentBy _ a = a
toString :: Value -> SubM Text
toString (String t) = return t
toString (Number n) = return $ either (pack . show) (pack . show) (floatingOrInteger n :: Either Double Integer)
toString (Lambda l) = do
  ((), res) <- catchSubstitute $ substituteAST =<< l []
  return res
toString e          = do
  tellError $ DirectlyRenderedValue e
  return $ pack $ show e
instance ToMustache (Context Value -> STree -> STree) where
  toMustache f = Lambda $ (<$> askContext) . flip f
instance ToMustache (Context Value -> STree -> Text) where
  toMustache = lambdaHelper id
instance ToMustache (Context Value -> STree -> LT.Text) where
  toMustache = lambdaHelper LT.toStrict
instance ToMustache (Context Value -> STree -> String) where
  toMustache = lambdaHelper pack
lambdaHelper :: (r -> Text) -> (Context Value -> STree -> r) -> Value
lambdaHelper conv f = Lambda $ (<$> askContext) . wrapper
  where
    wrapper ::  STree -> Context Value -> STree
    wrapper lSTree c = [TextBlock $ conv $ f c lSTree]
instance ToMustache (STree -> SubM Text) where
  toMustache f = Lambda (fmap (return . TextBlock) . f)