| Copyright | (c) 2016 AlphaSheets Inc | 
|---|---|
| Stability | Experimental | 
| Portability | Portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Language.R.Matcher
Description
- newtype Matcher s a = Matcher {- runMatcher :: forall r. SomeSEXP s -> (a -> r) -> (MatcherError s -> r) -> r
 
- matchOnly :: (MonadR m, NFData a) => Matcher s a -> SomeSEXP s -> m (Either (MatcherError s) a)
- somesexp :: Matcher s (SomeSEXP s)
- sexp :: SSEXPTYPE ty -> Matcher s (SEXP s ty)
- with :: SomeSEXP s -> Matcher s a -> Matcher s a
- hexp :: SSEXPTYPE ty -> (HExp s ty -> Matcher s a) -> Matcher s a
- null :: Matcher s ()
- s4 :: Matcher s ()
- s3 :: [String] -> Matcher s ()
- guardType :: SEXPTYPE -> Matcher s ()
- typeOf :: Matcher s SEXPTYPE
- getS3Class :: Matcher s [String]
- someAttribute :: String -> Matcher s (SomeSEXP s)
- attribute :: SSEXPTYPE a -> String -> Matcher s (SEXP s a)
- attributes :: Matcher s (Maybe a) -> Matcher s [(String, a)]
- lookupAttribute :: String -> Matcher s (Maybe (SomeSEXP s))
- names :: Matcher s [String]
- dim :: Matcher s [Int]
- dimnames :: Matcher s [[String]]
- rownames :: Matcher s [String]
- factor :: Matcher s [String]
- charList :: SEXP s String -> [String]
- choice :: [Matcher s a] -> Matcher s a
- list :: Int -> Matcher s a -> Matcher s [a]
Documentation
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 
 | |
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.
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.
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.
Queries
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.