Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2024 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb@hslua.org> |
Stability | beta |
Portability | non-portable (depends on GHC) |
Safe Haskell | None |
Language | Haskell2010 |
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
from
Hackage package lua.Core
Synopsis
- type Lua a = LuaE Exception a
- newtype LuaE e a = Lua {
- unLua :: ReaderT LuaEnvironment IO a
- compare :: LuaError e => StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
- concat :: LuaError e => NumArgs -> LuaE e ()
- class Exception e => LuaError e where
- popException :: LuaE e e
- pushException :: e -> LuaE e ()
- luaException :: String -> e
- newtype Name = Name {
- fromName :: ByteString
- getfield :: LuaError e => StackIndex -> Name -> LuaE e Type
- getglobal :: LuaError e => Name -> LuaE e Type
- nth :: CInt -> StackIndex
- pop :: Int -> LuaE e ()
- pushvalue :: StackIndex -> LuaE e ()
- remove :: StackIndex -> LuaE e ()
- setfield :: LuaError e => StackIndex -> Name -> LuaE e ()
- setglobal :: LuaError e => Name -> LuaE e ()
- top :: StackIndex
- error :: LuaE e NumResults
- data RelationalOperator
- newtype Integer = Integer Int64
- data Type
- insert :: StackIndex -> LuaE e ()
- checkstack' :: LuaError e => Int -> String -> LuaE e ()
- dofile :: Maybe FilePath -> LuaE e Status
- dostring :: ByteString -> LuaE e Status
- getmetafield :: StackIndex -> Name -> LuaE e Type
- getmetatable' :: Name -> LuaE e Type
- getref :: LuaError e => StackIndex -> Reference -> LuaE e Type
- getsubtable :: LuaError e => StackIndex -> Name -> LuaE e Bool
- loadbuffer :: ByteString -> Name -> LuaE e Status
- loaded :: Name
- loadfile :: Maybe FilePath -> LuaE e Status
- loadstring :: ByteString -> LuaE e Status
- newmetatable :: Name -> LuaE e Bool
- newstate :: IO State
- preload :: Name
- ref :: StackIndex -> LuaE e Reference
- requiref :: LuaError e => Name -> CFunction -> Bool -> LuaE e ()
- tostring' :: LuaError e => StackIndex -> LuaE e ByteString
- traceback :: State -> Maybe ByteString -> Int -> LuaE e ()
- unref :: StackIndex -> Reference -> LuaE e ()
- where' :: Int -> LuaE e ()
- pushHaskellFunction :: LuaError e => HaskellFunction e -> LuaE e ()
- pushPreCFunction :: PreCFunction -> LuaE e ()
- getupvalue :: StackIndex -> Int -> LuaE e (Maybe Name)
- setupvalue :: StackIndex -> Int -> LuaE e (Maybe Name)
- newtype Exception = Exception {
- exceptionMessage :: String
- 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 ()
- throwErrorAsException :: LuaError e => LuaE e a
- 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 ()
- absindex :: StackIndex -> LuaE e StackIndex
- call :: LuaError e => NumArgs -> NumResults -> LuaE e ()
- checkstack :: Int -> LuaE e Bool
- close :: State -> IO ()
- copy :: StackIndex -> StackIndex -> LuaE e ()
- createtable :: Int -> Int -> LuaE e ()
- equal :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool
- gc :: GCControl -> LuaE e Int
- getiuservalue :: StackIndex -> Int -> LuaE e Type
- getmetatable :: StackIndex -> LuaE e Bool
- gettable :: LuaError e => StackIndex -> LuaE e Type
- gettop :: LuaE e StackIndex
- isboolean :: StackIndex -> LuaE e Bool
- iscfunction :: StackIndex -> LuaE e Bool
- isfunction :: StackIndex -> LuaE e Bool
- isinteger :: StackIndex -> LuaE e Bool
- islightuserdata :: StackIndex -> LuaE e Bool
- isnil :: StackIndex -> LuaE e Bool
- isnone :: StackIndex -> LuaE e Bool
- isnoneornil :: StackIndex -> LuaE e Bool
- isnumber :: StackIndex -> LuaE e Bool
- isstring :: StackIndex -> LuaE e Bool
- istable :: StackIndex -> LuaE e Bool
- isthread :: StackIndex -> LuaE e Bool
- isuserdata :: StackIndex -> LuaE e Bool
- lessthan :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool
- load :: Reader -> Ptr () -> Name -> LuaE e Status
- ltype :: StackIndex -> LuaE e Type
- 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 ()
- pcall :: NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
- pushboolean :: Bool -> LuaE e ()
- pushcclosure :: CFunction -> NumArgs -> LuaE e ()
- pushcfunction :: CFunction -> LuaE e ()
- pushglobaltable :: LuaE e ()
- pushinteger :: Integer -> LuaE e ()
- pushlightuserdata :: Ptr a -> LuaE e ()
- pushnil :: LuaE e ()
- pushnumber :: Number -> LuaE e ()
- pushstring :: ByteString -> LuaE e ()
- pushthread :: LuaE e Bool
- rawequal :: StackIndex -> StackIndex -> LuaE e Bool
- rawget :: LuaError e => StackIndex -> LuaE e Type
- rawgeti :: LuaError e => StackIndex -> Integer -> LuaE e Type
- rawlen :: StackIndex -> LuaE e Int
- rawset :: LuaError e => StackIndex -> LuaE e ()
- rawseti :: LuaError e => StackIndex -> Integer -> LuaE e ()
- register :: LuaError e => Name -> CFunction -> LuaE e ()
- replace :: StackIndex -> LuaE e ()
- rotate :: StackIndex -> Int -> LuaE e ()
- setiuservalue :: StackIndex -> Int -> LuaE e Bool
- setmetatable :: StackIndex -> LuaE e ()
- settable :: LuaError e => StackIndex -> LuaE e ()
- settop :: StackIndex -> LuaE e ()
- setwarnf :: WarnFunction -> Ptr () -> LuaE e ()
- status :: LuaE e Status
- toboolean :: StackIndex -> LuaE e Bool
- tocfunction :: StackIndex -> LuaE e (Maybe CFunction)
- tointeger :: StackIndex -> LuaE e (Maybe Integer)
- 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
- upvalueindex :: StackIndex -> StackIndex
- data GCManagedState
- closeGCManagedState :: GCManagedState -> IO ()
- newGCManagedState :: IO GCManagedState
- run :: LuaE e a -> IO a
- runEither :: Exception e => LuaE e a -> IO (Either e a)
- withGCManagedState :: GCManagedState -> LuaE e a -> IO a
- callTrace :: LuaError e => NumArgs -> NumResults -> LuaE e ()
- dofileTrace :: Maybe FilePath -> LuaE e Status
- dostringTrace :: ByteString -> LuaE e Status
- pcallTrace :: NumArgs -> NumResults -> LuaE e Status
- data Status
- data GCControl
- type HaskellFunction e = LuaE e NumResults
- newtype LuaEnvironment = LuaEnvironment {
- luaEnvState :: State
- multret :: NumResults
- noref :: Int
- refnil :: Int
- registryindex :: StackIndex
- runWith :: State -> LuaE e a -> IO a
- state :: LuaE e State
- 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 ()
- nthBottom :: CInt -> StackIndex
- nthTop :: CInt -> StackIndex
- fromReference :: Reference -> CInt
- toReference :: CInt -> Reference
- liftIO :: MonadIO m => IO a -> m a
- data Reference
- type CFunction = FunPtr PreCFunction
- newtype NumArgs = NumArgs {
- fromNumArgs :: CInt
- newtype NumResults = NumResults {
- fromNumResults :: CInt
- newtype Number = Number Double
- type PreCFunction = State -> IO NumResults
- newtype StackIndex = StackIndex {
- fromStackIndex :: CInt
- newtype State = State (Ptr ())
- pushList :: LuaError e => Pusher e a -> [a] -> LuaE e ()
- liftLua :: LuaE e a -> Peek e a
- data Result a
- type Peeker e a = StackIndex -> Peek e a
- type Pusher e a = a -> LuaE e ()
- newtype Peek e a = Peek {}
- 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)
- peekName :: Peeker e Name
- peekNil :: Peeker e ()
- peekNilOr :: Alternative m => Peeker e a -> Peeker e (m a)
- peekNoneOr :: Alternative m => Peeker e a -> Peeker e (m a)
- peekNoneOrNil :: Peeker e ()
- 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
- data 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
- data Property e a = Property {
- propertyGet :: a -> LuaE e NumResults
- propertySet :: Maybe (StackIndex -> a -> LuaE e a)
- propertyDescription :: Text
- propertyType :: TypeSpec
- data AliasIndex
- 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 = UDTypeWithList {
- udName :: Name
- udOperations :: [(Operation, fn)]
- udProperties :: Map Name (Property e a)
- udMethods :: Map Name fn
- udAliases :: Map AliasIndex Alias
- udListSpec :: Maybe (ListSpec e a itemtype)
- udFnPusher :: fn -> LuaE e ()
- data Module e = Module {
- moduleName :: Name
- moduleDescription :: Text
- moduleFields :: [Field e]
- moduleFunctions :: [DocumentedFunction e]
- moduleOperations :: [(Operation, DocumentedFunction e)]
- moduleTypeInitializers :: [LuaE e Name]
- data 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
- docsField :: Name
- documentation :: LuaError e => DocumentedFunction e
- getdocumentation :: LuaError e => StackIndex -> LuaE e Type
- pushFieldDoc :: LuaError e => Pusher e (Field e)
- pushFunctionDoc :: LuaError e => Pusher e (DocumentedFunction e)
- pushModuleDoc :: LuaError e => Pusher e (Module e)
- registerDocumentation :: LuaError e => StackIndex -> LuaE e ()
- (###) :: (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a
- (#?) :: DocumentedFunction e -> Text -> DocumentedFunction e
- (<#>) :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
- (=#>) :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e
- (=?>) :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
- data FunctionResult e a = FunctionResult {
- fnResultPusher :: Pusher e a
- fnResultDoc :: ResultValueDoc
- type FunctionResults e a = [FunctionResult e a]
- data HsFnPrecursor e a
- data Parameter e a = Parameter {
- parameterPeeker :: Peeker e a
- parameterDoc :: ParameterDoc
- applyParameter :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
- 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
- pushDocumentedFunction :: LuaError e => DocumentedFunction e -> LuaE e ()
- returnResult :: HsFnPrecursor e (LuaE e a) -> FunctionResult e a -> DocumentedFunction e
- returnResults :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e
- returnResultsOnStack :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
- setName :: Name -> DocumentedFunction e -> DocumentedFunction e
- since :: DocumentedFunction e -> Version -> DocumentedFunction e
- toHsFnPrecursor :: StackIndex -> Name -> a -> HsFnPrecursor e a
- updateFunctionDescription :: DocumentedFunction e -> Text -> DocumentedFunction e
- preloadModule :: LuaError e => Module e -> LuaE e ()
- preloadModuleWithName :: LuaError e => Module e -> Name -> LuaE e ()
- pushModule :: LuaError e => Module e -> LuaE e ()
- registerModule :: LuaError e => Module e -> LuaE e ()
- data DocumentedFunction e = DocumentedFunction {}
- data Field e = Field {
- fieldName :: Text
- fieldType :: TypeSpec
- fieldDescription :: Text
- fieldPushValue :: LuaE e ()
- data FunctionDoc = FunctionDoc {
- functionDescription :: Text
- parameterDocs :: [ParameterDoc]
- functionResultsDocs :: ResultsDoc
- functionSince :: Maybe Version
- data ParameterDoc = ParameterDoc {
- parameterName :: Text
- parameterType :: TypeSpec
- parameterDescription :: Text
- parameterIsOptional :: Bool
- data ResultValueDoc = ResultValueDoc {
- resultValueType :: TypeSpec
- resultValueDescription :: Text
- data ResultsDoc
- = ResultsDocList [ResultValueDoc]
- | ResultsDocMult Text
- type DocumentedType e a = UDType e (DocumentedFunction e) a
- type DocumentedTypeWithList e a itemtype = UDTypeWithList e (DocumentedFunction e) a itemtype
- deftype :: LuaError e => Name -> [(Operation, DocumentedFunction e)] -> [Member e (DocumentedFunction e) a] -> DocumentedType e a
- deftype' :: LuaError e => Name -> [(Operation, DocumentedFunction e)] -> [Member e (DocumentedFunction e) a] -> Maybe (ListSpec e a itemtype) -> DocumentedTypeWithList e a itemtype
- initType :: LuaError e => DocumentedTypeWithList e a itemtype -> LuaE e Name
- method :: DocumentedFunction e -> Member e (DocumentedFunction e) a
- operation :: Operation -> DocumentedFunction e -> (Operation, DocumentedFunction e)
- 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
- data Property e a
- class LuaError e => Exposable e a where
- partialApply :: StackIndex -> a -> Peek e NumResults
- pushAsHaskellFunction :: Exposable e a => a -> LuaE e ()
- registerHaskellFunction :: Exposable e a => Name -> a -> LuaE e ()
- toHaskellFunction :: Exposable e a => a -> HaskellFunction e
- class Invokable a where
- invoke :: Invokable a => Name -> a
- class Peekable a where
- peek :: forall a e. (LuaError e, Peekable a) => StackIndex -> LuaE e a
- class Pushable a where
- jsonarray :: Name
- 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
- getglobal' :: LuaError e => Name -> LuaE e ()
- setglobal' :: LuaError e => Name -> LuaE e ()
- popValue :: (LuaError e, Peekable a) => LuaE e a
- newtype Optional a = Optional {
- fromOptional :: Maybe a
- peekEither :: (LuaError e, Peekable a) => StackIndex -> LuaE e (Either e a)
- raiseError :: (LuaError e, Pushable a) => a -> LuaE e NumResults
Core functionality
Constructors
Lua | |
Fields
|
Instances
LuaError e => Exposable e (HaskellFunction e) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> HaskellFunction e -> Peek e NumResults # | |
MonadReader LuaEnvironment (LuaE e) | |
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) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> LuaE e a -> Peek e NumResults # | |
MonadIO (LuaE e) | |
Defined in HsLua.Core.Types | |
MonadCatch (LuaE e) | |
Defined in HsLua.Core.Types | |
MonadMask (LuaE e) | |
Defined in HsLua.Core.Types | |
MonadThrow (LuaE e) | |
Defined in HsLua.Core.Types | |
Applicative (LuaE e) | |
Functor (LuaE e) | |
Monad (LuaE e) | |
(LuaError e, Peekable a) => Invokable (LuaE e a) | |
compare :: LuaError e => StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool #
class Exception e => LuaError e where #
Instances
LuaError Exception | |
Defined in HsLua.Core.Error Methods popException :: LuaE Exception Exception # pushException :: Exception -> LuaE Exception () # luaException :: String -> Exception # |
Instances
Semigroup Name | |
IsString Name | |
Defined in HsLua.Core.Types Methods fromString :: String -> Name | |
Show Name | |
Eq Name | |
Ord Name | |
nth :: CInt -> StackIndex #
pushvalue :: StackIndex -> LuaE e () #
remove :: StackIndex -> LuaE e () #
top :: StackIndex #
error :: LuaE e NumResults #
data RelationalOperator #
Instances
Show RelationalOperator | |
Defined in HsLua.Core.Types Methods showsPrec :: Int -> RelationalOperator -> ShowS show :: RelationalOperator -> String showList :: [RelationalOperator] -> ShowS | |
Eq RelationalOperator | |
Defined in HsLua.Core.Types Methods (==) :: RelationalOperator -> RelationalOperator -> Bool (/=) :: RelationalOperator -> RelationalOperator -> Bool | |
Ord RelationalOperator | |
Defined in HsLua.Core.Types Methods compare :: RelationalOperator -> RelationalOperator -> Ordering (<) :: RelationalOperator -> RelationalOperator -> Bool (<=) :: RelationalOperator -> RelationalOperator -> Bool (>) :: RelationalOperator -> RelationalOperator -> Bool (>=) :: RelationalOperator -> RelationalOperator -> Bool max :: RelationalOperator -> RelationalOperator -> RelationalOperator min :: RelationalOperator -> RelationalOperator -> RelationalOperator |
Constructors
Integer Int64 |
Constructors
TypeNone | |
TypeNil | |
TypeBoolean | |
TypeLightUserdata | |
TypeNumber | |
TypeString | |
TypeTable | |
TypeFunction | |
TypeUserdata | |
TypeThread |
Instances
Bounded Type | |
Defined in HsLua.Core.Types | |
Enum Type | |
Read Type | |
Defined in HsLua.Core.Types | |
Show Type | |
Eq Type | |
Ord Type | |
insert :: StackIndex -> LuaE e () #
checkstack' :: LuaError e => Int -> String -> LuaE e () #
getmetafield :: StackIndex -> Name -> LuaE e Type #
getmetatable' :: Name -> LuaE e Type #
getsubtable :: LuaError e => StackIndex -> Name -> LuaE e Bool #
loadbuffer :: ByteString -> Name -> LuaE e Status #
loadstring :: ByteString -> LuaE e Status #
newmetatable :: Name -> LuaE e Bool #
ref :: StackIndex -> LuaE e Reference #
tostring' :: LuaError e => StackIndex -> LuaE e ByteString #
unref :: StackIndex -> Reference -> LuaE e () #
pushHaskellFunction :: LuaError e => HaskellFunction e -> LuaE e () #
pushPreCFunction :: PreCFunction -> LuaE e () #
getupvalue :: StackIndex -> Int -> LuaE e (Maybe Name) #
setupvalue :: StackIndex -> Int -> LuaE e (Maybe Name) #
Constructors
Exception | |
Fields
|
Instances
Exception Exception | |
Defined in HsLua.Core.Error Methods toException :: Exception -> SomeException fromException :: SomeException -> Maybe Exception displayException :: Exception -> String backtraceDesired :: Exception -> Bool | |
Show Exception | |
Eq Exception | |
LuaError Exception | |
Defined in HsLua.Core.Error Methods popException :: LuaE Exception Exception # pushException :: Exception -> LuaE Exception () # luaException :: String -> Exception # |
changeErrorType :: forall old new a. LuaE old a -> LuaE new a #
popErrorMessage :: State -> IO ByteString #
pushTypeMismatchError :: ByteString -> StackIndex -> LuaE e () #
throwErrorAsException :: LuaError e => LuaE e a #
throwTypeMismatchError :: LuaError e => ByteString -> StackIndex -> LuaE e a #
absindex :: StackIndex -> LuaE e StackIndex #
checkstack :: Int -> LuaE e Bool #
copy :: StackIndex -> StackIndex -> LuaE e () #
createtable :: Int -> Int -> LuaE e () #
equal :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool #
getiuservalue :: StackIndex -> Int -> LuaE e Type #
getmetatable :: StackIndex -> LuaE e Bool #
gettop :: LuaE e StackIndex #
isboolean :: StackIndex -> LuaE e Bool #
iscfunction :: StackIndex -> LuaE e Bool #
isfunction :: StackIndex -> LuaE e Bool #
isinteger :: StackIndex -> LuaE e Bool #
islightuserdata :: StackIndex -> LuaE e Bool #
isnil :: StackIndex -> LuaE e Bool #
isnone :: StackIndex -> LuaE e Bool #
isnoneornil :: StackIndex -> LuaE e Bool #
isnumber :: StackIndex -> LuaE e Bool #
isstring :: StackIndex -> LuaE e Bool #
istable :: StackIndex -> LuaE e Bool #
isthread :: StackIndex -> LuaE e Bool #
isuserdata :: StackIndex -> LuaE e Bool #
lessthan :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool #
ltype :: StackIndex -> LuaE e Type #
newuserdatauv :: Int -> Int -> LuaE e (Ptr ()) #
next :: LuaError e => StackIndex -> LuaE e Bool #
openpackage :: LuaError e => LuaE e () #
openstring :: LuaError e => LuaE e () #
pcall :: NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status #
pushboolean :: Bool -> LuaE e () #
pushcclosure :: CFunction -> NumArgs -> LuaE e () #
pushcfunction :: CFunction -> LuaE e () #
pushglobaltable :: LuaE e () #
pushinteger :: Integer -> LuaE e () #
pushlightuserdata :: Ptr a -> LuaE e () #
pushnumber :: Number -> LuaE e () #
pushstring :: ByteString -> LuaE e () #
pushthread :: LuaE e Bool #
rawequal :: StackIndex -> StackIndex -> LuaE e Bool #
rawlen :: StackIndex -> LuaE e Int #
rawset :: LuaError e => StackIndex -> LuaE e () #
replace :: StackIndex -> LuaE e () #
rotate :: StackIndex -> Int -> LuaE e () #
setiuservalue :: StackIndex -> Int -> LuaE e Bool #
setmetatable :: StackIndex -> LuaE e () #
settable :: LuaError e => StackIndex -> LuaE e () #
settop :: StackIndex -> LuaE e () #
toboolean :: StackIndex -> LuaE e Bool #
tocfunction :: StackIndex -> LuaE e (Maybe CFunction) #
tointeger :: StackIndex -> LuaE e (Maybe Integer) #
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)) #
upvalueindex :: StackIndex -> StackIndex #
data GCManagedState #
closeGCManagedState :: GCManagedState -> IO () #
newGCManagedState :: IO GCManagedState #
withGCManagedState :: GCManagedState -> LuaE e a -> IO a #
dofileTrace :: Maybe FilePath -> LuaE e Status #
dostringTrace :: ByteString -> LuaE e Status #
pcallTrace :: NumArgs -> NumResults -> LuaE e Status #
Constructors
GCStop | |
GCRestart | |
GCCollect | |
GCCount | |
GCCountb | |
GCStep CInt | |
GCInc CInt CInt CInt | |
GCGen CInt CInt | |
GCIsRunning |
Instances
Show GCControl | |
Eq GCControl | |
Ord GCControl | |
Defined in HsLua.Core.Types |
type HaskellFunction e = LuaE e NumResults #
newtype LuaEnvironment #
Constructors
LuaEnvironment | |
Fields
|
Instances
MonadReader LuaEnvironment (LuaE e) | |
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 |
multret :: NumResults #
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 #
nthBottom :: CInt -> StackIndex #
nthTop :: CInt -> StackIndex #
fromReference :: Reference -> CInt #
toReference :: CInt -> Reference #
type CFunction = FunPtr PreCFunction #
Constructors
NumArgs | |
Fields
|
newtype NumResults #
Constructors
NumResults | |
Fields
|
Instances
Constructors
Number Double |
Instances
Floating Number | |
RealFloat Number | |
Defined in Lua.Types Methods floatRadix :: Number -> Integer floatDigits :: Number -> Int floatRange :: Number -> (Int, Int) decodeFloat :: Number -> (Integer, Int) encodeFloat :: Integer -> Int -> Number significand :: Number -> Number scaleFloat :: Int -> Number -> Number isInfinite :: Number -> Bool isDenormalized :: Number -> Bool isNegativeZero :: Number -> Bool | |
Num Number | |
Read Number | |
Fractional Number | |
Real Number | |
Defined in Lua.Types Methods toRational :: Number -> Rational | |
RealFrac Number | |
Show Number | |
Eq Number | |
Ord Number | |
Peekable Number | |
Pushable Number | |
type PreCFunction = State -> IO NumResults #
newtype StackIndex #
Constructors
StackIndex | |
Fields
|
Instances
Constructors
State (Ptr ()) |
Marshalling
Instances
Alternative Result | |
Applicative Result | |
Functor Result | |
Monad Result | |
MonadPlus Result | |
MonadFail Result | |
Defined in HsLua.Marshalling.Peek | |
Foldable Result | |
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 elem :: Eq a => a -> Result a -> Bool maximum :: Ord a => Result a -> a | |
Traversable Result | |
Show a => Show (Result a) | |
Eq a => Eq (Result a) | |
type Peeker e a = StackIndex -> Peek e a #
Instances
(LuaError e, Pushable a) => Exposable e (Peek e a) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> Peek e a -> Peek e NumResults # | |
Alternative (Peek e) | |
Applicative (Peek e) | |
Functor (Peek e) | |
Monad (Peek e) | |
MonadPlus (Peek e) | |
MonadFail (Peek e) | |
Defined in HsLua.Marshalling.Peek |
pushLazyByteString :: Pusher e ByteString #
pushRealFloat :: RealFloat a => a -> LuaE e () #
pushString :: String -> LuaE e () #
resultToEither :: Result a -> Either String a #
retrieving :: Name -> Peek e a -> Peek e a #
withContext :: Name -> Peek e a -> Peek e a #
peekByteString :: Peeker e ByteString #
peekIntegral :: (Integral a, Read a) => Peeker e a #
peekLazyByteString :: Peeker e ByteString #
peekNoneOr :: Alternative m => Peeker e a -> Peeker e (m a) #
peekNoneOrNil :: Peeker e () #
peekNoneOrNilOr :: Alternative m => Peeker e a -> Peeker e (m a) #
peekRealFloat :: (RealFloat a, Read a) => Peeker e a #
peekString :: Peeker e String #
peekStringy :: IsString a => Peeker e a #
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 #
pushByteString :: Pusher e ByteString #
pushIntegral :: (Integral a, Show a) => a -> LuaE e () #
pushNonEmpty :: LuaError e => Pusher e a -> NonEmpty a -> LuaE e () #
pushIterator :: forall a e. LuaError e => (a -> LuaE e NumResults) -> [a] -> LuaE e NumResults #
Module, data, and function packaging
Constructors
Add | |
Sub | |
Mul | |
Div | |
Mod | |
Pow | |
Unm | |
Idiv | |
Band | |
Bor | |
Bxor | |
Bnot | |
Shl | |
Shr | |
Concat | |
Len | |
Eq | |
Lt | |
Le | |
Index | |
Newindex | |
Call | |
Tostring | |
Pairs | |
CustomOperation Name |
Instances
Show Operation | |
Eq Operation | |
Ord Operation | |
Defined in HsLua.ObjectOrientation.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 #
udDocs :: UDTypeWithList e fn a itemtype -> TypeDocs #
udTypeSpec :: UDTypeWithList e fn a itemtype -> TypeSpec #
Constructors
Property | |
Fields
|
data AliasIndex #
Constructors
StringIndex Name | |
IntegerIndex Integer |
Instances
IsString AliasIndex | |
Defined in HsLua.ObjectOrientation Methods fromString :: String -> AliasIndex | |
Eq AliasIndex | |
Defined in HsLua.ObjectOrientation | |
Ord AliasIndex | |
Defined in HsLua.ObjectOrientation Methods compare :: AliasIndex -> AliasIndex -> Ordering (<) :: AliasIndex -> AliasIndex -> Bool (<=) :: AliasIndex -> AliasIndex -> Bool (>) :: AliasIndex -> AliasIndex -> Bool (>=) :: AliasIndex -> AliasIndex -> Bool max :: AliasIndex -> AliasIndex -> AliasIndex min :: AliasIndex -> AliasIndex -> AliasIndex |
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
|
Constructors
Module | |
Fields
|
Constructors
Add | |
Sub | |
Mul | |
Div | |
Mod | |
Pow | |
Unm | |
Idiv | |
Band | |
Bor | |
Bxor | |
Bnot | |
Shl | |
Shr | |
Concat | |
Len | |
Eq | |
Lt | |
Le | |
Index | |
Newindex | |
Call | |
Tostring | |
Pairs | |
CustomOperation Name |
Instances
Show Operation | |
Eq Operation | |
Ord Operation | |
Defined in HsLua.ObjectOrientation.Operation |
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 #
textResult :: Text -> FunctionResults e Text #
documentation :: LuaError e => DocumentedFunction e #
getdocumentation :: LuaError e => StackIndex -> LuaE e Type #
pushFieldDoc :: LuaError e => Pusher e (Field e) #
pushFunctionDoc :: LuaError e => Pusher e (DocumentedFunction e) #
pushModuleDoc :: LuaError e => Pusher e (Module e) #
registerDocumentation :: LuaError e => StackIndex -> LuaE e () #
(###) :: (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a #
(#?) :: DocumentedFunction e -> Text -> DocumentedFunction e #
(<#>) :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b #
(=#>) :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e #
(=?>) :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e #
data FunctionResult e a #
Constructors
FunctionResult | |
Fields
|
type FunctionResults e a = [FunctionResult e a] #
data HsFnPrecursor e a #
Instances
Functor (HsFnPrecursor e) | |
Defined in HsLua.Packaging.Function Methods fmap :: (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b (<$) :: a -> HsFnPrecursor e b -> HsFnPrecursor e a |
Constructors
Parameter | |
Fields
|
applyParameter :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b #
defun :: Name -> a -> HsFnPrecursor e a #
functionResult :: Pusher e a -> TypeSpec -> Text -> FunctionResults e a #
lambda :: a -> HsFnPrecursor e a #
optionalParameter :: Peeker e a -> TypeSpec -> Text -> Text -> Parameter e (Maybe a) #
pushDocumentedFunction :: LuaError e => DocumentedFunction e -> LuaE e () #
returnResult :: HsFnPrecursor e (LuaE e a) -> FunctionResult e a -> DocumentedFunction e #
returnResults :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e #
returnResultsOnStack :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e #
setName :: Name -> DocumentedFunction e -> DocumentedFunction e #
since :: DocumentedFunction e -> Version -> DocumentedFunction e #
toHsFnPrecursor :: StackIndex -> Name -> a -> HsFnPrecursor e a #
updateFunctionDescription :: DocumentedFunction e -> Text -> DocumentedFunction e #
preloadModule :: LuaError e => Module e -> LuaE e () #
pushModule :: LuaError e => Module e -> LuaE e () #
registerModule :: LuaError e => Module e -> LuaE e () #
data DocumentedFunction e #
Constructors
DocumentedFunction | |
Fields
|
Constructors
Field | |
Fields
|
data FunctionDoc #
Constructors
FunctionDoc | |
Fields
|
Instances
Show FunctionDoc | |
Defined in HsLua.Packaging.Types Methods showsPrec :: Int -> FunctionDoc -> ShowS show :: FunctionDoc -> String showList :: [FunctionDoc] -> ShowS | |
Eq FunctionDoc | |
Defined in HsLua.Packaging.Types | |
Ord FunctionDoc | |
Defined in HsLua.Packaging.Types Methods compare :: FunctionDoc -> FunctionDoc -> Ordering (<) :: FunctionDoc -> FunctionDoc -> Bool (<=) :: FunctionDoc -> FunctionDoc -> Bool (>) :: FunctionDoc -> FunctionDoc -> Bool (>=) :: FunctionDoc -> FunctionDoc -> Bool max :: FunctionDoc -> FunctionDoc -> FunctionDoc min :: FunctionDoc -> FunctionDoc -> FunctionDoc |
data ParameterDoc #
Constructors
ParameterDoc | |
Fields
|
Instances
Show ParameterDoc | |
Defined in HsLua.Packaging.Types Methods showsPrec :: Int -> ParameterDoc -> ShowS show :: ParameterDoc -> String showList :: [ParameterDoc] -> ShowS | |
Eq ParameterDoc | |
Defined in HsLua.Packaging.Types | |
Ord ParameterDoc | |
Defined in HsLua.Packaging.Types Methods compare :: ParameterDoc -> ParameterDoc -> Ordering (<) :: ParameterDoc -> ParameterDoc -> Bool (<=) :: ParameterDoc -> ParameterDoc -> Bool (>) :: ParameterDoc -> ParameterDoc -> Bool (>=) :: ParameterDoc -> ParameterDoc -> Bool max :: ParameterDoc -> ParameterDoc -> ParameterDoc min :: ParameterDoc -> ParameterDoc -> ParameterDoc |
data ResultValueDoc #
Constructors
ResultValueDoc | |
Fields
|
Instances
Show ResultValueDoc | |
Defined in HsLua.Packaging.Types Methods showsPrec :: Int -> ResultValueDoc -> ShowS show :: ResultValueDoc -> String showList :: [ResultValueDoc] -> ShowS | |
Eq ResultValueDoc | |
Defined in HsLua.Packaging.Types Methods (==) :: ResultValueDoc -> ResultValueDoc -> Bool (/=) :: ResultValueDoc -> ResultValueDoc -> Bool | |
Ord ResultValueDoc | |
Defined in HsLua.Packaging.Types Methods compare :: ResultValueDoc -> ResultValueDoc -> Ordering (<) :: ResultValueDoc -> ResultValueDoc -> Bool (<=) :: ResultValueDoc -> ResultValueDoc -> Bool (>) :: ResultValueDoc -> ResultValueDoc -> Bool (>=) :: ResultValueDoc -> ResultValueDoc -> Bool max :: ResultValueDoc -> ResultValueDoc -> ResultValueDoc min :: ResultValueDoc -> ResultValueDoc -> ResultValueDoc |
data ResultsDoc #
Constructors
ResultsDocList [ResultValueDoc] | |
ResultsDocMult Text |
Instances
Show ResultsDoc | |
Defined in HsLua.Packaging.Types Methods showsPrec :: Int -> ResultsDoc -> ShowS show :: ResultsDoc -> String showList :: [ResultsDoc] -> ShowS | |
Eq ResultsDoc | |
Defined in HsLua.Packaging.Types | |
Ord ResultsDoc | |
Defined in HsLua.Packaging.Types Methods compare :: ResultsDoc -> ResultsDoc -> Ordering (<) :: ResultsDoc -> ResultsDoc -> Bool (<=) :: ResultsDoc -> ResultsDoc -> Bool (>) :: ResultsDoc -> ResultsDoc -> Bool (>=) :: ResultsDoc -> ResultsDoc -> Bool max :: ResultsDoc -> ResultsDoc -> ResultsDoc min :: ResultsDoc -> ResultsDoc -> ResultsDoc |
type DocumentedType e a = UDType e (DocumentedFunction e) a #
type DocumentedTypeWithList e a itemtype = UDTypeWithList e (DocumentedFunction e) a itemtype #
deftype :: LuaError e => Name -> [(Operation, DocumentedFunction e)] -> [Member e (DocumentedFunction e) a] -> DocumentedType e a #
deftype' :: LuaError e => Name -> [(Operation, DocumentedFunction e)] -> [Member e (DocumentedFunction e) a] -> Maybe (ListSpec e a itemtype) -> DocumentedTypeWithList e a itemtype #
method :: DocumentedFunction e -> Member e (DocumentedFunction e) a #
operation :: Operation -> DocumentedFunction e -> (Operation, DocumentedFunction e) #
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 #
udDocs :: UDTypeWithList e fn a itemtype -> TypeDocs #
udTypeSpec :: UDTypeWithList e fn a itemtype -> TypeSpec #
Type classes
class LuaError e => Exposable e a where #
Methods
partialApply :: StackIndex -> a -> Peek e NumResults #
Instances
LuaError e => Exposable e (HaskellFunction e) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> HaskellFunction e -> Peek e NumResults # | |
(LuaError e, Pushable a) => Exposable e (LuaE e a) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> LuaE e a -> Peek e NumResults # | |
(LuaError e, Pushable a) => Exposable e (Peek e a) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> Peek e a -> Peek e NumResults # | |
(Peekable a, Exposable e b) => Exposable e (a -> b) | |
Defined in HsLua.Class.Exposable Methods partialApply :: StackIndex -> (a -> b) -> Peek e NumResults # |
pushAsHaskellFunction :: Exposable e a => a -> LuaE e () #
registerHaskellFunction :: Exposable e a => Name -> a -> LuaE e () #
toHaskellFunction :: Exposable e a => a -> HaskellFunction e #
Instances
Instances
Marshal to and from JSON-like structures
peekToAeson :: Peeker e (ToAeson e) #
peekViaJSON :: (FromJSON a, LuaError e) => Peeker e a #
pushToAeson :: Pusher e (ToAeson e) #
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.
Constructors
Optional | |
Fields
|
peekEither :: (LuaError e, Peekable a) => StackIndex -> LuaE e (Either e a) #
raiseError :: (LuaError e, Pushable a) => a -> LuaE e NumResults #