fortran-vars-0.3.0: Fortran memory model and other static analysis tools.
Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Vars.CPValue

Synopsis

Documentation

data CPValue Source #

CPValue (Constant Propagation Value) represnts the value of an expression determined by constant propagation analysis. The value can be uninitialized, a constant, or unknown due to conflict. The data type is represented with ExpVal together with two special values: Top represents uninitialized value and is the least upper bound Bot represents unknown and is the greatest lower bound Top, Const, and Bot forms a lattice strucutre with meet operation defined below

Constructors

Top

represents uninitialized value

Const ExpVal

represents a constant value

Bot

short for bottom, represents unknown value

Instances

Instances details
Eq CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

Methods

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

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

Data CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

Methods

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

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

toConstr :: CPValue -> Constr #

dataTypeOf :: CPValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

Show CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

Generic CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

Associated Types

type Rep CPValue :: Type -> Type #

Methods

from :: CPValue -> Rep CPValue x #

to :: Rep CPValue x -> CPValue #

NFData CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

Methods

rnf :: CPValue -> () #

type Rep CPValue Source # 
Instance details

Defined in Language.Fortran.Vars.CPValue

type Rep CPValue = D1 ('MetaData "CPValue" "Language.Fortran.Vars.CPValue" "fortran-vars-0.3.0-inplace" 'False) (C1 ('MetaCons "Top" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Const" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExpVal)) :+: C1 ('MetaCons "Bot" 'PrefixI 'False) (U1 :: Type -> Type)))

meet :: CPValue -> CPValue -> CPValue Source #

meet operation for CPValue lattice. meet of two different constant value indicates conflict, therefore yields Bot.