hs-perl5-0.1.0: Haskell interface to embedded Perl 5 interpreter

Safe HaskellSafe
LanguageHaskell2010

Language.Perl

Contents

Description

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.

Synopsis

Perl calling context

Major types

data SV Source #

(pointer to a) scalar value.

Instances

Eq SV Source # 

Methods

(==) :: SV -> SV -> Bool #

(/=) :: SV -> SV -> Bool #

Show SV Source # 

Methods

showsPrec :: Int -> SV -> ShowS #

show :: SV -> String #

showList :: [SV] -> ShowS #

FromSV SV Source # 

Methods

fromSV :: SV -> IO SV Source #

ToSV SV Source # 

Methods

toSV :: SV -> IO SV Source #

Marshal values between Haskell and Perl

class ToSV a where Source #

Data types that can be cast to a Perl 5 value (SV).

Minimal complete definition

toSV

Methods

toSV :: a -> IO SV Source #

Instances

ToSV Bool Source # 

Methods

toSV :: Bool -> IO SV Source #

ToSV Int Source #

For convenience, a ToSV instance is provided for Ints. However, a Haskell Int on your platform might not be the same size as Perl's integral type - for an exact conversion, see the instance for IV.

Methods

toSV :: Int -> IO SV Source #

ToSV () Source # 

Methods

toSV :: () -> IO SV Source #

ToSV String Source # 

Methods

toSV :: String -> IO SV Source #

ToSV Text Source # 

Methods

toSV :: Text -> IO SV Source #

ToSV NV Source # 

Methods

toSV :: NV -> IO SV Source #

ToSV IV Source # 

Methods

toSV :: IV -> IO SV Source #

ToSV SV Source # 

Methods

toSV :: SV -> IO SV Source #

ToArgs a => ToSV (IO a) Source # 

Methods

toSV :: IO a -> IO SV Source #

(ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> a) Source # 

Methods

toSV :: (r1 -> r2 -> a) -> IO SV Source #

(ToArgs a, FromArgs r) => ToSV (r -> a) Source # 

Methods

toSV :: (r -> a) -> IO SV Source #

(ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> IO a) Source # 

Methods

toSV :: (r1 -> r2 -> IO a) -> IO SV Source #

(ToArgs a, FromArgs r) => ToSV (r -> IO a) Source # 

Methods

toSV :: (r -> IO a) -> IO SV Source #

class FromSV a where Source #

Data types that can be cast from a Perl 5 value (SV).

Minimal complete definition

fromSV

Methods

fromSV :: SV -> IO a Source #

Instances

FromSV Bool Source # 

Methods

fromSV :: SV -> IO Bool Source #

FromSV Int Source # 

Methods

fromSV :: SV -> IO Int Source #

FromSV () Source # 

Methods

fromSV :: SV -> IO () Source #

FromSV String Source # 

Methods

fromSV :: SV -> IO String Source #

FromSV Text Source # 

Methods

fromSV :: SV -> IO Text Source #

FromSV NV Source # 

Methods

fromSV :: SV -> IO NV Source #

FromSV IV Source # 

Methods

fromSV :: SV -> IO IV Source #

FromSV SV Source # 

Methods

fromSV :: SV -> IO SV Source #

FromArgs r => FromSV (IO r) Source # 

Methods

fromSV :: SV -> IO (IO r) Source #

(ToArgs a, ToArgs b, FromArgs r) => FromSV (a -> b -> IO r) Source # 

Methods

fromSV :: SV -> IO (a -> b -> IO r) Source #

(ToArgs a, FromArgs r) => FromSV (a -> IO r) Source # 

Methods

fromSV :: SV -> IO (a -> IO r) Source #

Safely run Perl things

withPerl :: IO a -> IO a Source #

Run a computation within the context of a Perl 5 interpreter.

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, FromArgs ret) => sub -> args -> IO ret Source #

alias for callSub

(.!) :: (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

eval :: forall a. FromArgs a => String -> IO a Source #

Evaluate a snippet of Perl 5 code.

eval_ :: String -> IO () Source #

Same as eval but always in void context.

utility functions

use :: String -> IO SV Source #

Use a module. Returns a prototype object representing the module.