{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE LambdaCase #-}
module Foreign.Lua.Aeson
( pushNull
) where
import Control.Monad (when)
import Data.HashMap.Lazy (HashMap)
import Data.Hashable (Hashable)
import Data.Scientific (Scientific, toRealFloat, fromFloatDigits)
import Data.Vector (Vector, fromList, toList)
import Foreign.Lua as Lua
import qualified Data.Aeson as Aeson
import qualified Data.HashMap.Lazy as HashMap
import qualified Data.Vector as Vector
instance Pushable Scientific where
push = pushnumber . toRealFloat
instance Peekable Scientific where
peek = fmap (fromFloatDigits :: Lua.Number -> Scientific) . peek
instance (Pushable a) => Pushable (Vector a) where
push = pushvector
instance (Peekable a) => Peekable (Vector a) where
peek = tovector
instance (Eq a, Hashable a, Pushable a, Pushable b)
=> Pushable (HashMap a b) where
push = pushTextHashMap
instance (Eq a, Hashable a, Peekable a, Peekable b)
=> Peekable (HashMap a b) where
peek = fmap HashMap.fromList . peekKeyValuePairs
instance Pushable Aeson.Value where
push = \case
Aeson.Object o -> push o
Aeson.Number n -> push n
Aeson.String s -> push s
Aeson.Array a -> push a
Aeson.Bool b -> push b
Aeson.Null -> pushNull
instance Peekable Aeson.Value where
peek idx =
ltype idx >>= \case
TypeBoolean -> Aeson.Bool <$> peek idx
TypeNumber -> Aeson.Number <$> peek idx
TypeString -> Aeson.String <$> peek idx
TypeTable -> do
rawgeti idx 0
isInt <- isinteger stackTop
pop 1
if isInt
then Aeson.Array <$> peek idx
else do
rawlen' <- rawlen idx
if rawlen' > 0
then Aeson.Array <$> peek idx
else do
isNull' <- isNull idx
if isNull'
then return Aeson.Null
else Aeson.Object <$> peek idx
TypeNil -> return Aeson.Null
luaType -> Lua.throwException ("Unexpected type: " ++ show luaType)
nullRegistryField :: String
nullRegistryField = "HSLUA_AESON_NULL"
pushNull :: Lua ()
pushNull = do
push nullRegistryField
rawget registryindex
uninitialized <- isnil stackTop
when uninitialized $ do
pop 1
newtable
pushvalue stackTop
setfield registryindex nullRegistryField
isNull :: StackIndex -> Lua Bool
isNull idx = do
idx' <- absindex idx
pushNull
rawequal idx' stackTop <* pop 1
pushvector :: Pushable a => Vector a -> Lua ()
pushvector v = do
pushList . toList $ v
push (fromIntegral (Vector.length v) :: Lua.Integer)
rawseti (-2) 0
tovector :: Peekable a => StackIndex -> Lua (Vector a)
tovector = fmap fromList . Lua.peekList
pushTextHashMap :: (Pushable a, Pushable b) => HashMap a b -> Lua ()
pushTextHashMap hm = do
let addValue (k, v) = push k *> push v *> rawset (-3)
newtable
mapM_ addValue (HashMap.toList hm)