{-# LANGUAGE OverloadedStrings #-}
module Foreign.Lua.Module.Text
( pushModule
, pushModuleText
, preloadTextModule
)where
import Control.Applicative ((<$>))
import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Maybe (fromMaybe)
import Foreign.Lua (NumResults, Lua, Peekable, Pushable, ToHaskellFunction)
import qualified Foreign.Lua as Lua
import qualified Data.Text as T
pushModule :: Lua NumResults
pushModule = do
Lua.newtable
Lua.addfunction "lower" (return . T.toLower :: Text -> Lua Text)
Lua.addfunction "upper" (return . T.toUpper :: Text -> Lua Text)
Lua.addfunction "reverse" (return . T.reverse :: Text -> Lua Text)
Lua.addfunction "len" (return . fromIntegral . T.length :: Text -> Lua Lua.Integer)
Lua.addfunction "sub" sub
return 1
pushModuleText :: Lua NumResults
pushModuleText = pushModule
preloadTextModule :: String -> Lua ()
preloadTextModule = flip Lua.preloadhs pushModule
sub :: Text -> Lua.Integer -> Lua.Optional Lua.Integer -> Lua Text
sub s i j =
let i' = fromIntegral i
j' = fromIntegral . fromMaybe (-1) $ Lua.fromOptional j
fromStart = if i' >= 0 then i' - 1 else T.length s + i'
fromEnd = if j' < 0 then -j' - 1 else T.length s - j'
in return . T.dropEnd fromEnd . T.drop fromStart $ s