module Text.Ginger.GVal
where
import Prelude ( (.), ($), (==), (/=)
, (++), (+), (), (*), (/), div
, (>>=), return
, undefined, otherwise, id, const
, Maybe (..)
, Bool (..)
, Either (..)
, Char
, Int
, Integer
, Double
, Show, show
, Integral
, fromIntegral, floor
, not
, fst, snd
, Monad
)
import qualified Prelude
import qualified Data.List as List
import Data.Maybe ( fromMaybe, catMaybes, isJust )
import Data.Text (Text)
import Data.String (IsString, fromString)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LText
import qualified Data.List as List
import Safe (readMay, atMay)
import Data.Monoid
import Data.Scientific ( Scientific
, floatingOrInteger
, toBoundedInteger
)
import Control.Applicative
import qualified Data.Aeson as JSON
import qualified Data.HashMap.Strict as HashMap
import Data.HashMap.Strict (HashMap)
import qualified Data.Vector as Vector
import Control.Monad ( forM, mapM )
import Control.Monad.Trans (MonadTrans, lift)
import Data.Default (Default, def)
import Text.Ginger.Html
data GVal m =
GVal
{ asList :: Maybe [GVal m]
, asDictItems :: Maybe [(Text, GVal m)]
, asLookup :: Maybe (Text -> Maybe (GVal m))
, asHtml :: Html
, asText :: Text
, asBoolean :: Bool
, asNumber :: Maybe Scientific
, asFunction :: Maybe (Function m)
, length :: Maybe Int
, isNull :: Bool
}
instance Default (GVal m) where
def = GVal
{ asList = Nothing
, asDictItems = Nothing
, asLookup = Nothing
, asHtml = unsafeRawHtml ""
, asText = ""
, asBoolean = False
, asNumber = Nothing
, asFunction = Nothing
, isNull = True
, length = Nothing
}
instance Show (GVal m) where
show v
| isNull v = "null"
| isJust (asFunction v) = "<<function>>"
| isJust (asDictItems v) = "{" <> (mconcat . List.intersperse ", " $ [ show k <> ": " <> show v | (k, v) <- fromMaybe [] (asDictItems v) ]) <> "}"
| isJust (asList v) = "[" <> (mconcat . List.intersperse ", " . Prelude.map show $ fromMaybe [] (asList v)) <> "]"
| isJust (asNumber v) =
case floatingOrInteger <$> asNumber v :: Maybe (Either Double Integer) of
Just (Left x) -> show (asNumber v)
Just (Right x) -> show x
Nothing -> ""
| otherwise = show $ asText v
instance ToHtml (GVal m) where
toHtml = asHtml
type Function m = [(Maybe Text, GVal m)] -> m (GVal m)
matchFuncArgs :: [Text] -> [(Maybe Text, GVal m)] -> (HashMap Text (GVal m), [GVal m], HashMap Text (GVal m))
matchFuncArgs names args =
(matched, positional, named)
where
positionalRaw = [ v | (Nothing, v) <- args ]
namedRaw = HashMap.fromList [ (n, v) | (Just n, v) <- args ]
fromPositional = Prelude.zip names positionalRaw
numPositional = Prelude.length fromPositional
namesRemaining = Prelude.drop numPositional names
positional = Prelude.drop numPositional positionalRaw
fromNamed = catMaybes $ (List.map lookupName namesRemaining)
lookupName n = do
v <- HashMap.lookup n namedRaw
return (n, v)
matched = HashMap.fromList $ fromPositional ++ fromNamed
named = HashMap.difference namedRaw (HashMap.fromList fromNamed)
class ToGVal m a where
toGVal :: a -> GVal m
instance ToGVal m (GVal m) where
toGVal = id
instance ToGVal m v => ToGVal m (Maybe v) where
toGVal Nothing = def
toGVal (Just x) = toGVal x
instance ToGVal m v => ToGVal m [v] where
toGVal xs = helper (Prelude.map toGVal xs)
where
helper :: [GVal m] -> GVal m
helper xs =
def
{ asHtml = mconcat . Prelude.map asHtml $ xs
, asText = mconcat . Prelude.map asText $ xs
, asBoolean = not . List.null $ xs
, isNull = False
, asList = Just $ Prelude.map toGVal xs
, length = Just $ Prelude.length xs
}
instance ToGVal m v => ToGVal m (HashMap Text v) where
toGVal xs = helper (HashMap.map toGVal xs)
where
helper :: HashMap Text (GVal m) -> GVal m
helper xs =
def
{ asHtml = mconcat . Prelude.map asHtml . HashMap.elems $ xs
, asText = mconcat . Prelude.map asText . HashMap.elems $ xs
, asBoolean = not . HashMap.null $ xs
, isNull = False
, asLookup = Just (\v -> HashMap.lookup v xs)
, asDictItems = Just $ HashMap.toList xs
}
instance ToGVal m Int where
toGVal x =
def
{ asHtml = html . Text.pack . show $ x
, asText = Text.pack . show $ x
, asBoolean = x /= 0
, asNumber = Just . fromIntegral $ x
, isNull = False
}
instance ToGVal m Integer where
toGVal x =
def
{ asHtml = html . Text.pack . show $ x
, asText = Text.pack . show $ x
, asBoolean = x /= 0
, asNumber = Just . fromIntegral $ x
, isNull = False
}
instance ToGVal m Scientific where
toGVal x =
def
{ asHtml = html $ scientificToText x
, asText = scientificToText x
, asBoolean = x /= 0
, asNumber = Just x
, isNull = False
}
instance (ToGVal m a, ToGVal m b) => ToGVal m (a, b) where
toGVal (a, b) = toGVal ([ toGVal a, toGVal b ] :: [GVal m])
instance (ToGVal m a, ToGVal m b, ToGVal m c) => ToGVal m (a, b, c) where
toGVal (a, b, c) = toGVal ([ toGVal a, toGVal b, toGVal c ] :: [GVal m])
instance (ToGVal m a, ToGVal m b, ToGVal m c, ToGVal m d) => ToGVal m (a, b, c, d) where
toGVal (a, b, c, d) = toGVal ([ toGVal a, toGVal b, toGVal c, toGVal d ] :: [GVal m])
type Pair m = (Text, GVal m)
dict :: [Pair m] -> GVal m
dict = toGVal . HashMap.fromList
orderedDict :: [Pair m] -> GVal m
orderedDict xs =
def
{ asHtml = mconcat . Prelude.map asHtml . Prelude.map snd $ xs
, asText = mconcat . Prelude.map asText . Prelude.map snd $ xs
, asBoolean = not . Prelude.null $ xs
, isNull = False
, asLookup = Just (\v -> HashMap.lookup v hm)
, asDictItems = Just xs
}
where
hm = HashMap.fromList xs
(~>) :: ToGVal m a => Text -> a -> Pair m
k ~> v = (k, toGVal v)
scientificToText :: Scientific -> Text
scientificToText x =
Text.pack $ case floatingOrInteger x of
Left x -> show x
Right x -> show x
instance ToGVal m Bool where
toGVal x =
def
{ asHtml = if x then html "1" else html ""
, asText = if x then "1" else ""
, asBoolean = x
, asNumber = Just $ if x then 1 else 0
, isNull = False
}
instance IsString (GVal m) where
fromString x =
def
{ asHtml = html . Text.pack $ x
, asText = Text.pack x
, asBoolean = not $ Prelude.null x
, asNumber = readMay x
, isNull = False
, length = Just . Prelude.length $ x
}
instance ToGVal m Char where
toGVal = toGVal . Text.singleton
instance ToGVal m Text where
toGVal x =
def
{ asHtml = html x
, asText = x
, asBoolean = not $ Text.null x
, asNumber = readMay . Text.unpack $ x
, isNull = False
}
instance ToGVal m LText.Text where
toGVal x =
def
{ asHtml = html (LText.toStrict x)
, asText = LText.toStrict x
, asBoolean = not $ LText.null x
, asNumber = readMay . LText.unpack $ x
, isNull = False
}
instance ToGVal m Html where
toGVal x =
def
{ asHtml = x
, asText = htmlSource x
, asBoolean = not . Text.null . htmlSource $ x
, asNumber = readMay . Text.unpack . htmlSource $ x
, isNull = False
}
instance ToGVal m JSON.Value where
toGVal (JSON.Number n) = toGVal n
toGVal (JSON.String s) = toGVal s
toGVal (JSON.Bool b) = toGVal b
toGVal (JSON.Null) = def
toGVal (JSON.Array a) = toGVal $ Vector.toList a
toGVal (JSON.Object o) = toGVal o
fromFunction :: Function m -> GVal m
fromFunction f =
def
{ asHtml = html ""
, asText = ""
, asBoolean = True
, isNull = False
, asFunction = Just f
}
isList :: GVal m -> Bool
isList = isJust . asList
isDict :: GVal m -> Bool
isDict = isJust . asDictItems
lookupIndex :: Int -> GVal m -> Maybe (GVal m)
lookupIndex = lookupIndexMay . Just
lookupIndexMay :: Maybe Int -> GVal m -> Maybe (GVal m)
lookupIndexMay i v = do
index <- i
items <- asList v
atMay items index
lookupKey :: Text -> GVal m -> Maybe (GVal m)
lookupKey k v = do
lf <- asLookup v
lf k
lookupLoose :: GVal m -> GVal m -> Maybe (GVal m)
lookupLoose k v =
lookupKey (asText k) v <|> lookupIndexMay (floor <$> asNumber k) v
keys :: GVal m -> Maybe [Text]
keys v = Prelude.map fst <$> asDictItems v
toNumber :: GVal m -> Maybe Scientific
toNumber = asNumber
toInt :: GVal m -> Maybe Int
toInt x = toNumber x >>= toBoundedInteger
toBoolean :: GVal m -> Bool
toBoolean = asBoolean
toFunction :: GVal m -> Maybe (Function m)
toFunction = asFunction