language-c-0.8: Analysis and generation of C code

Copyright(c) 2008 Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityexperimental
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Syntax.Ops

Contents

Description

Unary, binary and asssignment operators. Exported via AST.

Synopsis

Assignment operators

data CAssignOp Source #

C assignment operators (K&R A7.17)

Instances

Eq CAssignOp Source # 
Data CAssignOp Source # 

Methods

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

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

toConstr :: CAssignOp -> Constr #

dataTypeOf :: CAssignOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CAssignOp Source # 
Show CAssignOp Source # 
Generic CAssignOp Source # 

Associated Types

type Rep CAssignOp :: * -> * #

NFData CAssignOp Source # 

Methods

rnf :: CAssignOp -> () #

Pretty CAssignOp Source # 
type Rep CAssignOp Source # 
type Rep CAssignOp = D1 * (MetaData "CAssignOp" "Language.C.Syntax.Ops" "language-c-0.8-KoBDKGTf2gtDsoj7Q0ypyE" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CAssignOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CMulAssOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CDivAssOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CRmdAssOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CAddAssOp" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CSubAssOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CShlAssOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CShrAssOp" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "CAndAssOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CXorAssOp" PrefixI False) (U1 *)) (C1 * (MetaCons "COrAssOp" PrefixI False) (U1 *))))))

Binary operators

data CBinaryOp Source #

C binary operators (K&R A7.6-15)

Constructors

CMulOp 
CDivOp 
CRmdOp

remainder of division

CAddOp 
CSubOp 
CShlOp

shift left

CShrOp

shift right

CLeOp

less

CGrOp

greater

CLeqOp

less or equal

CGeqOp

greater or equal

CEqOp

equal

CNeqOp

not equal

CAndOp

bitwise and

CXorOp

exclusive bitwise or

COrOp

inclusive bitwise or

CLndOp

logical and

CLorOp

logical or

Instances

Eq CBinaryOp Source # 
Data CBinaryOp Source # 

Methods

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

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

toConstr :: CBinaryOp -> Constr #

dataTypeOf :: CBinaryOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CBinaryOp Source # 
Show CBinaryOp Source # 
Generic CBinaryOp Source # 

Associated Types

type Rep CBinaryOp :: * -> * #

NFData CBinaryOp Source # 

Methods

rnf :: CBinaryOp -> () #

Pretty CBinaryOp Source # 
type Rep CBinaryOp Source # 
type Rep CBinaryOp = D1 * (MetaData "CBinaryOp" "Language.C.Syntax.Ops" "language-c-0.8-KoBDKGTf2gtDsoj7Q0ypyE" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CMulOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CDivOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CRmdOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CAddOp" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CSubOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CShlOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CShrOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CLeOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CGrOp" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CLeqOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CGeqOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CEqOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CNeqOp" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CAndOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CXorOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "COrOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CLndOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CLorOp" PrefixI False) (U1 *)))))))

Unary operators

data CUnaryOp Source #

C unary operator (K&R A7.3-4)

Constructors

CPreIncOp

prefix increment operator

CPreDecOp

prefix decrement operator

CPostIncOp

postfix increment operator

CPostDecOp

postfix decrement operator

CAdrOp

address operator

CIndOp

indirection operator

CPlusOp

prefix plus

CMinOp

prefix minus

CCompOp

one's complement

CNegOp

logical negation

Instances

Eq CUnaryOp Source # 
Data CUnaryOp Source # 

Methods

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

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

toConstr :: CUnaryOp -> Constr #

dataTypeOf :: CUnaryOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CUnaryOp Source # 
Show CUnaryOp Source # 
Generic CUnaryOp Source # 

Associated Types

type Rep CUnaryOp :: * -> * #

Methods

from :: CUnaryOp -> Rep CUnaryOp x #

to :: Rep CUnaryOp x -> CUnaryOp #

NFData CUnaryOp Source # 

Methods

rnf :: CUnaryOp -> () #

Pretty CUnaryOp Source # 
type Rep CUnaryOp Source # 
type Rep CUnaryOp = D1 * (MetaData "CUnaryOp" "Language.C.Syntax.Ops" "language-c-0.8-KoBDKGTf2gtDsoj7Q0ypyE" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CPreIncOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CPreDecOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CPostIncOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CPostDecOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CAdrOp" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CIndOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CPlusOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CMinOp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CCompOp" PrefixI False) (U1 *)) (C1 * (MetaCons "CNegOp" PrefixI False) (U1 *))))))