Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Interact with embedded Perl interpreter.
Interpreter instance
Pretty much any function in this module will only operated correctly if a
properly initialized interpreter instance exists -- that is,
the function hsperl_init
has been called. You don't
have to pass the resulting Interpreter
to the functions, typically --
rather, calling hsperl_init
has the side effect
of initializing various global variables needed by Perl.
Normally, only one interpreter instance can exist at a time
(unless your Perl library has been specially compiled to allow for multiple
instances -- see perlembed).
For convenience, a bracket
-like function is provided, withPerl
, which creates
an interpreter using hsperl_init
, cleans up afterwards using
perl_destruct
, and runs your IO
actions in between.
Calling withPerl
creates an Interpreter
instance that is
equivalent to running
perl -e ""
at the command-line.
- data Context
- data SV
- class ToSV a where
- class FromSV a where
- withPerl :: IO a -> IO a
- callSub :: forall s a r. (ToCV s, ToArgs a, FromArgs r) => s -> a -> IO r
- (.:) :: (ToCV sub, ToArgs args, FromArgs ret) => sub -> args -> IO ret
- (.!) :: (ToCV sub, ToArgs args) => sub -> args -> IO ()
- callMethod :: forall i m a r. (ToSV i, ToSV m, ToArgs a, FromArgs r) => i -> m -> a -> IO r
- (.$) :: (ToSV meth, ToArgs args, FromArgs ret) => SV -> meth -> args -> IO ret
- (.$!) :: (ToSV meth, ToArgs args) => SV -> meth -> args -> IO ()
- eval :: forall a. FromArgs a => String -> IO a
- eval_ :: String -> IO ()
- use :: String -> IO SV
Perl calling context
Perl's calling context.
Major types
(pointer to a) scalar value.
Marshal values between Haskell and Perl
Data types that can be cast to a Perl 5 value (SV).
ToSV Bool Source # | |
ToSV Int Source # | For convenience, a |
ToSV () Source # | |
ToSV String Source # | |
ToSV Text Source # | |
ToSV NV Source # | |
ToSV IV Source # | |
ToSV SV Source # | |
ToArgs a => ToSV (IO a) Source # | |
(ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> a) Source # | |
(ToArgs a, FromArgs r) => ToSV (r -> a) Source # | |
(ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> IO a) Source # | |
(ToArgs a, FromArgs r) => ToSV (r -> IO a) Source # | |
Data types that can be cast from a Perl 5 value (SV).
FromSV Bool Source # | |
FromSV Int Source # | |
FromSV () Source # | |
FromSV String Source # | |
FromSV Text Source # | |
FromSV NV Source # | |
FromSV IV Source # | |
FromSV SV Source # | |
FromArgs r => FromSV (IO r) Source # | |
(ToArgs a, ToArgs b, FromArgs r) => FromSV (a -> b -> IO r) Source # | |
(ToArgs a, FromArgs r) => FromSV (a -> IO r) Source # | |
Safely run Perl things
evaluate in a Perl context
callSub :: forall s a r. (ToCV s, ToArgs a, FromArgs r) => s -> a -> IO r Source #
Call a Perl 5 subroutine.
(.!) :: (ToCV sub, ToArgs args) => sub -> args -> IO () Source #
version of callSub
that returns no result
callMethod :: forall i m a r. (ToSV i, ToSV m, ToArgs a, FromArgs r) => i -> m -> a -> IO r Source #
Call a Perl 5 method.
(.$) :: (ToSV meth, ToArgs args, FromArgs ret) => SV -> meth -> args -> IO ret Source #
alias for callMethod
(.$!) :: (ToSV meth, ToArgs args) => SV -> meth -> args -> IO () Source #
version of callMethod
that returns no result