{-# LANGUAGE OverloadedStrings #-}
module Pencil.Env.Internal where
import qualified Pencil.Parser as P
import Data.Text.Encoding (encodeUtf8)
import qualified Data.HashMap.Strict as H
import qualified Data.Maybe as M
import qualified Data.Text as T
import qualified Data.Time.Clock as TC
import qualified Data.Time.Format as TF
import qualified Data.Vector as V
import qualified Data.Yaml as A
data Value =
VNull
| VText T.Text
| VBool Bool
| VDateTime TC.UTCTime
| VArray [Value]
| VEnvList [Env]
| VNodes [P.PNode]
deriving (Eq, Show)
type Env = H.HashMap T.Text Value
toValue :: A.Value -> Maybe Value
toValue A.Null = Just VNull
toValue (A.Bool b) = Just $ VBool b
toValue (A.String s) =
case toDateTime (T.unpack s) of
Nothing -> Just $ VText s
Just dt -> Just $ VDateTime dt
toValue (A.Array arr) =
Just $ VArray (V.toList (V.mapMaybe toValue arr))
toValue _ = Nothing
toDateTime :: String -> Maybe TC.UTCTime
toDateTime s =
case parseIso8601 Nothing s of
Nothing -> parseIso8601 (Just "%H:%M:%S") s
Just dt -> Just dt
parseIso8601 :: Maybe String -> String -> Maybe TC.UTCTime
parseIso8601 f = TF.parseTimeM True TF.defaultTimeLocale (TF.iso8601DateFormat f)
getNodes :: Env -> [P.PNode]
getNodes env =
case H.lookup "this.nodes" env of
Just (VNodes nodes) -> nodes
_ -> []
findEnv :: [P.PNode] -> Env
findEnv nodes =
aesonToEnv $ M.fromMaybe H.empty (P.findPreambleText nodes >>= (A.decodeThrow . encodeUtf8 . T.strip))
aesonToEnv :: A.Object -> Env
aesonToEnv = H.foldlWithKey' maybeInsertIntoEnv H.empty
maybeInsertIntoEnv :: Env -> T.Text -> A.Value -> Env
maybeInsertIntoEnv env k v =
case toValue v of
Nothing -> env
Just d -> H.insert k d env
getContent :: Env -> Maybe T.Text
getContent env =
case H.lookup "this.content" env of
Just (VText content) -> return content
_ -> Nothing
toText :: Value -> T.Text
toText VNull = "null"
toText (VText t) = t
toText (VArray arr) = T.unwords $ map toText arr
toText (VBool b) = if b then "true" else "false"
toText (VEnvList envs) = T.unwords $ map (T.unwords . map toText . H.elems) envs
toText (VDateTime dt) =
T.pack $ TF.formatTime TF.defaultTimeLocale "%B %e, %Y" dt
toText (VNodes nodes) = P.renderNodes nodes
toTextRss :: Value -> T.Text
toTextRss (VDateTime dt) = T.pack $ TF.formatTime TF.defaultTimeLocale rfc822DateFormat dt
toTextRss v = toText v
rfc822DateFormat :: String
rfc822DateFormat = "%a, %d %b %Y %H:%M:%S %z"