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

Safe HaskellSafe
LanguageHaskell2010

Language.Perl.Internal.Types

Contents

Description

Types for interfacing with an embedded Perl interpreter.

Synopsis

main types

newtype Interpreter Source #

(pointer to a) Perl interpreter instance.

Constructors

Interpreter 

newtype SV Source #

(pointer to a) scalar value.

Constructors

SV 

Fields

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 #

newtype AV Source #

(pointer to an) array value.

Constructors

AV 

Fields

Instances

Eq AV Source # 

Methods

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

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

Show AV Source # 

Methods

showsPrec :: Int -> AV -> ShowS #

show :: AV -> String #

showList :: [AV] -> ShowS #

newtype CV Source #

(pointer to a) code value.

Constructors

CV 

Fields

Instances

Eq CV Source # 

Methods

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

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

Show CV Source # 

Methods

showsPrec :: Int -> CV -> ShowS #

show :: CV -> String #

showList :: [CV] -> ShowS #

type Callback = Ptr SV -> CInt -> IO (Ptr SV) Source #

type of a callback from Perl into Haskell.

Underlying C types

type IV = Int64 Source #

Underlying C integer type used by Perl. ("IV" = "Integer value".)

type NV = Double Source #

Underlying C floating-point type used by Perl. ("NV" = "Numeric value".)

Perl calling context

numContext :: (Eq p, Num p) => Context -> p Source #

Convert a Context to an integral value that can be passed to the C API.

Used by the various "call_..." and "eval_..." Perl functions (which then pass it on to whatever code is being called).

ptr-to-ptr utility functions

the downside of the "newtype X = X (Ptr X)" approach is that working with arrays of ptrs-to-X becomes more fiddly.

So we define a few helper functions for working with arrays-of-ptrs-to-SVs.

asSVList :: Ptr SV -> IO [SV] Source #

convert a NULL terminated "array of pointers" (ptr-to-ptr-to-SV) to a list of SVs.

wrapper around "peekArray nullPtr"

svTail :: Ptr a -> IO [SV] Source #

advance one el, and get the "tail" of an "array of pointers".

wrapper around advancePtr 1 fed into peekArray0 nullPtr

svEither :: Ptr SV -> IO (Either [SV] [SV]) Source #

return either the error list, or the result list from an array of pointers.

mkSVList :: [SV] -> IO (Ptr SV) Source #

Make a NULL-terminated array of SVs.

Wrapper around 'newArray0 nullPtr'

withSVArray :: [SV] -> (Ptr SV -> IO b) -> IO b Source #

temporarily marshal a list of SVs into a NULL-terminated array, and perform some action with them.

Wrapper around withArray0.