inline-r-0.9.1: Seamlessly call R from Haskell and vice versa. No FFI required.

Copyright(c) 2016 AlphaSheets Inc
StabilityExperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Language.R.Matcher

Contents

Description

A Matcher lets you match SEXP values against composable patterns, where cascading cases would otherwise be necessary otherwise.

Example:

-- Check that input is an S3 object of class "matrix"
-- and return the value of the "dim" attribute.
isMatrix = matchOnly $ do
   s3 ["matrix"]
   dim

Synopsis

Documentation

newtype Matcher s a Source #

A composition of SEXP destructors. A Matcher is bound to the region where SomeSEXP is allocated, so extracted value will not leak out of the region scope.

This matcher is a pure function, so if you need to allocate any object (for example for comparison or lookup) you should do it before running matcher.

Constructors

Matcher 

Fields

Instances

Monad (Matcher s) Source # 

Methods

(>>=) :: Matcher s a -> (a -> Matcher s b) -> Matcher s b #

(>>) :: Matcher s a -> Matcher s b -> Matcher s b #

return :: a -> Matcher s a #

fail :: String -> Matcher s a #

Functor (Matcher s) Source # 

Methods

fmap :: (a -> b) -> Matcher s a -> Matcher s b #

(<$) :: a -> Matcher s b -> Matcher s a #

Applicative (Matcher s) Source # 

Methods

pure :: a -> Matcher s a #

(<*>) :: Matcher s (a -> b) -> Matcher s a -> Matcher s b #

liftA2 :: (a -> b -> c) -> Matcher s a -> Matcher s b -> Matcher s c #

(*>) :: Matcher s a -> Matcher s b -> Matcher s b #

(<*) :: Matcher s a -> Matcher s b -> Matcher s a #

Alternative (Matcher s) Source # 

Methods

empty :: Matcher s a #

(<|>) :: Matcher s a -> Matcher s a -> Matcher s a #

some :: Matcher s a -> Matcher s [a] #

many :: Matcher s a -> Matcher s [a] #

matchOnly :: (MonadR m, NFData a) => Matcher s a -> SomeSEXP s -> m (Either (MatcherError s) a) Source #

Match a SomeSEXP, returning a MatchError if matching failed.

Result is always fully evaluated, since otherwise it wouldn't be possible to guarantee that thunks in the return value will not escape the memory region.

Matcher interface.

The main functions of the matcher provide a simple way of accessing information about the current SomeSEXP. Those functions are useful if you use pure internal functions R functions to get information out of the data structure.

Another scenario is to use them in submatchers together with with combinator, that allow you to inspect the structure deeper without exiting the matcher.

somesexp :: Matcher s (SomeSEXP s) Source #

Returns current SomeSEXP. Never fails.

sexp :: SSEXPTYPE ty -> Matcher s (SEXP s ty) Source #

Returns current SEXP if it is of the requested type, fails otherwise, returns TypeMissmatch in that case.

with :: SomeSEXP s -> Matcher s a -> Matcher s a Source #

Run a submatcher on another SomeSEXP. All exceptions in the internal matcher are propagated to the parent one. This combinator allows to inspect nested structures without exiting the matcher, so it's possible to effectively combine it with alternative function.

Type guards

Guards provides a handy way to check if we are expecting object of the type we are interesting in.

hexp :: SSEXPTYPE ty -> (HExp s ty -> Matcher s a) -> Matcher s a Source #

hexp lifted to Matcher, applies hexp to the current value and allow to run internal matcher on it. Is useful when you need to inspect data using high level functions from Language.R.

null :: Matcher s () Source #

Succeeds if current SomeSEXP is Null.

s4 :: Matcher s () Source #

Succeeds if current SomeSEXP is S4 object. This check is more accurate then using guardType S4 as it uses internal R's function to check if the object is S4.

s3 :: [String] -> Matcher s () Source #

Succeeds if SomeSEXP is an S3 object of the given type. In general case it's better to use getS3Class because it will run same check, but also will return the class(es) of the current expression.

This test is not expressible in terms of the guardType, becausee guardType does not see additional information about S3 types. And any raw object can be a class instance.

guardType :: SEXPTYPE -> Matcher s () Source #

Continue execution if SEXP have required type. This check tests basic types of the expression like if it's integer, or real or character vector and such. If you need to test object type use s3 or s4 directly.

Queries

typeOf :: Matcher s SEXPTYPE Source #

Returns type of the current SEXP. Can never fail.

getS3Class :: Matcher s [String] Source #

Return the class of the S3 object, fails otherwise.

Attributes

Attributes are additional data that can be attached to any R value. Attributes may be seen as a Map Text (SomeSEXP s0). Attributes may add additional information to the data that may completely change it's meaning. For example by adding dim attribute matrix or array can be created out of vector, or factors are presented as an interger vector with rownames attribute attached.

someAttribute :: String -> Matcher s (SomeSEXP s) Source #

Returns any attribute by it's name if it exists. Fails with NoSuchAttribute otherwise.

attribute :: SSEXPTYPE a -> String -> Matcher s (SEXP s a) Source #

Typed version of the someAttribute call. In addition to retrieving value it's dynamically type checked.

attributes :: Matcher s (Maybe a) -> Matcher s [(String, a)] Source #

Match all attributes, takes a matcher and applies it to the each attribute exists, returns list of the attribute name, together with matcher result. If matcher returns Nothing - result is omitted..

lookupAttribute :: String -> Matcher s (Maybe (SomeSEXP s)) Source #

Find an attribute in attribute list if it exists.

Attribute matchers

names :: Matcher s [String] Source #

Get names attribute.

dim :: Matcher s [Int] Source #

Get dim attribute.

dimnames :: Matcher s [[String]] Source #

Get dimnames attribute.

rownames :: Matcher s [String] Source #

Get rownames attribute.

Derived matchers

factor :: Matcher s [String] Source #

Match a factor. Returns the levels of the factor.

Helpers

charList :: SEXP s String -> [String] Source #

Convert String SEXP to the list of Strings.

choice :: [Matcher s a] -> Matcher s a Source #

Execute first matcher that will not fail.

list Source #

Arguments

:: Int

Upper bound on number of elements to match.

-> Matcher s a

Matcher to apply to each element

-> Matcher s [a] 

Matches a List object.