module Foreign.Lua.Push
( Pusher
, pushBool
, pushIntegral
, pushRealFloat
, pushByteString
, pushLazyByteString
, pushString
, pushText
, pushList
, pushMap
, pushSet
) where
import Control.Monad (zipWithM_)
import Data.ByteString (ByteString)
import Data.Map (Map, toList)
import Data.Set (Set)
import Foreign.Lua.Core as Lua
import Numeric (showGFloat)
import qualified Data.Text as T
import qualified Data.ByteString.Lazy as BL
import qualified Foreign.Lua.Utf8 as Utf8
type Pusher a = a -> Lua ()
pushBool :: Pusher Bool
pushBool = pushboolean
pushText :: Pusher T.Text
pushText = pushstring . Utf8.fromText
pushByteString :: Pusher ByteString
pushByteString = pushstring
pushLazyByteString :: Pusher BL.ByteString
pushLazyByteString = pushstring . BL.toStrict
pushString :: String -> Lua ()
pushString = pushstring . Utf8.fromString
pushIntegral :: (Integral a, Show a) => a -> Lua ()
pushIntegral i =
let maxInt = fromIntegral (maxBound :: Lua.Integer)
minInt = fromIntegral (minBound :: Lua.Integer)
i' = fromIntegral i :: Prelude.Integer
in if i' >= minInt && i' <= maxInt
then pushinteger $ fromIntegral i
else pushString $ show i
pushRealFloat :: RealFloat a => a -> Lua ()
pushRealFloat f =
let
number = 0 :: Lua.Number
realFloatFitsInNumber = floatRadix number == floatRadix f
&& floatDigits number == floatDigits f
&& floatRange number == floatRange f
in if realFloatFitsInNumber
then pushnumber (realToFrac f :: Lua.Number)
else pushString (showGFloat Nothing f "")
pushKeyValuePairs :: Pusher a -> Pusher b -> Pusher [(a,b)]
pushKeyValuePairs pushKey pushValue m = do
let addValue (k, v) = pushKey k *> pushValue v *> rawset (-3)
newtable
mapM_ addValue m
pushList :: Pusher a -> [a] -> Lua ()
pushList push xs = do
let setField i x = push x *> rawseti (-2) i
newtable
zipWithM_ setField [1..] xs
pushMap :: Pusher a -> Pusher b -> Pusher (Map a b)
pushMap pushKey pushValue m = pushKeyValuePairs pushKey pushValue $ toList m
pushSet :: Pusher a -> Pusher (Set a)
pushSet pushElement set = do
let addItem item = pushElement item *> pushboolean True *> rawset (-3)
newtable
mapM_ addItem set