module Foreign.Lua.Aeson
( registerNull
) where
#if MIN_VERSION_base(4,8,0)
#else
import Control.Applicative ((<$>), (<*>), (*>), (<*))
#endif
import Data.HashMap.Lazy (HashMap)
import Data.Hashable (Hashable)
import Data.Scientific (Scientific, toRealFloat, fromFloatDigits)
import Data.Vector (Vector, fromList, toList)
import Foreign.Lua hiding (newstate, toList)
import qualified Foreign.Lua as Lua
import qualified Data.Aeson as Aeson
import qualified Data.HashMap.Lazy as HashMap
import qualified Data.Vector as Vector
instance ToLuaStack Scientific where
push n = pushnumber (toRealFloat n)
instance FromLuaStack Scientific where
peek n = fromFloatDigits <$> (peek n :: Lua LuaNumber)
instance (ToLuaStack a) => ToLuaStack (Vector a) where
push v = pushvector v
instance (FromLuaStack a) => FromLuaStack (Vector a) where
peek i = tovector i
instance (Eq a, Hashable a, ToLuaStack a, ToLuaStack b)
=> ToLuaStack (HashMap a b) where
push h = pushTextHashMap h
instance (Eq a, Hashable a, FromLuaStack a, FromLuaStack b)
=> FromLuaStack (HashMap a b) where
peek i = HashMap.fromList <$> pairsFromTable i
instance ToLuaStack 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 -> getglobal "_NULL"
instance FromLuaStack Aeson.Value where
peek i = do
ltype' <- ltype i
case ltype' of
TypeBoolean -> Aeson.Bool <$> peek i
TypeNumber -> Aeson.Number <$> peek i
TypeString -> Aeson.String <$> peek i
TypeTable -> do
rawgeti i 0
isInt <- isnumber (1)
pop 1
if isInt
then Aeson.Array <$> peek i
else do
rawlen' <- rawlen i
if rawlen' > 0
then Aeson.Array <$> peek i
else do
isNull <- isLuaNull i
if isNull
then return Aeson.Null
else Aeson.Object <$> peek i
TypeNil -> return Aeson.Null
_ -> error $ "Unexpected type: " ++ (show ltype')
registerNull :: Lua ()
registerNull = do
createtable 0 0
setglobal "_NULL"
isLuaNull :: StackIndex -> Lua Bool
isLuaNull i = do
let i' = if i < 0 then i 1 else i
getglobal "_NULL"
rawequal i' (1) <* pop 1
pushvector :: ToLuaStack a => Vector a -> Lua ()
pushvector v = do
pushList . toList $ v
push (fromIntegral (Vector.length v) :: LuaInteger)
rawseti (2) 0
tovector :: FromLuaStack a => StackIndex -> Lua (Vector a)
tovector = fmap fromList . Lua.toList
pushTextHashMap :: (ToLuaStack a, ToLuaStack b) => HashMap a b -> Lua ()
pushTextHashMap hm = do
let xs = HashMap.toList hm
let addValue (k, v) = push k *> push v *> rawset (3)
newtable
mapM_ addValue xs