Copyright | (c) Masahiro Sakai 2013 |
---|---|
License | BSD-style |
Maintainer | masahiro.sakai@gmail.com |
Stability | provisional |
Portability | non-portable (FlexibleInstances, DeriveDataTypeable, CPP) |
Safe Haskell | Safe |
Language | Haskell2010 |
Data.Sign
Description
This module provides arithmetic over signs (i.e. {-, 0, +}) and set of signs.
For the purpose of abstract interpretation, it might be convenient to use
Lattice
instance. See also lattices package
(http://hackage.haskell.org/package/lattices).
The Sign data type
Signs of real numbers.
Instances
Bounded Sign Source # | |
Enum Sign Source # | |
Eq Sign Source # | |
Data Sign Source # | |
Defined in Data.Sign Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sign -> c Sign # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sign # dataTypeOf :: Sign -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Sign) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sign) # gmapT :: (forall b. Data b => b -> b) -> Sign -> Sign # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r # gmapQ :: (forall d. Data d => d -> u) -> Sign -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sign -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sign -> m Sign # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign # | |
Ord Sign Source # | |
Read Sign Source # | |
Show Sign Source # | |
NFData Sign Source # | |
Hashable Sign Source # | |
Universe Sign Source # | |
Finite Sign Source # | |
Fractional (Set Sign) Source # | |
Num (Set Sign) Source # | |
Operations over signs
Operations over sets of signs
is equipped with instances of Set
Sign
Num
and Fractional
.
Therefore arithmetic operations can be applied to
.Set
Sign
Instances of Lattice
and BoundedLattice
are also provided for
the purpose of abstract interpretation.