HsPerl5-0.0.6: Haskell interface to embedded Perl 5 interpreter

Language.Perl5

Synopsis

Documentation

data Context Source

Perl 5's calling context.

Constructors

Void 
Item 
List 

class ToSV a whereSource

Data types that can be casted into a Perl 5 value (SV).

Methods

toSV :: a -> IO SVSource

Instances

ToSV Bool 
ToSV Double 
ToSV Int 
ToSV String 
ToSV () 
ToSV SV 
ToArgs a => ToSV (IO a) 
(ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> a) 
(ToArgs a, FromArgs r) => ToSV (r -> a) 
(ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> IO a) 
(ToArgs a, FromArgs r) => ToSV (r -> IO a) 

class FromSV a whereSource

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

Methods

fromSV :: SV -> IO aSource

Instances

FromSV Bool 
FromSV Double 
FromSV Int 
FromSV String 
FromSV () 
FromSV SV 
FromArgs r => FromSV (IO r) 
(ToArgs a, ToArgs b, FromArgs r) => FromSV (a -> b -> IO r) 
(ToArgs a, FromArgs r) => FromSV (a -> IO r) 

withPerl5 :: IO a -> IO aSource

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

callSub :: forall s a r. (ToCV s, ToArgs a, FromArgs r) => s -> a -> IO rSource

Call a Perl 5 subroutine.

(.:) :: (ToCV sub, ToArgs args, FromArgs ret) => sub -> args -> IO retSource

(.!) :: (ToCV sub, ToArgs args) => sub -> args -> IO ()Source

callMethod :: forall i m a r. (ToSV i, ToSV m, ToArgs a, FromArgs r) => i -> m -> a -> IO rSource

Call a Perl 5 method.

(.$) :: (ToSV meth, ToArgs args, FromArgs ret) => SV -> meth -> args -> IO retSource

(.$!) :: (ToSV meth, ToArgs args) => SV -> meth -> args -> IO ()Source

eval :: forall a. FromArgs a => String -> IO aSource

Evaluate a snippet of Perl 5 code.

eval_ :: String -> IO ()Source

Same as eval but always in void context.

type SV = Ptr ()Source

use :: String -> IO SVSource

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