hslua-2.3.1: Bindings to Lua, an embeddable scripting language
Copyright© 2007–2012 Gracjan Polak;
© 2012–2016 Ömer Sinan Ağacan;
© 2017-2024 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb@hslua.org>
Stabilitybeta
Portabilitynon-portable (depends on GHC)
Safe HaskellNone
LanguageHaskell2010

HsLua

Description

Functions and utilities enabling the seamless integration of a Lua interpreter into a Haskell project.

This module combines and re-exports the functionality of the HsLua framework. Basic access to the Lua API is provided by Core from Hackage package lua.

Synopsis

Core functionality

type Lua a = LuaE Exception a #

newtype LuaE e a #

Constructors

Lua 

Fields

Instances

Instances details
LuaError e => Exposable e (HaskellFunction e) 
Instance details

Defined in HsLua.Class.Exposable

MonadReader LuaEnvironment (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

ask :: LuaE e LuaEnvironment

local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a

reader :: (LuaEnvironment -> a) -> LuaE e a

(LuaError e, Pushable a) => Exposable e (LuaE e a) 
Instance details

Defined in HsLua.Class.Exposable

MonadIO (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

liftIO :: IO a -> LuaE e a #

Applicative (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

pure :: a -> LuaE e a

(<*>) :: LuaE e (a -> b) -> LuaE e a -> LuaE e b

liftA2 :: (a -> b -> c) -> LuaE e a -> LuaE e b -> LuaE e c

(*>) :: LuaE e a -> LuaE e b -> LuaE e b

(<*) :: LuaE e a -> LuaE e b -> LuaE e a

Functor (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

fmap :: (a -> b) -> LuaE e a -> LuaE e b

(<$) :: a -> LuaE e b -> LuaE e a

Monad (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

(>>=) :: LuaE e a -> (a -> LuaE e b) -> LuaE e b

(>>) :: LuaE e a -> LuaE e b -> LuaE e b

return :: a -> LuaE e a

MonadCatch (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

catch :: (HasCallStack, Exception e0) => LuaE e a -> (e0 -> LuaE e a) -> LuaE e a

MonadMask (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

mask :: HasCallStack => ((forall a. LuaE e a -> LuaE e a) -> LuaE e b) -> LuaE e b

uninterruptibleMask :: HasCallStack => ((forall a. LuaE e a -> LuaE e a) -> LuaE e b) -> LuaE e b

generalBracket :: HasCallStack => LuaE e a -> (a -> ExitCase b -> LuaE e c) -> (a -> LuaE e b) -> LuaE e (b, c)

MonadThrow (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

throwM :: (HasCallStack, Exception e0) => e0 -> LuaE e a

(LuaError e, Peekable a) => Invokable (LuaE e a) 
Instance details

Defined in HsLua.Class.Invokable

Methods

addArg :: Name -> (forall e0. LuaError e0 => LuaE e0 ()) -> NumArgs -> LuaE e a #

concat :: LuaError e => NumArgs -> LuaE e () #

class Exception e => LuaError e where #

Methods

popException :: LuaE e e #

pushException :: e -> LuaE e () #

luaException :: String -> e #

Instances

Instances details
LuaError Exception 
Instance details

Defined in HsLua.Core.Error

newtype Name #

Constructors

Name 

Fields

Instances

Instances details
IsString Name 
Instance details

Defined in HsLua.Core.Types

Methods

fromString :: String -> Name

Semigroup Name 
Instance details

Defined in HsLua.Core.Types

Methods

(<>) :: Name -> Name -> Name

sconcat :: NonEmpty Name -> Name

stimes :: Integral b => b -> Name -> Name

Show Name 
Instance details

Defined in HsLua.Core.Types

Methods

showsPrec :: Int -> Name -> ShowS

show :: Name -> String

showList :: [Name] -> ShowS

Eq Name 
Instance details

Defined in HsLua.Core.Types

Methods

(==) :: Name -> Name -> Bool

(/=) :: Name -> Name -> Bool

Ord Name 
Instance details

Defined in HsLua.Core.Types

Methods

compare :: Name -> Name -> Ordering

(<) :: Name -> Name -> Bool

(<=) :: Name -> Name -> Bool

(>) :: Name -> Name -> Bool

(>=) :: Name -> Name -> Bool

max :: Name -> Name -> Name

min :: Name -> Name -> Name

nth :: CInt -> StackIndex #

pop :: Int -> LuaE e () #

remove :: StackIndex -> LuaE e () #

setfield :: LuaError e => StackIndex -> Name -> LuaE e () #

setglobal :: LuaError e => Name -> LuaE e () #

newtype Integer #

Constructors

Integer Int64 

Instances

Instances details
Bounded Integer 
Instance details

Defined in Lua.Types

Enum Integer 
Instance details

Defined in Lua.Types

Num Integer 
Instance details

Defined in Lua.Types

Read Integer 
Instance details

Defined in Lua.Types

Methods

readsPrec :: Int -> ReadS Integer

readList :: ReadS [Integer]

readPrec :: ReadPrec Integer

readListPrec :: ReadPrec [Integer]

Integral Integer 
Instance details

Defined in Lua.Types

Real Integer 
Instance details

Defined in Lua.Types

Methods

toRational :: Integer -> Rational

Show Integer 
Instance details

Defined in Lua.Types

Methods

showsPrec :: Int -> Integer -> ShowS

show :: Integer -> String

showList :: [Integer] -> ShowS

Eq Integer 
Instance details

Defined in Lua.Types

Methods

(==) :: Integer -> Integer -> Bool

(/=) :: Integer -> Integer -> Bool

Ord Integer 
Instance details

Defined in Lua.Types

Methods

compare :: Integer -> Integer -> Ordering

(<) :: Integer -> Integer -> Bool

(<=) :: Integer -> Integer -> Bool

(>) :: Integer -> Integer -> Bool

(>=) :: Integer -> Integer -> Bool

max :: Integer -> Integer -> Integer

min :: Integer -> Integer -> Integer

Peekable Integer 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Integer #

Pushable Integer 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Integer -> LuaE e () #

data Type #

Instances

Instances details
Bounded Type 
Instance details

Defined in HsLua.Core.Types

Enum Type 
Instance details

Defined in HsLua.Core.Types

Methods

succ :: Type -> Type

pred :: Type -> Type

toEnum :: Int -> Type

fromEnum :: Type -> Int

enumFrom :: Type -> [Type]

enumFromThen :: Type -> Type -> [Type]

enumFromTo :: Type -> Type -> [Type]

enumFromThenTo :: Type -> Type -> Type -> [Type]

Read Type 
Instance details

Defined in HsLua.Core.Types

Methods

readsPrec :: Int -> ReadS Type

readList :: ReadS [Type]

readPrec :: ReadPrec Type

readListPrec :: ReadPrec [Type]

Show Type 
Instance details

Defined in HsLua.Core.Types

Methods

showsPrec :: Int -> Type -> ShowS

show :: Type -> String

showList :: [Type] -> ShowS

Eq Type 
Instance details

Defined in HsLua.Core.Types

Methods

(==) :: Type -> Type -> Bool

(/=) :: Type -> Type -> Bool

Ord Type 
Instance details

Defined in HsLua.Core.Types

Methods

compare :: Type -> Type -> Ordering

(<) :: Type -> Type -> Bool

(<=) :: Type -> Type -> Bool

(>) :: Type -> Type -> Bool

(>=) :: Type -> Type -> Bool

max :: Type -> Type -> Type

min :: Type -> Type -> Type

insert :: StackIndex -> LuaE e () #

checkstack' :: LuaError e => Int -> String -> LuaE e () #

dofile :: Maybe FilePath -> LuaE e Status #

dostring :: ByteString -> LuaE e Status #

getsubtable :: LuaError e => StackIndex -> Name -> LuaE e Bool #

loadbuffer :: ByteString -> Name -> LuaE e Status #

loadfile :: Maybe FilePath -> LuaE e Status #

loadstring :: ByteString -> LuaE e Status #

newmetatable :: Name -> LuaE e Bool #

requiref :: LuaError e => Name -> CFunction -> Bool -> LuaE e () #

tostring' :: LuaError e => StackIndex -> LuaE e ByteString #

traceback :: State -> Maybe ByteString -> Int -> LuaE e () #

where' :: Int -> LuaE e () #

getupvalue :: StackIndex -> Int -> LuaE e (Maybe Name) #

setupvalue :: StackIndex -> Int -> LuaE e (Maybe Name) #

newtype Exception #

Constructors

Exception 

Fields

Instances

Instances details
Exception Exception 
Instance details

Defined in HsLua.Core.Error

Methods

toException :: Exception -> SomeException

fromException :: SomeException -> Maybe Exception

displayException :: Exception -> String

Show Exception 
Instance details

Defined in HsLua.Core.Error

Methods

showsPrec :: Int -> Exception -> ShowS

show :: Exception -> String

showList :: [Exception] -> ShowS

Eq Exception 
Instance details

Defined in HsLua.Core.Error

Methods

(==) :: Exception -> Exception -> Bool

(/=) :: Exception -> Exception -> Bool

LuaError Exception 
Instance details

Defined in HsLua.Core.Error

changeErrorType :: forall old new a. LuaE old a -> LuaE new a #

failLua :: LuaError e => String -> LuaE e a #

popErrorMessage :: State -> IO ByteString #

pushTypeMismatchError :: ByteString -> StackIndex -> LuaE e () #

throwTypeMismatchError :: LuaError e => ByteString -> StackIndex -> LuaE e a #

try :: Exception e => LuaE e a -> LuaE e (Either e a) #

preloadhs :: LuaError e => Name -> LuaE e NumResults -> LuaE e () #

requirehs :: LuaError e => Name -> (Name -> LuaE e ()) -> LuaE e () #

call :: LuaError e => NumArgs -> NumResults -> LuaE e () #

checkstack :: Int -> LuaE e Bool #

close :: State -> IO () #

createtable :: Int -> Int -> LuaE e () #

equal :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool #

gc :: GCControl -> LuaE e Int #

isboolean :: StackIndex -> LuaE e Bool #

isinteger :: StackIndex -> LuaE e Bool #

isnil :: StackIndex -> LuaE e Bool #

isnone :: StackIndex -> LuaE e Bool #

isnumber :: StackIndex -> LuaE e Bool #

isstring :: StackIndex -> LuaE e Bool #

istable :: StackIndex -> LuaE e Bool #

isthread :: StackIndex -> LuaE e Bool #

load :: Reader -> Ptr () -> Name -> LuaE e Status #

newtable :: LuaE e () #

newuserdatauv :: Int -> Int -> LuaE e (Ptr ()) #

next :: LuaError e => StackIndex -> LuaE e Bool #

openbase :: LuaError e => LuaE e () #

opendebug :: LuaError e => LuaE e () #

openio :: LuaError e => LuaE e () #

openlibs :: LuaE e () #

openmath :: LuaError e => LuaE e () #

openos :: LuaError e => LuaE e () #

openpackage :: LuaError e => LuaE e () #

openstring :: LuaError e => LuaE e () #

opentable :: LuaError e => LuaE e () #

pushboolean :: Bool -> LuaE e () #

pushlightuserdata :: Ptr a -> LuaE e () #

pushnil :: LuaE e () #

pushnumber :: Number -> LuaE e () #

pushstring :: ByteString -> LuaE e () #

pushthread :: LuaE e Bool #

rawlen :: StackIndex -> LuaE e Int #

rawset :: LuaError e => StackIndex -> LuaE e () #

register :: LuaError e => Name -> CFunction -> LuaE e () #

rotate :: StackIndex -> Int -> LuaE e () #

setiuservalue :: StackIndex -> Int -> LuaE e Bool #

settop :: StackIndex -> LuaE e () #

setwarnf :: WarnFunction -> Ptr () -> LuaE e () #

toboolean :: StackIndex -> LuaE e Bool #

tonumber :: StackIndex -> LuaE e (Maybe Number) #

topointer :: StackIndex -> LuaE e (Ptr ()) #

tostring :: StackIndex -> LuaE e (Maybe ByteString) #

tothread :: StackIndex -> LuaE e (Maybe State) #

touserdata :: StackIndex -> LuaE e (Maybe (Ptr a)) #

typename :: Type -> LuaE e ByteString #

run :: LuaE e a -> IO a #

runEither :: Exception e => LuaE e a -> IO (Either e a) #

dofileTrace :: Maybe FilePath -> LuaE e Status #

dostringTrace :: ByteString -> LuaE e Status #

data Status #

Instances

Instances details
Show Status 
Instance details

Defined in HsLua.Core.Types

Methods

showsPrec :: Int -> Status -> ShowS

show :: Status -> String

showList :: [Status] -> ShowS

Eq Status 
Instance details

Defined in HsLua.Core.Types

Methods

(==) :: Status -> Status -> Bool

(/=) :: Status -> Status -> Bool

data GCControl #

Constructors

GCStop 
GCRestart 
GCCollect 
GCCount 
GCCountb 
GCStep CInt 
GCInc CInt CInt CInt 
GCGen CInt CInt 
GCIsRunning 

Instances

Instances details
Show GCControl 
Instance details

Defined in HsLua.Core.Types

Methods

showsPrec :: Int -> GCControl -> ShowS

show :: GCControl -> String

showList :: [GCControl] -> ShowS

Eq GCControl 
Instance details

Defined in HsLua.Core.Types

Methods

(==) :: GCControl -> GCControl -> Bool

(/=) :: GCControl -> GCControl -> Bool

Ord GCControl 
Instance details

Defined in HsLua.Core.Types

Methods

compare :: GCControl -> GCControl -> Ordering

(<) :: GCControl -> GCControl -> Bool

(<=) :: GCControl -> GCControl -> Bool

(>) :: GCControl -> GCControl -> Bool

(>=) :: GCControl -> GCControl -> Bool

max :: GCControl -> GCControl -> GCControl

min :: GCControl -> GCControl -> GCControl

newtype LuaEnvironment #

Constructors

LuaEnvironment 

Fields

Instances

Instances details
MonadReader LuaEnvironment (LuaE e) 
Instance details

Defined in HsLua.Core.Types

Methods

ask :: LuaE e LuaEnvironment

local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a

reader :: (LuaEnvironment -> a) -> LuaE e a

noref :: Int #

refnil :: Int #

runWith :: State -> LuaE e a -> IO a #

unsafeRunWith :: State -> LuaE e a -> IO a #

fromuserdata :: forall a e. StackIndex -> Name -> LuaE e (Maybe a) #

newhsuserdatauv :: a -> Int -> LuaE e () #

newudmetatable :: Name -> LuaE e Bool #

putuserdata :: StackIndex -> Name -> a -> LuaE e Bool #

setwarnf' :: LuaError e => (ByteString -> LuaE e ()) -> LuaE e () #

nthTop :: CInt -> StackIndex #

liftIO :: MonadIO m => IO a -> m a #

data Reference #

Constructors

Reference CInt 
RefNil 

Instances

Instances details
Show Reference 
Instance details

Defined in Lua.Auxiliary

Methods

showsPrec :: Int -> Reference -> ShowS

show :: Reference -> String

showList :: [Reference] -> ShowS

Eq Reference 
Instance details

Defined in Lua.Auxiliary

Methods

(==) :: Reference -> Reference -> Bool

(/=) :: Reference -> Reference -> Bool

type CFunction = FunPtr PreCFunction #

newtype NumArgs #

Constructors

NumArgs 

Fields

Instances

Instances details
Num NumArgs 
Instance details

Defined in Lua.Types

Show NumArgs 
Instance details

Defined in Lua.Types

Methods

showsPrec :: Int -> NumArgs -> ShowS

show :: NumArgs -> String

showList :: [NumArgs] -> ShowS

Eq NumArgs 
Instance details

Defined in Lua.Types

Methods

(==) :: NumArgs -> NumArgs -> Bool

(/=) :: NumArgs -> NumArgs -> Bool

Ord NumArgs 
Instance details

Defined in Lua.Types

Methods

compare :: NumArgs -> NumArgs -> Ordering

(<) :: NumArgs -> NumArgs -> Bool

(<=) :: NumArgs -> NumArgs -> Bool

(>) :: NumArgs -> NumArgs -> Bool

(>=) :: NumArgs -> NumArgs -> Bool

max :: NumArgs -> NumArgs -> NumArgs

min :: NumArgs -> NumArgs -> NumArgs

newtype NumResults #

Constructors

NumResults 

Fields

Instances

Instances details
Num NumResults 
Instance details

Defined in Lua.Types

Show NumResults 
Instance details

Defined in Lua.Types

Methods

showsPrec :: Int -> NumResults -> ShowS

show :: NumResults -> String

showList :: [NumResults] -> ShowS

Eq NumResults 
Instance details

Defined in Lua.Types

Methods

(==) :: NumResults -> NumResults -> Bool

(/=) :: NumResults -> NumResults -> Bool

Ord NumResults 
Instance details

Defined in Lua.Types

Peekable CFunction 
Instance details

Defined in HsLua.Class.Peekable

Pushable CFunction 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => CFunction -> LuaE e () #

LuaError e => Exposable e (HaskellFunction e) 
Instance details

Defined in HsLua.Class.Exposable

newtype Number #

Constructors

Number Double 

Instances

Instances details
Floating Number 
Instance details

Defined in Lua.Types

RealFloat Number 
Instance details

Defined in Lua.Types

Methods

floatRadix :: Number -> Integer

floatDigits :: Number -> Int

floatRange :: Number -> (Int, Int)

decodeFloat :: Number -> (Integer, Int)

encodeFloat :: Integer -> Int -> Number

exponent :: Number -> Int

significand :: Number -> Number

scaleFloat :: Int -> Number -> Number

isNaN :: Number -> Bool

isInfinite :: Number -> Bool

isDenormalized :: Number -> Bool

isNegativeZero :: Number -> Bool

isIEEE :: Number -> Bool

atan2 :: Number -> Number -> Number

Num Number 
Instance details

Defined in Lua.Types

Read Number 
Instance details

Defined in Lua.Types

Methods

readsPrec :: Int -> ReadS Number

readList :: ReadS [Number]

readPrec :: ReadPrec Number

readListPrec :: ReadPrec [Number]

Fractional Number 
Instance details

Defined in Lua.Types

Methods

(/) :: Number -> Number -> Number

recip :: Number -> Number

fromRational :: Rational -> Number

Real Number 
Instance details

Defined in Lua.Types

Methods

toRational :: Number -> Rational

RealFrac Number 
Instance details

Defined in Lua.Types

Methods

properFraction :: Integral b => Number -> (b, Number)

truncate :: Integral b => Number -> b

round :: Integral b => Number -> b

ceiling :: Integral b => Number -> b

floor :: Integral b => Number -> b

Show Number 
Instance details

Defined in Lua.Types

Methods

showsPrec :: Int -> Number -> ShowS

show :: Number -> String

showList :: [Number] -> ShowS

Eq Number 
Instance details

Defined in Lua.Types

Methods

(==) :: Number -> Number -> Bool

(/=) :: Number -> Number -> Bool

Ord Number 
Instance details

Defined in Lua.Types

Methods

compare :: Number -> Number -> Ordering

(<) :: Number -> Number -> Bool

(<=) :: Number -> Number -> Bool

(>) :: Number -> Number -> Bool

(>=) :: Number -> Number -> Bool

max :: Number -> Number -> Number

min :: Number -> Number -> Number

Peekable Number 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Number #

Pushable Number 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Number -> LuaE e () #

newtype StackIndex #

Constructors

StackIndex 

Fields

Instances

Instances details
Enum StackIndex 
Instance details

Defined in Lua.Types

Num StackIndex 
Instance details

Defined in Lua.Types

Show StackIndex 
Instance details

Defined in Lua.Types

Methods

showsPrec :: Int -> StackIndex -> ShowS

show :: StackIndex -> String

showList :: [StackIndex] -> ShowS

Eq StackIndex 
Instance details

Defined in Lua.Types

Methods

(==) :: StackIndex -> StackIndex -> Bool

(/=) :: StackIndex -> StackIndex -> Bool

Ord StackIndex 
Instance details

Defined in Lua.Types

newtype State #

Constructors

State (Ptr ()) 

Instances

Instances details
Generic State 
Instance details

Defined in Lua.Types

Associated Types

type Rep State 
Instance details

Defined in Lua.Types

type Rep State = D1 ('MetaData "State" "Lua.Types" "lua-2.3.3-I17iNMvL686B2bOl7VRsn7" 'True) (C1 ('MetaCons "State" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr ()))))

Methods

from :: State -> Rep State x

to :: Rep State x -> State

Eq State 
Instance details

Defined in Lua.Types

Methods

(==) :: State -> State -> Bool

(/=) :: State -> State -> Bool

Peekable CFunction 
Instance details

Defined in HsLua.Class.Peekable

Peekable State 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e State #

Pushable CFunction 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => CFunction -> LuaE e () #

type Rep State 
Instance details

Defined in Lua.Types

type Rep State = D1 ('MetaData "State" "Lua.Types" "lua-2.3.3-I17iNMvL686B2bOl7VRsn7" 'True) (C1 ('MetaCons "State" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr ()))))

Marshalling

pushList :: LuaError e => Pusher e a -> [a] -> LuaE e () #

liftLua :: LuaE e a -> Peek e a #

data Result a #

Constructors

Success !a 
Failure ByteString [Name] 

Instances

Instances details
MonadFail Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fail :: String -> Result a

Foldable Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fold :: Monoid m => Result m -> m

foldMap :: Monoid m => (a -> m) -> Result a -> m

foldMap' :: Monoid m => (a -> m) -> Result a -> m

foldr :: (a -> b -> b) -> b -> Result a -> b

foldr' :: (a -> b -> b) -> b -> Result a -> b

foldl :: (b -> a -> b) -> b -> Result a -> b

foldl' :: (b -> a -> b) -> b -> Result a -> b

foldr1 :: (a -> a -> a) -> Result a -> a

foldl1 :: (a -> a -> a) -> Result a -> a

toList :: Result a -> [a]

null :: Result a -> Bool

length :: Result a -> Int

elem :: Eq a => a -> Result a -> Bool

maximum :: Ord a => Result a -> a

minimum :: Ord a => Result a -> a

sum :: Num a => Result a -> a

product :: Num a => Result a -> a

Traversable Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b)

sequenceA :: Applicative f => Result (f a) -> f (Result a)

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b)

sequence :: Monad m => Result (m a) -> m (Result a)

Alternative Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

empty :: Result a

(<|>) :: Result a -> Result a -> Result a

some :: Result a -> Result [a]

many :: Result a -> Result [a]

Applicative Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

pure :: a -> Result a

(<*>) :: Result (a -> b) -> Result a -> Result b

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c

(*>) :: Result a -> Result b -> Result b

(<*) :: Result a -> Result b -> Result a

Functor Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fmap :: (a -> b) -> Result a -> Result b

(<$) :: a -> Result b -> Result a

Monad Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b

(>>) :: Result a -> Result b -> Result b

return :: a -> Result a

MonadPlus Result 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

mzero :: Result a

mplus :: Result a -> Result a -> Result a

Show a => Show (Result a) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

showsPrec :: Int -> Result a -> ShowS

show :: Result a -> String

showList :: [Result a] -> ShowS

Eq a => Eq (Result a) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

(==) :: Result a -> Result a -> Bool

(/=) :: Result a -> Result a -> Bool

type Peeker e a = StackIndex -> Peek e a #

type Pusher e a = a -> LuaE e () #

newtype Peek e a #

Constructors

Peek 

Fields

Instances

Instances details
(LuaError e, Pushable a) => Exposable e (Peek e a) 
Instance details

Defined in HsLua.Class.Exposable

MonadFail (Peek e) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fail :: String -> Peek e a

Alternative (Peek e) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

empty :: Peek e a

(<|>) :: Peek e a -> Peek e a -> Peek e a

some :: Peek e a -> Peek e [a]

many :: Peek e a -> Peek e [a]

Applicative (Peek e) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

pure :: a -> Peek e a

(<*>) :: Peek e (a -> b) -> Peek e a -> Peek e b

liftA2 :: (a -> b -> c) -> Peek e a -> Peek e b -> Peek e c

(*>) :: Peek e a -> Peek e b -> Peek e b

(<*) :: Peek e a -> Peek e b -> Peek e a

Functor (Peek e) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fmap :: (a -> b) -> Peek e a -> Peek e b

(<$) :: a -> Peek e b -> Peek e a

Monad (Peek e) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

(>>=) :: Peek e a -> (a -> Peek e b) -> Peek e b

(>>) :: Peek e a -> Peek e b -> Peek e b

return :: a -> Peek e a

MonadPlus (Peek e) 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

mzero :: Peek e a

mplus :: Peek e a -> Peek e a -> Peek e a

peekList :: forall a e. LuaError e => Peeker e a -> Peeker e [a] #

pushLazyByteString :: Pusher e ByteString #

pushRealFloat :: RealFloat a => a -> LuaE e () #

pushString :: String -> LuaE e () #

pushText :: Pusher e Text #

cleanup :: Peek e a -> Peek e a #

failPeek :: forall a e. ByteString -> Peek e a #

failure :: ByteString -> Result a #

force :: LuaError e => Result a -> LuaE e a #

forcePeek :: LuaError e => Peek e a -> LuaE e a #

lastly :: Peek e a -> LuaE e b -> Peek e a #

resultToEither :: Result a -> Either String a #

retrieving :: Name -> Peek e a -> Peek e a #

runPeeker :: Peeker e a -> StackIndex -> LuaE e (Result a) #

withContext :: Name -> Peek e a -> Peek e a #

choice :: LuaError e => [Peeker e a] -> Peeker e a #

peekBool :: Peeker e Bool #

peekByteString :: Peeker e ByteString #

peekFieldRaw :: LuaError e => Peeker e a -> Name -> Peeker e a #

peekIntegral :: (Integral a, Read a) => Peeker e a #

peekKeyValuePairs :: LuaError e => Peeker e a -> Peeker e b -> Peeker e [(a, b)] #

peekLazyByteString :: Peeker e ByteString #

peekMap :: (LuaError e, Ord a) => Peeker e a -> Peeker e b -> Peeker e (Map a b) #

peekNil :: Peeker e () #

peekNilOr :: Alternative m => Peeker e a -> Peeker e (m a) #

peekNoneOr :: Alternative m => Peeker e a -> Peeker e (m a) #

peekNoneOrNilOr :: Alternative m => Peeker e a -> Peeker e (m a) #

peekPair :: LuaError e => Peeker e a -> Peeker e b -> Peeker e (a, b) #

peekRead :: Read a => Peeker e a #

peekRealFloat :: (RealFloat a, Read a) => Peeker e a #

peekSet :: (LuaError e, Ord a) => Peeker e a -> Peeker e (Set a) #

peekString :: Peeker e String #

peekStringy :: IsString a => Peeker e a #

peekText :: Peeker e Text #

peekTriple :: LuaError e => Peeker e a -> Peeker e b -> Peeker e c -> Peeker e (a, b, c) #

reportValueOnFailure :: Name -> (StackIndex -> LuaE e (Maybe a)) -> Peeker e a #

typeChecked :: Name -> (StackIndex -> LuaE e Bool) -> Peeker e a -> Peeker e a #

typeMismatchMessage :: Name -> StackIndex -> Peek e ByteString #

pushAsTable :: LuaError e => [(Name, a -> LuaE e ())] -> a -> LuaE e () #

pushBool :: Pusher e Bool #

pushByteString :: Pusher e ByteString #

pushIntegral :: (Integral a, Show a) => a -> LuaE e () #

pushKeyValuePairs :: LuaError e => Pusher e a -> Pusher e b -> Pusher e [(a, b)] #

pushMap :: LuaError e => Pusher e a -> Pusher e b -> Pusher e (Map a b) #

pushName :: Name -> LuaE e () #

pushNonEmpty :: LuaError e => Pusher e a -> NonEmpty a -> LuaE e () #

pushPair :: LuaError e => Pusher e a -> Pusher e b -> (a, b) -> LuaE e () #

pushSet :: LuaError e => Pusher e a -> Pusher e (Set a) #

pushTriple :: LuaError e => Pusher e a -> Pusher e b -> Pusher e c -> (a, b, c) -> LuaE e () #

pushIterator :: forall a e. LuaError e => (a -> LuaE e NumResults) -> [a] -> LuaE e NumResults #

Module, data, and function packaging

data Operation #

Instances

Instances details
Show Operation 
Instance details

Defined in HsLua.ObjectOrientation.Operation

Methods

showsPrec :: Int -> Operation -> ShowS

show :: Operation -> String

showList :: [Operation] -> ShowS

Eq Operation 
Instance details

Defined in HsLua.ObjectOrientation.Operation

Methods

(==) :: Operation -> Operation -> Bool

(/=) :: Operation -> Operation -> Bool

Ord Operation 
Instance details

Defined in HsLua.ObjectOrientation.Operation

Methods

compare :: Operation -> Operation -> Ordering

(<) :: Operation -> Operation -> Bool

(<=) :: Operation -> Operation -> Bool

(>) :: Operation -> Operation -> Bool

(>=) :: Operation -> Operation -> Bool

max :: Operation -> Operation -> Operation

min :: Operation -> Operation -> Operation

alias :: AliasIndex -> Text -> [AliasIndex] -> Member e fn a #

possibleProperty :: LuaError e => Name -> Text -> (Pusher e b, a -> Possible b) -> (Peeker e b, a -> b -> Possible a) -> Member e fn a #

possibleProperty' :: LuaError e => Name -> TypeSpec -> Text -> (Pusher e b, a -> Possible b) -> (Peeker e b, a -> b -> Possible a) -> Member e fn a #

property :: LuaError e => Name -> Text -> (Pusher e b, a -> b) -> (Peeker e b, a -> b -> a) -> Member e fn a #

property' :: LuaError e => Name -> TypeSpec -> Text -> (Pusher e b, a -> b) -> (Peeker e b, a -> b -> a) -> Member e fn a #

readonly :: Name -> Text -> (Pusher e b, a -> b) -> Member e fn a #

readonly' :: Name -> TypeSpec -> Text -> (Pusher e b, a -> b) -> Member e fn a #

udDocs :: UDTypeWithList e fn a itemtype -> TypeDocs #

udTypeSpec :: UDTypeWithList e fn a itemtype -> TypeSpec #

data Member e fn a #

data Possible a #

Constructors

Actual a 
Absent 

data Property e a #

Constructors

Property 

Fields

data AliasIndex #

Instances

Instances details
IsString AliasIndex 
Instance details

Defined in HsLua.ObjectOrientation

Methods

fromString :: String -> AliasIndex

Eq AliasIndex 
Instance details

Defined in HsLua.ObjectOrientation

Methods

(==) :: AliasIndex -> AliasIndex -> Bool

(/=) :: AliasIndex -> AliasIndex -> Bool

Ord AliasIndex 
Instance details

Defined in HsLua.ObjectOrientation

deftypeGeneric :: Pusher e fn -> Name -> [(Operation, fn)] -> [Member e fn a] -> UDType e fn a #

deftypeGeneric' :: Pusher e fn -> Name -> [(Operation, fn)] -> [Member e fn a] -> Maybe (ListSpec e a itemtype) -> UDTypeWithList e fn a itemtype #

initTypeGeneric :: LuaError e => (UDTypeWithList e fn a itemtype -> LuaE e ()) -> UDTypeWithList e fn a itemtype -> LuaE e Name #

methodGeneric :: Name -> fn -> Member e fn a #

peekUDGeneric :: LuaError e => UDTypeWithList e fn a itemtype -> Peeker e a #

pushUDGeneric :: LuaError e => (UDTypeWithList e fn a itemtype -> LuaE e ()) -> UDTypeWithList e fn a itemtype -> a -> LuaE e () #

type Alias = [AliasIndex] #

type ListSpec e a itemtype = ((Pusher e itemtype, a -> [itemtype]), (Peeker e itemtype, a -> [itemtype] -> a)) #

type UDType e fn a = UDTypeWithList e fn a Void #

data UDTypeWithList e fn a itemtype #

Constructors

UDTypeWithList 

Fields

data Operation #

Instances

Instances details
Show Operation 
Instance details

Defined in HsLua.ObjectOrientation.Operation

Methods

showsPrec :: Int -> Operation -> ShowS

show :: Operation -> String

showList :: [Operation] -> ShowS

Eq Operation 
Instance details

Defined in HsLua.ObjectOrientation.Operation

Methods

(==) :: Operation -> Operation -> Bool

(/=) :: Operation -> Operation -> Bool

Ord Operation 
Instance details

Defined in HsLua.ObjectOrientation.Operation

Methods

compare :: Operation -> Operation -> Ordering

(<) :: Operation -> Operation -> Bool

(<=) :: Operation -> Operation -> Bool

(>) :: Operation -> Operation -> Bool

(>=) :: Operation -> Operation -> Bool

max :: Operation -> Operation -> Operation

min :: Operation -> Operation -> Operation

boolParam :: Text -> Text -> Parameter e Bool #

boolResult :: Text -> FunctionResults e Bool #

integralParam :: (Read a, Integral a) => Text -> Text -> Parameter e a #

integralResult :: (Integral a, Show a) => Text -> FunctionResults e a #

stringParam :: Text -> Text -> Parameter e String #

stringResult :: Text -> FunctionResults e String #

textParam :: Text -> Text -> Parameter e Text #

textResult :: Text -> FunctionResults e Text #

(###) :: (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a #

(<#>) :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b #

data HsFnPrecursor e a #

Instances

Instances details
Functor (HsFnPrecursor e) 
Instance details

Defined in HsLua.Packaging.Function

Methods

fmap :: (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b

(<$) :: a -> HsFnPrecursor e b -> HsFnPrecursor e a

data Parameter e a #

Constructors

Parameter 

defun :: Name -> a -> HsFnPrecursor e a #

functionResult :: Pusher e a -> TypeSpec -> Text -> FunctionResults e a #

lambda :: a -> HsFnPrecursor e a #

liftPure :: (a -> b) -> a -> LuaE e b #

liftPure2 :: (a -> b -> c) -> a -> b -> LuaE e c #

liftPure3 :: (a -> b -> c -> d) -> a -> b -> c -> LuaE e d #

liftPure4 :: (a -> b -> c -> d -> e) -> a -> b -> c -> d -> LuaE err e #

liftPure5 :: (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> LuaE err f #

opt :: Parameter e a -> Parameter e (Maybe a) #

optionalParameter :: Peeker e a -> TypeSpec -> Text -> Text -> Parameter e (Maybe a) #

parameter :: Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a #

preloadModule :: LuaError e => Module e -> LuaE e () #

pushModule :: LuaError e => Module e -> LuaE e () #

registerModule :: LuaError e => Module e -> LuaE e () #

data Field e #

Constructors

Field 

Fields

data FunctionDoc #

Instances

Instances details
Show FunctionDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

showsPrec :: Int -> FunctionDoc -> ShowS

show :: FunctionDoc -> String

showList :: [FunctionDoc] -> ShowS

Eq FunctionDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

(==) :: FunctionDoc -> FunctionDoc -> Bool

(/=) :: FunctionDoc -> FunctionDoc -> Bool

Ord FunctionDoc 
Instance details

Defined in HsLua.Packaging.Types

data ParameterDoc #

Constructors

ParameterDoc 

Fields

Instances

Instances details
Show ParameterDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

showsPrec :: Int -> ParameterDoc -> ShowS

show :: ParameterDoc -> String

showList :: [ParameterDoc] -> ShowS

Eq ParameterDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

(==) :: ParameterDoc -> ParameterDoc -> Bool

(/=) :: ParameterDoc -> ParameterDoc -> Bool

Ord ParameterDoc 
Instance details

Defined in HsLua.Packaging.Types

data ResultValueDoc #

Constructors

ResultValueDoc 

Fields

Instances

Instances details
Show ResultValueDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

showsPrec :: Int -> ResultValueDoc -> ShowS

show :: ResultValueDoc -> String

showList :: [ResultValueDoc] -> ShowS

Eq ResultValueDoc 
Instance details

Defined in HsLua.Packaging.Types

Ord ResultValueDoc 
Instance details

Defined in HsLua.Packaging.Types

data ResultsDoc #

Instances

Instances details
Show ResultsDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

showsPrec :: Int -> ResultsDoc -> ShowS

show :: ResultsDoc -> String

showList :: [ResultsDoc] -> ShowS

Eq ResultsDoc 
Instance details

Defined in HsLua.Packaging.Types

Methods

(==) :: ResultsDoc -> ResultsDoc -> Bool

(/=) :: ResultsDoc -> ResultsDoc -> Bool

Ord ResultsDoc 
Instance details

Defined in HsLua.Packaging.Types

type DocumentedTypeWithList e a itemtype = UDTypeWithList e (DocumentedFunction e) a itemtype #

deftype' :: LuaError e => Name -> [(Operation, DocumentedFunction e)] -> [Member e (DocumentedFunction e) a] -> Maybe (ListSpec e a itemtype) -> DocumentedTypeWithList e a itemtype #

peekUD :: LuaError e => DocumentedTypeWithList e a itemtype -> Peeker e a #

pushUD :: LuaError e => DocumentedTypeWithList e a itemtype -> a -> LuaE e () #

udparam :: LuaError e => DocumentedTypeWithList e a itemtype -> Text -> Text -> Parameter e a #

udresult :: LuaError e => DocumentedTypeWithList e a itemtype -> Text -> FunctionResults e a #

alias :: AliasIndex -> Text -> [AliasIndex] -> Member e fn a #

possibleProperty :: LuaError e => Name -> Text -> (Pusher e b, a -> Possible b) -> (Peeker e b, a -> b -> Possible a) -> Member e fn a #

possibleProperty' :: LuaError e => Name -> TypeSpec -> Text -> (Pusher e b, a -> Possible b) -> (Peeker e b, a -> b -> Possible a) -> Member e fn a #

property :: LuaError e => Name -> Text -> (Pusher e b, a -> b) -> (Peeker e b, a -> b -> a) -> Member e fn a #

property' :: LuaError e => Name -> TypeSpec -> Text -> (Pusher e b, a -> b) -> (Peeker e b, a -> b -> a) -> Member e fn a #

readonly :: Name -> Text -> (Pusher e b, a -> b) -> Member e fn a #

readonly' :: Name -> TypeSpec -> Text -> (Pusher e b, a -> b) -> Member e fn a #

udDocs :: UDTypeWithList e fn a itemtype -> TypeDocs #

udTypeSpec :: UDTypeWithList e fn a itemtype -> TypeSpec #

data Member e fn a #

data Possible a #

Constructors

Actual a 
Absent 

data Property e a #

Type classes

class LuaError e => Exposable e a where #

Instances

Instances details
LuaError e => Exposable e (HaskellFunction e) 
Instance details

Defined in HsLua.Class.Exposable

(LuaError e, Pushable a) => Exposable e (LuaE e a) 
Instance details

Defined in HsLua.Class.Exposable

(LuaError e, Pushable a) => Exposable e (Peek e a) 
Instance details

Defined in HsLua.Class.Exposable

(Peekable a, Exposable e b) => Exposable e (a -> b) 
Instance details

Defined in HsLua.Class.Exposable

Methods

partialApply :: StackIndex -> (a -> b) -> Peek e NumResults #

class Invokable a where #

Methods

addArg :: Name -> (forall e. LuaError e => LuaE e ()) -> NumArgs -> a #

Instances

Instances details
(LuaError e, Peekable a) => Invokable (LuaE e a) 
Instance details

Defined in HsLua.Class.Invokable

Methods

addArg :: Name -> (forall e0. LuaError e0 => LuaE e0 ()) -> NumArgs -> LuaE e a #

(Pushable a, Invokable b) => Invokable (a -> b) 
Instance details

Defined in HsLua.Class.Invokable

Methods

addArg :: Name -> (forall e. LuaError e => LuaE e ()) -> NumArgs -> a -> b #

invoke :: Invokable a => Name -> a #

class Peekable a where #

Methods

safepeek :: LuaError e => Peeker e a #

Instances

Instances details
Peekable ByteString 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e ByteString #

Peekable ByteString 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e ByteString #

Peekable CFunction 
Instance details

Defined in HsLua.Class.Peekable

Peekable Integer 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Integer #

Peekable Number 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Number #

Peekable State 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e State #

Peekable Text 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Text #

Peekable Integer 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Integer #

Peekable () 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e () #

Peekable Bool 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Bool #

Peekable Double 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Double #

Peekable Float 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Float #

Peekable Int 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e Int #

Peekable (Ptr a) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e (Ptr a) #

(Ord a, Peekable a) => Peekable (Set a) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e (Set a) #

Peekable a => Peekable (Optional a) 
Instance details

Defined in HsLua.Class.Util

Methods

safepeek :: LuaError e => Peeker e (Optional a) #

Peekable [Char] 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e [Char] #

Peekable a => Peekable [a] 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e [a] #

(Ord a, Peekable a, Peekable b) => Peekable (Map a b) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e (Map a b) #

(Peekable a, Peekable b) => Peekable (a, b) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e (a, b) #

(Peekable a, Peekable b, Peekable c) => Peekable (a, b, c) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e (a, b, c) #

(Peekable a, Peekable b, Peekable c, Peekable d) => Peekable (a, b, c, d) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e => Peeker e (a, b, c, d) #

(Peekable a, Peekable b, Peekable c, Peekable d, Peekable e) => Peekable (a, b, c, d, e) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e0 => Peeker e0 (a, b, c, d, e) #

(Peekable a, Peekable b, Peekable c, Peekable d, Peekable e, Peekable f) => Peekable (a, b, c, d, e, f) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e0 => Peeker e0 (a, b, c, d, e, f) #

(Peekable a, Peekable b, Peekable c, Peekable d, Peekable e, Peekable f, Peekable g) => Peekable (a, b, c, d, e, f, g) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e0 => Peeker e0 (a, b, c, d, e, f, g) #

(Peekable a, Peekable b, Peekable c, Peekable d, Peekable e, Peekable f, Peekable g, Peekable h) => Peekable (a, b, c, d, e, f, g, h) 
Instance details

Defined in HsLua.Class.Peekable

Methods

safepeek :: LuaError e0 => Peeker e0 (a, b, c, d, e, f, g, h) #

peek :: forall a e. (LuaError e, Peekable a) => StackIndex -> LuaE e a #

class Pushable a where #

Methods

push :: LuaError e => a -> LuaE e () #

Instances

Instances details
Pushable ByteString 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => ByteString -> LuaE e () #

Pushable ByteString 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => ByteString -> LuaE e () #

Pushable CFunction 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => CFunction -> LuaE e () #

Pushable Integer 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Integer -> LuaE e () #

Pushable Number 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Number -> LuaE e () #

Pushable Text 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Text -> LuaE e () #

Pushable Integer 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Integer -> LuaE e () #

Pushable () 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => () -> LuaE e () #

Pushable Bool 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Bool -> LuaE e () #

Pushable Double 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Double -> LuaE e () #

Pushable Float 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Float -> LuaE e () #

Pushable Int 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Int -> LuaE e () #

Pushable (Ptr a) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Ptr a -> LuaE e () #

Pushable a => Pushable (Set a) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Set a -> LuaE e () #

Pushable a => Pushable (Optional a) 
Instance details

Defined in HsLua.Class.Util

Methods

push :: LuaError e => Optional a -> LuaE e () #

Pushable [Char] 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => [Char] -> LuaE e () #

Pushable a => Pushable [a] 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => [a] -> LuaE e () #

(Pushable a, Pushable b) => Pushable (Map a b) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => Map a b -> LuaE e () #

(Pushable a, Pushable b) => Pushable (a, b) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => (a, b) -> LuaE e () #

(Pushable a, Pushable b, Pushable c) => Pushable (a, b, c) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => (a, b, c) -> LuaE e () #

(Pushable a, Pushable b, Pushable c, Pushable d) => Pushable (a, b, c, d) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e => (a, b, c, d) -> LuaE e () #

(Pushable a, Pushable b, Pushable c, Pushable d, Pushable e) => Pushable (a, b, c, d, e) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e0 => (a, b, c, d, e) -> LuaE e0 () #

(Pushable a, Pushable b, Pushable c, Pushable d, Pushable e, Pushable f) => Pushable (a, b, c, d, e, f) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e0 => (a, b, c, d, e, f) -> LuaE e0 () #

(Pushable a, Pushable b, Pushable c, Pushable d, Pushable e, Pushable f, Pushable g) => Pushable (a, b, c, d, e, f, g) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e0 => (a, b, c, d, e, f, g) -> LuaE e0 () #

(Pushable a, Pushable b, Pushable c, Pushable d, Pushable e, Pushable f, Pushable g, Pushable h) => Pushable (a, b, c, d, e, f, g, h) 
Instance details

Defined in HsLua.Class.Pushable

Methods

push :: LuaError e0 => (a, b, c, d, e, f, g, h) -> LuaE e0 () #

Marshal to and from JSON-like structures

peekToAeson :: Peeker e (ToAeson e) #

peekValue :: LuaError e => Peeker e Value #

peekViaJSON :: (FromJSON a, LuaError e) => Peeker e a #

pushToAeson :: Pusher e (ToAeson e) #

pushValue :: LuaError e => Pusher e Value #

pushViaJSON :: (ToJSON a, LuaError e) => Pusher e a #

Utility functions

getglobal' :: LuaError e => Name -> LuaE e () Source #

Like getglobal, but knows about packages and nested tables. E.g.

getglobal' "math.sin"

will return the function sin in package math.

setglobal' :: LuaError e => Name -> LuaE e () Source #

Like setglobal, but knows about packages and nested tables. E.g.

pushstring "0.9.4"
setglobal' "mypackage.version"

All tables and fields, except for the last field, must exist.

popValue :: (LuaError e, Peekable a) => LuaE e a #

newtype Optional a #

Constructors

Optional 

Fields

Instances

Instances details
Peekable a => Peekable (Optional a) 
Instance details

Defined in HsLua.Class.Util

Methods

safepeek :: LuaError e => Peeker e (Optional a) #

Pushable a => Pushable (Optional a) 
Instance details

Defined in HsLua.Class.Util

Methods

push :: LuaError e => Optional a -> LuaE e () #

peekEither :: (LuaError e, Peekable a) => StackIndex -> LuaE e (Either e a) #