{-# LANGUAGE OverloadedStrings #-}
module Pencil.Internal.Env where
import qualified Data.HashMap.Strict as H
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]
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
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
toDateTime :: String -> Maybe TC.UTCTime
toDateTime s =
case maybeParseIso8601 Nothing s of
Nothing -> maybeParseIso8601 (Just "%H:%M:%S") s
Just dt -> Just dt
maybeParseIso8601 :: Maybe String -> String -> Maybe TC.UTCTime
maybeParseIso8601 f = TF.parseTimeM True TF.defaultTimeLocale (TF.iso8601DateFormat f)
maybeOrdering :: (Value -> Value -> Ordering)
-> Maybe Value -> Maybe Value -> Ordering
maybeOrdering _ Nothing Nothing = EQ
maybeOrdering _ (Just _) Nothing = GT
maybeOrdering _ Nothing (Just _) = LT
maybeOrdering o (Just a) (Just b) = o a b
dateOrdering :: Value -> Value -> Ordering
dateOrdering (VDateTime a) (VDateTime b) = compare b a
dateOrdering _ _ = EQ
arrayContainsString :: T.Text -> Value -> Bool
arrayContainsString t (VArray arr) =
any (\d -> case d of
VText t' -> t == t'
_ -> False)
arr
arrayContainsString _ _ = False