forsyde-deep-0.2.0: ForSyDe's Haskell-embedded Domain Specific Language.

Copyright(c) ES Group, KTH/ICT/ES 2007-2013
LicenseBSD-style (see the file LICENSE)
Maintainerforsyde-dev@ict.kth.se
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

ForSyDe.Deep.AbsentExt

Description

The AbstExt is used to extend existing data types with the value 'absent', which models the absence of a value.

Synopsis

Documentation

data AbstExt a Source #

The data type AbstExt has two constructors. The constructor Abst is used to model the absence of a value, while the constructor Prst is used to model present values.

Constructors

Abst 
Prst a 

Instances

Eq a => Eq (AbstExt a) Source # 

Methods

(==) :: AbstExt a -> AbstExt a -> Bool #

(/=) :: AbstExt a -> AbstExt a -> Bool #

Data a => Data (AbstExt a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbstExt a -> c (AbstExt a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AbstExt a) #

toConstr :: AbstExt a -> Constr #

dataTypeOf :: AbstExt a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (AbstExt a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AbstExt a)) #

gmapT :: (forall b. Data b => b -> b) -> AbstExt a -> AbstExt a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbstExt a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbstExt a -> r #

gmapQ :: (forall d. Data d => d -> u) -> AbstExt a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AbstExt a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbstExt a -> m (AbstExt a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbstExt a -> m (AbstExt a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbstExt a -> m (AbstExt a) #

Read a => Read (AbstExt a) Source # 
Show a => Show (AbstExt a) Source #

The data type AbstExt is defined as an instance of Show and Read. '_' represents the value Abst while a present value is represented with its value, e.g. Prst 1 is represented as '1'.

Methods

showsPrec :: Int -> AbstExt a -> ShowS #

show :: AbstExt a -> String #

showList :: [AbstExt a] -> ShowS #

Lift a0 => Lift (AbstExt a0) Source # 

Methods

lift :: AbstExt a0 -> Q Exp #

fromAbstExt Source #

Arguments

:: a

Default value returned if the input is Abst

-> AbstExt a 
-> a 

The function fromAbstExt extracts the inner value contained in AbstExt

unsafeFromAbstExt :: AbstExt a -> a Source #

Similar to fromAbstExt, but without default value

abstExt :: a -> AbstExt a Source #

The function abstExt converts a usual value to a present value.

psi :: (a -> b) -> AbstExt a -> AbstExt b Source #

The function psi is identical to abstExtFunc and should be used in future.

isAbsent :: AbstExt a -> Bool Source #

The functions isAbsent checks for the absence of a value.

isPresent :: AbstExt a -> Bool Source #

The functions isPresent checks for the presence of a value.

abstExtFunc :: (a -> b) -> AbstExt a -> AbstExt b Source #

The function abstExtFunc extends a function in order to process absent extended values. If the input is ("bottom"), the output will also be ("bottom").