{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Language.C.Syntax.AST (
CTranslUnit, CExtDecl,
CTranslationUnit(..), CExternalDeclaration(..),
CFunDef, CDecl, CStructUnion, CEnum,
CFunctionDef(..), CDeclaration(..),
CStructTag(..), CStructureUnion(..), CEnumeration(..),
CDeclSpec, partitionDeclSpecs,
CStorageSpec, CTypeSpec, isSUEDef, CTypeQual, CFunSpec, CAlignSpec, CAttr,
CFunctionSpecifier(..), CDeclarationSpecifier(..), CStorageSpecifier(..), CTypeSpecifier(..),
CAlignmentSpecifier(..),
CTypeQualifier(..), CAttribute(..),
CDeclr,CDerivedDeclr,CArrSize,
CDeclarator(..), CDerivedDeclarator(..), CArraySize(..),
CInit, CInitList, CDesignator,
CInitializer(..), CInitializerList, CPartDesignator(..),
CStat, CBlockItem, CAsmStmt, CAsmOperand,
CStatement(..), CCompoundBlockItem(..),
CAssemblyStatement(..), CAssemblyOperand(..),
CExpr, CExpression(..),
CAssignOp(..), CBinaryOp(..), CUnaryOp(..),
CBuiltin, CBuiltinThing(..),
CConst, CStrLit, cstringOfLit, liftStrLit,
CConstant(..), CStringLiteral(..),
Annotated(..)
) where
import Language.C.Syntax.Constants
import Language.C.Syntax.Ops
import Language.C.Data.Ident
import Language.C.Data.Node
import Language.C.Data.Position
import Data.Data (Data)
import Data.Typeable (Typeable)
import GHC.Generics (Generic, Generic1)
import Control.DeepSeq (NFData)
type CTranslUnit = CTranslationUnit NodeInfo
data CTranslationUnit a
= CTranslUnit [CExternalDeclaration a] a
deriving (Int -> CTranslationUnit a -> ShowS
[CTranslationUnit a] -> ShowS
CTranslationUnit a -> String
(Int -> CTranslationUnit a -> ShowS)
-> (CTranslationUnit a -> String)
-> ([CTranslationUnit a] -> ShowS)
-> Show (CTranslationUnit a)
forall a. Show a => Int -> CTranslationUnit a -> ShowS
forall a. Show a => [CTranslationUnit a] -> ShowS
forall a. Show a => CTranslationUnit a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CTranslationUnit a -> ShowS
showsPrec :: Int -> CTranslationUnit a -> ShowS
$cshow :: forall a. Show a => CTranslationUnit a -> String
show :: CTranslationUnit a -> String
$cshowList :: forall a. Show a => [CTranslationUnit a] -> ShowS
showList :: [CTranslationUnit a] -> ShowS
Show, Typeable (CTranslationUnit a)
Typeable (CTranslationUnit a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> c (CTranslationUnit a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTranslationUnit a))
-> (CTranslationUnit a -> Constr)
-> (CTranslationUnit a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTranslationUnit a)))
-> ((forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CTranslationUnit a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CTranslationUnit a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a))
-> Data (CTranslationUnit a)
CTranslationUnit a -> Constr
CTranslationUnit a -> DataType
(forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
forall a. Data a => Typeable (CTranslationUnit a)
forall a. Data a => CTranslationUnit a -> Constr
forall a. Data a => CTranslationUnit a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CTranslationUnit a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTranslationUnit a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTranslationUnit a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> c (CTranslationUnit a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTranslationUnit a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CTranslationUnit a -> u
forall u. (forall d. Data d => d -> u) -> CTranslationUnit a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTranslationUnit a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> c (CTranslationUnit a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTranslationUnit a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> c (CTranslationUnit a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> c (CTranslationUnit a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTranslationUnit a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTranslationUnit a)
$ctoConstr :: forall a. Data a => CTranslationUnit a -> Constr
toConstr :: CTranslationUnit a -> Constr
$cdataTypeOf :: forall a. Data a => CTranslationUnit a -> DataType
dataTypeOf :: CTranslationUnit a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTranslationUnit a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTranslationUnit a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
gmapT :: (forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTranslationUnit a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CTranslationUnit a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CTranslationUnit a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CTranslationUnit a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
Data, Typeable, (forall x. CTranslationUnit a -> Rep (CTranslationUnit a) x)
-> (forall x. Rep (CTranslationUnit a) x -> CTranslationUnit a)
-> Generic (CTranslationUnit a)
forall x. Rep (CTranslationUnit a) x -> CTranslationUnit a
forall x. CTranslationUnit a -> Rep (CTranslationUnit a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CTranslationUnit a) x -> CTranslationUnit a
forall a x. CTranslationUnit a -> Rep (CTranslationUnit a) x
$cfrom :: forall a x. CTranslationUnit a -> Rep (CTranslationUnit a) x
from :: forall x. CTranslationUnit a -> Rep (CTranslationUnit a) x
$cto :: forall a x. Rep (CTranslationUnit a) x -> CTranslationUnit a
to :: forall x. Rep (CTranslationUnit a) x -> CTranslationUnit a
Generic, (forall a. CTranslationUnit a -> Rep1 CTranslationUnit a)
-> (forall a. Rep1 CTranslationUnit a -> CTranslationUnit a)
-> Generic1 CTranslationUnit
forall a. Rep1 CTranslationUnit a -> CTranslationUnit a
forall a. CTranslationUnit a -> Rep1 CTranslationUnit a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CTranslationUnit a -> Rep1 CTranslationUnit a
from1 :: forall a. CTranslationUnit a -> Rep1 CTranslationUnit a
$cto1 :: forall a. Rep1 CTranslationUnit a -> CTranslationUnit a
to1 :: forall a. Rep1 CTranslationUnit a -> CTranslationUnit a
Generic1 )
instance NFData a => NFData (CTranslationUnit a)
type CExtDecl = CExternalDeclaration NodeInfo
data CExternalDeclaration a
= CDeclExt (CDeclaration a)
| CFDefExt (CFunctionDef a)
| CAsmExt (CStringLiteral a) a
deriving (Int -> CExternalDeclaration a -> ShowS
[CExternalDeclaration a] -> ShowS
CExternalDeclaration a -> String
(Int -> CExternalDeclaration a -> ShowS)
-> (CExternalDeclaration a -> String)
-> ([CExternalDeclaration a] -> ShowS)
-> Show (CExternalDeclaration a)
forall a. Show a => Int -> CExternalDeclaration a -> ShowS
forall a. Show a => [CExternalDeclaration a] -> ShowS
forall a. Show a => CExternalDeclaration a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CExternalDeclaration a -> ShowS
showsPrec :: Int -> CExternalDeclaration a -> ShowS
$cshow :: forall a. Show a => CExternalDeclaration a -> String
show :: CExternalDeclaration a -> String
$cshowList :: forall a. Show a => [CExternalDeclaration a] -> ShowS
showList :: [CExternalDeclaration a] -> ShowS
Show, Typeable (CExternalDeclaration a)
Typeable (CExternalDeclaration a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> c (CExternalDeclaration a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExternalDeclaration a))
-> (CExternalDeclaration a -> Constr)
-> (CExternalDeclaration a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (CExternalDeclaration a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExternalDeclaration a)))
-> ((forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> CExternalDeclaration a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CExternalDeclaration a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a))
-> Data (CExternalDeclaration a)
CExternalDeclaration a -> Constr
CExternalDeclaration a -> DataType
(forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
forall a. Data a => Typeable (CExternalDeclaration a)
forall a. Data a => CExternalDeclaration a -> Constr
forall a. Data a => CExternalDeclaration a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CExternalDeclaration a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CExternalDeclaration a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExternalDeclaration a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> c (CExternalDeclaration a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExternalDeclaration a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CExternalDeclaration a -> u
forall u.
(forall d. Data d => d -> u) -> CExternalDeclaration a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExternalDeclaration a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> c (CExternalDeclaration a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExternalDeclaration a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> c (CExternalDeclaration a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> c (CExternalDeclaration a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExternalDeclaration a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExternalDeclaration a)
$ctoConstr :: forall a. Data a => CExternalDeclaration a -> Constr
toConstr :: CExternalDeclaration a -> Constr
$cdataTypeOf :: forall a. Data a => CExternalDeclaration a -> DataType
dataTypeOf :: CExternalDeclaration a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExternalDeclaration a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExternalDeclaration a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
gmapT :: (forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CExternalDeclaration a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CExternalDeclaration a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CExternalDeclaration a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CExternalDeclaration a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
Data,Typeable, (forall x.
CExternalDeclaration a -> Rep (CExternalDeclaration a) x)
-> (forall x.
Rep (CExternalDeclaration a) x -> CExternalDeclaration a)
-> Generic (CExternalDeclaration a)
forall x. Rep (CExternalDeclaration a) x -> CExternalDeclaration a
forall x. CExternalDeclaration a -> Rep (CExternalDeclaration a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (CExternalDeclaration a) x -> CExternalDeclaration a
forall a x.
CExternalDeclaration a -> Rep (CExternalDeclaration a) x
$cfrom :: forall a x.
CExternalDeclaration a -> Rep (CExternalDeclaration a) x
from :: forall x. CExternalDeclaration a -> Rep (CExternalDeclaration a) x
$cto :: forall a x.
Rep (CExternalDeclaration a) x -> CExternalDeclaration a
to :: forall x. Rep (CExternalDeclaration a) x -> CExternalDeclaration a
Generic, (forall a. CExternalDeclaration a -> Rep1 CExternalDeclaration a)
-> (forall a.
Rep1 CExternalDeclaration a -> CExternalDeclaration a)
-> Generic1 CExternalDeclaration
forall a. Rep1 CExternalDeclaration a -> CExternalDeclaration a
forall a. CExternalDeclaration a -> Rep1 CExternalDeclaration a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CExternalDeclaration a -> Rep1 CExternalDeclaration a
from1 :: forall a. CExternalDeclaration a -> Rep1 CExternalDeclaration a
$cto1 :: forall a. Rep1 CExternalDeclaration a -> CExternalDeclaration a
to1 :: forall a. Rep1 CExternalDeclaration a -> CExternalDeclaration a
Generic1 )
instance NFData a => NFData (CExternalDeclaration a)
type CFunDef = CFunctionDef NodeInfo
data CFunctionDef a
= CFunDef
[CDeclarationSpecifier a]
(CDeclarator a)
[CDeclaration a]
(CStatement a)
a
deriving (Int -> CFunctionDef a -> ShowS
[CFunctionDef a] -> ShowS
CFunctionDef a -> String
(Int -> CFunctionDef a -> ShowS)
-> (CFunctionDef a -> String)
-> ([CFunctionDef a] -> ShowS)
-> Show (CFunctionDef a)
forall a. Show a => Int -> CFunctionDef a -> ShowS
forall a. Show a => [CFunctionDef a] -> ShowS
forall a. Show a => CFunctionDef a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CFunctionDef a -> ShowS
showsPrec :: Int -> CFunctionDef a -> ShowS
$cshow :: forall a. Show a => CFunctionDef a -> String
show :: CFunctionDef a -> String
$cshowList :: forall a. Show a => [CFunctionDef a] -> ShowS
showList :: [CFunctionDef a] -> ShowS
Show, Typeable (CFunctionDef a)
Typeable (CFunctionDef a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> c (CFunctionDef a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionDef a))
-> (CFunctionDef a -> Constr)
-> (CFunctionDef a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionDef a)))
-> ((forall b. Data b => b -> b)
-> CFunctionDef a -> CFunctionDef a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CFunctionDef a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CFunctionDef a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a))
-> Data (CFunctionDef a)
CFunctionDef a -> Constr
CFunctionDef a -> DataType
(forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
forall a. Data a => Typeable (CFunctionDef a)
forall a. Data a => CFunctionDef a -> Constr
forall a. Data a => CFunctionDef a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CFunctionDef a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CFunctionDef a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionDef a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> c (CFunctionDef a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionDef a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CFunctionDef a -> u
forall u. (forall d. Data d => d -> u) -> CFunctionDef a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionDef a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> c (CFunctionDef a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionDef a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> c (CFunctionDef a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> c (CFunctionDef a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionDef a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionDef a)
$ctoConstr :: forall a. Data a => CFunctionDef a -> Constr
toConstr :: CFunctionDef a -> Constr
$cdataTypeOf :: forall a. Data a => CFunctionDef a -> DataType
dataTypeOf :: CFunctionDef a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionDef a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionDef a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
gmapT :: (forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CFunctionDef a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CFunctionDef a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CFunctionDef a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CFunctionDef a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
Data,Typeable, (forall x. CFunctionDef a -> Rep (CFunctionDef a) x)
-> (forall x. Rep (CFunctionDef a) x -> CFunctionDef a)
-> Generic (CFunctionDef a)
forall x. Rep (CFunctionDef a) x -> CFunctionDef a
forall x. CFunctionDef a -> Rep (CFunctionDef a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CFunctionDef a) x -> CFunctionDef a
forall a x. CFunctionDef a -> Rep (CFunctionDef a) x
$cfrom :: forall a x. CFunctionDef a -> Rep (CFunctionDef a) x
from :: forall x. CFunctionDef a -> Rep (CFunctionDef a) x
$cto :: forall a x. Rep (CFunctionDef a) x -> CFunctionDef a
to :: forall x. Rep (CFunctionDef a) x -> CFunctionDef a
Generic, (forall a. CFunctionDef a -> Rep1 CFunctionDef a)
-> (forall a. Rep1 CFunctionDef a -> CFunctionDef a)
-> Generic1 CFunctionDef
forall a. Rep1 CFunctionDef a -> CFunctionDef a
forall a. CFunctionDef a -> Rep1 CFunctionDef a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CFunctionDef a -> Rep1 CFunctionDef a
from1 :: forall a. CFunctionDef a -> Rep1 CFunctionDef a
$cto1 :: forall a. Rep1 CFunctionDef a -> CFunctionDef a
to1 :: forall a. Rep1 CFunctionDef a -> CFunctionDef a
Generic1 )
instance NFData a => NFData (CFunctionDef a)
type CDecl = CDeclaration NodeInfo
data CDeclaration a
= CDecl
[CDeclarationSpecifier a]
[(Maybe (CDeclarator a),
Maybe (CInitializer a),
Maybe (CExpression a))]
a
| CStaticAssert
(CExpression a)
(CStringLiteral a)
a
deriving (Int -> CDeclaration a -> ShowS
[CDeclaration a] -> ShowS
CDeclaration a -> String
(Int -> CDeclaration a -> ShowS)
-> (CDeclaration a -> String)
-> ([CDeclaration a] -> ShowS)
-> Show (CDeclaration a)
forall a. Show a => Int -> CDeclaration a -> ShowS
forall a. Show a => [CDeclaration a] -> ShowS
forall a. Show a => CDeclaration a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CDeclaration a -> ShowS
showsPrec :: Int -> CDeclaration a -> ShowS
$cshow :: forall a. Show a => CDeclaration a -> String
show :: CDeclaration a -> String
$cshowList :: forall a. Show a => [CDeclaration a] -> ShowS
showList :: [CDeclaration a] -> ShowS
Show, Typeable (CDeclaration a)
Typeable (CDeclaration a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> c (CDeclaration a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclaration a))
-> (CDeclaration a -> Constr)
-> (CDeclaration a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclaration a)))
-> ((forall b. Data b => b -> b)
-> CDeclaration a -> CDeclaration a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CDeclaration a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CDeclaration a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a))
-> Data (CDeclaration a)
CDeclaration a -> Constr
CDeclaration a -> DataType
(forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
forall a. Data a => Typeable (CDeclaration a)
forall a. Data a => CDeclaration a -> Constr
forall a. Data a => CDeclaration a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDeclaration a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclaration a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclaration a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> c (CDeclaration a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclaration a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CDeclaration a -> u
forall u. (forall d. Data d => d -> u) -> CDeclaration a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclaration a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> c (CDeclaration a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclaration a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> c (CDeclaration a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> c (CDeclaration a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclaration a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclaration a)
$ctoConstr :: forall a. Data a => CDeclaration a -> Constr
toConstr :: CDeclaration a -> Constr
$cdataTypeOf :: forall a. Data a => CDeclaration a -> DataType
dataTypeOf :: CDeclaration a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclaration a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclaration a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
gmapT :: (forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclaration a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CDeclaration a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDeclaration a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CDeclaration a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
Data,Typeable, (forall x. CDeclaration a -> Rep (CDeclaration a) x)
-> (forall x. Rep (CDeclaration a) x -> CDeclaration a)
-> Generic (CDeclaration a)
forall x. Rep (CDeclaration a) x -> CDeclaration a
forall x. CDeclaration a -> Rep (CDeclaration a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CDeclaration a) x -> CDeclaration a
forall a x. CDeclaration a -> Rep (CDeclaration a) x
$cfrom :: forall a x. CDeclaration a -> Rep (CDeclaration a) x
from :: forall x. CDeclaration a -> Rep (CDeclaration a) x
$cto :: forall a x. Rep (CDeclaration a) x -> CDeclaration a
to :: forall x. Rep (CDeclaration a) x -> CDeclaration a
Generic )
instance NFData a => NFData (CDeclaration a)
instance Functor CDeclaration where
fmap :: forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
fmap a -> b
f (CDecl [CDeclarationSpecifier a]
specs [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
declarators a
annot) =
[CDeclarationSpecifier b]
-> [(Maybe (CDeclarator b), Maybe (CInitializer b),
Maybe (CExpression b))]
-> b
-> CDeclaration b
forall a.
[CDeclarationSpecifier a]
-> [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
-> a
-> CDeclaration a
CDecl ((CDeclarationSpecifier a -> CDeclarationSpecifier b)
-> [CDeclarationSpecifier a] -> [CDeclarationSpecifier b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> CDeclarationSpecifier a -> CDeclarationSpecifier b
forall a b.
(a -> b) -> CDeclarationSpecifier a -> CDeclarationSpecifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) [CDeclarationSpecifier a]
specs) (((Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))
-> (Maybe (CDeclarator b), Maybe (CInitializer b),
Maybe (CExpression b)))
-> [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
-> [(Maybe (CDeclarator b), Maybe (CInitializer b),
Maybe (CExpression b))]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))
-> (Maybe (CDeclarator b), Maybe (CInitializer b),
Maybe (CExpression b))
forall {f :: * -> *} {f :: * -> *} {f :: * -> *} {f :: * -> *}
{f :: * -> *} {f :: * -> *}.
(Functor f, Functor f, Functor f, Functor f, Functor f,
Functor f) =>
(f (f a), f (f a), f (f a)) -> (f (f b), f (f b), f (f b))
fmap3m [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
declarators) (a -> b
f a
annot)
where fmap3m :: (f (f a), f (f a), f (f a)) -> (f (f b), f (f b), f (f b))
fmap3m (f (f a)
a,f (f a)
b,f (f a)
c) = ((f a -> f b) -> f (f a) -> f (f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> f a -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) f (f a)
a, (f a -> f b) -> f (f a) -> f (f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> f a -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) f (f a)
b, (f a -> f b) -> f (f a) -> f (f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> f a -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) f (f a)
c)
fmap a -> b
f (CStaticAssert CExpression a
expression CStringLiteral a
strlit a
annot) =
CExpression b -> CStringLiteral b -> b -> CDeclaration b
forall a. CExpression a -> CStringLiteral a -> a -> CDeclaration a
CStaticAssert ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f CExpression a
expression) ((a -> b) -> CStringLiteral a -> CStringLiteral b
forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f CStringLiteral a
strlit) (a -> b
f a
annot)
type CDeclr = CDeclarator NodeInfo
data CDeclarator a
= CDeclr (Maybe Ident) [CDerivedDeclarator a] (Maybe (CStringLiteral a)) [CAttribute a] a
deriving (Int -> CDeclarator a -> ShowS
[CDeclarator a] -> ShowS
CDeclarator a -> String
(Int -> CDeclarator a -> ShowS)
-> (CDeclarator a -> String)
-> ([CDeclarator a] -> ShowS)
-> Show (CDeclarator a)
forall a. Show a => Int -> CDeclarator a -> ShowS
forall a. Show a => [CDeclarator a] -> ShowS
forall a. Show a => CDeclarator a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CDeclarator a -> ShowS
showsPrec :: Int -> CDeclarator a -> ShowS
$cshow :: forall a. Show a => CDeclarator a -> String
show :: CDeclarator a -> String
$cshowList :: forall a. Show a => [CDeclarator a] -> ShowS
showList :: [CDeclarator a] -> ShowS
Show, Typeable (CDeclarator a)
Typeable (CDeclarator a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> c (CDeclarator a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarator a))
-> (CDeclarator a -> Constr)
-> (CDeclarator a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarator a)))
-> ((forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r)
-> (forall u. (forall d. Data d => d -> u) -> CDeclarator a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CDeclarator a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a))
-> Data (CDeclarator a)
CDeclarator a -> Constr
CDeclarator a -> DataType
(forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
forall a. Data a => Typeable (CDeclarator a)
forall a. Data a => CDeclarator a -> Constr
forall a. Data a => CDeclarator a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDeclarator a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclarator a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarator a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> c (CDeclarator a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarator a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CDeclarator a -> u
forall u. (forall d. Data d => d -> u) -> CDeclarator a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarator a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> c (CDeclarator a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarator a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> c (CDeclarator a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> c (CDeclarator a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarator a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarator a)
$ctoConstr :: forall a. Data a => CDeclarator a -> Constr
toConstr :: CDeclarator a -> Constr
$cdataTypeOf :: forall a. Data a => CDeclarator a -> DataType
dataTypeOf :: CDeclarator a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarator a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarator a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
gmapT :: (forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclarator a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CDeclarator a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDeclarator a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CDeclarator a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
Data,Typeable, (forall x. CDeclarator a -> Rep (CDeclarator a) x)
-> (forall x. Rep (CDeclarator a) x -> CDeclarator a)
-> Generic (CDeclarator a)
forall x. Rep (CDeclarator a) x -> CDeclarator a
forall x. CDeclarator a -> Rep (CDeclarator a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CDeclarator a) x -> CDeclarator a
forall a x. CDeclarator a -> Rep (CDeclarator a) x
$cfrom :: forall a x. CDeclarator a -> Rep (CDeclarator a) x
from :: forall x. CDeclarator a -> Rep (CDeclarator a) x
$cto :: forall a x. Rep (CDeclarator a) x -> CDeclarator a
to :: forall x. Rep (CDeclarator a) x -> CDeclarator a
Generic, (forall a. CDeclarator a -> Rep1 CDeclarator a)
-> (forall a. Rep1 CDeclarator a -> CDeclarator a)
-> Generic1 CDeclarator
forall a. Rep1 CDeclarator a -> CDeclarator a
forall a. CDeclarator a -> Rep1 CDeclarator a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CDeclarator a -> Rep1 CDeclarator a
from1 :: forall a. CDeclarator a -> Rep1 CDeclarator a
$cto1 :: forall a. Rep1 CDeclarator a -> CDeclarator a
to1 :: forall a. Rep1 CDeclarator a -> CDeclarator a
Generic1 )
instance NFData a => NFData (CDeclarator a)
type CDerivedDeclr = CDerivedDeclarator NodeInfo
data CDerivedDeclarator a
= CPtrDeclr [CTypeQualifier a] a
| CArrDeclr [CTypeQualifier a] (CArraySize a) a
| CFunDeclr (Either [Ident] ([CDeclaration a],Bool)) [CAttribute a] a
deriving (Int -> CDerivedDeclarator a -> ShowS
[CDerivedDeclarator a] -> ShowS
CDerivedDeclarator a -> String
(Int -> CDerivedDeclarator a -> ShowS)
-> (CDerivedDeclarator a -> String)
-> ([CDerivedDeclarator a] -> ShowS)
-> Show (CDerivedDeclarator a)
forall a. Show a => Int -> CDerivedDeclarator a -> ShowS
forall a. Show a => [CDerivedDeclarator a] -> ShowS
forall a. Show a => CDerivedDeclarator a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CDerivedDeclarator a -> ShowS
showsPrec :: Int -> CDerivedDeclarator a -> ShowS
$cshow :: forall a. Show a => CDerivedDeclarator a -> String
show :: CDerivedDeclarator a -> String
$cshowList :: forall a. Show a => [CDerivedDeclarator a] -> ShowS
showList :: [CDerivedDeclarator a] -> ShowS
Show, Typeable (CDerivedDeclarator a)
Typeable (CDerivedDeclarator a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> c (CDerivedDeclarator a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDerivedDeclarator a))
-> (CDerivedDeclarator a -> Constr)
-> (CDerivedDeclarator a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDerivedDeclarator a)))
-> ((forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CDerivedDeclarator a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a))
-> Data (CDerivedDeclarator a)
CDerivedDeclarator a -> Constr
CDerivedDeclarator a -> DataType
(forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
forall a. Data a => Typeable (CDerivedDeclarator a)
forall a. Data a => CDerivedDeclarator a -> Constr
forall a. Data a => CDerivedDeclarator a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDerivedDeclarator a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDerivedDeclarator a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> c (CDerivedDeclarator a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDerivedDeclarator a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CDerivedDeclarator a -> u
forall u.
(forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDerivedDeclarator a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> c (CDerivedDeclarator a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDerivedDeclarator a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> c (CDerivedDeclarator a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> c (CDerivedDeclarator a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDerivedDeclarator a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDerivedDeclarator a)
$ctoConstr :: forall a. Data a => CDerivedDeclarator a -> Constr
toConstr :: CDerivedDeclarator a -> Constr
$cdataTypeOf :: forall a. Data a => CDerivedDeclarator a -> DataType
dataTypeOf :: CDerivedDeclarator a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDerivedDeclarator a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDerivedDeclarator a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
gmapT :: (forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDerivedDeclarator a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CDerivedDeclarator a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
Data,Typeable, (forall x. CDerivedDeclarator a -> Rep (CDerivedDeclarator a) x)
-> (forall x. Rep (CDerivedDeclarator a) x -> CDerivedDeclarator a)
-> Generic (CDerivedDeclarator a)
forall x. Rep (CDerivedDeclarator a) x -> CDerivedDeclarator a
forall x. CDerivedDeclarator a -> Rep (CDerivedDeclarator a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CDerivedDeclarator a) x -> CDerivedDeclarator a
forall a x. CDerivedDeclarator a -> Rep (CDerivedDeclarator a) x
$cfrom :: forall a x. CDerivedDeclarator a -> Rep (CDerivedDeclarator a) x
from :: forall x. CDerivedDeclarator a -> Rep (CDerivedDeclarator a) x
$cto :: forall a x. Rep (CDerivedDeclarator a) x -> CDerivedDeclarator a
to :: forall x. Rep (CDerivedDeclarator a) x -> CDerivedDeclarator a
Generic )
instance NFData a => NFData (CDerivedDeclarator a)
instance Functor CDerivedDeclarator where
fmap :: forall a b.
(a -> b) -> CDerivedDeclarator a -> CDerivedDeclarator b
fmap a -> b
_f (CPtrDeclr [CTypeQualifier a]
a1 a
a2) = [CTypeQualifier b] -> b -> CDerivedDeclarator b
forall a. [CTypeQualifier a] -> a -> CDerivedDeclarator a
CPtrDeclr ((CTypeQualifier a -> CTypeQualifier b)
-> [CTypeQualifier a] -> [CTypeQualifier b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall a b. (a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CTypeQualifier a]
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CArrDeclr [CTypeQualifier a]
a1 CArraySize a
a2 a
a3)
= [CTypeQualifier b] -> CArraySize b -> b -> CDerivedDeclarator b
forall a.
[CTypeQualifier a] -> CArraySize a -> a -> CDerivedDeclarator a
CArrDeclr ((CTypeQualifier a -> CTypeQualifier b)
-> [CTypeQualifier a] -> [CTypeQualifier b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall a b. (a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CTypeQualifier a]
a1) ((a -> b) -> CArraySize a -> CArraySize b
forall a b. (a -> b) -> CArraySize a -> CArraySize b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CArraySize a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CFunDeclr Either [Ident] ([CDeclaration a], Bool)
a1 [CAttribute a]
a2 a
a3)
= Either [Ident] ([CDeclaration b], Bool)
-> [CAttribute b] -> b -> CDerivedDeclarator b
forall a.
Either [Ident] ([CDeclaration a], Bool)
-> [CAttribute a] -> a -> CDerivedDeclarator a
CFunDeclr ((([CDeclaration a], Bool) -> ([CDeclaration b], Bool))
-> Either [Ident] ([CDeclaration a], Bool)
-> Either [Ident] ([CDeclaration b], Bool)
forall a b. (a -> b) -> Either [Ident] a -> Either [Ident] b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([CDeclaration a] -> [CDeclaration b])
-> ([CDeclaration a], Bool) -> ([CDeclaration b], Bool)
forall {t} {a} {b}. (t -> a) -> (t, b) -> (a, b)
fmapFirst ((CDeclaration a -> CDeclaration b)
-> [CDeclaration a] -> [CDeclaration b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f))) Either [Ident] ([CDeclaration a], Bool)
a1) ((CAttribute a -> CAttribute b) -> [CAttribute a] -> [CAttribute b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAttribute a -> CAttribute b
forall a b. (a -> b) -> CAttribute a -> CAttribute b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAttribute a]
a2)
(a -> b
_f a
a3)
where fmapFirst :: (t -> a) -> (t, b) -> (a, b)
fmapFirst t -> a
f (t
a,b
b) = (t -> a
f t
a, b
b)
type CArrSize = CArraySize NodeInfo
data CArraySize a
= CNoArrSize Bool
| CArrSize Bool (CExpression a)
deriving (Int -> CArraySize a -> ShowS
[CArraySize a] -> ShowS
CArraySize a -> String
(Int -> CArraySize a -> ShowS)
-> (CArraySize a -> String)
-> ([CArraySize a] -> ShowS)
-> Show (CArraySize a)
forall a. Show a => Int -> CArraySize a -> ShowS
forall a. Show a => [CArraySize a] -> ShowS
forall a. Show a => CArraySize a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CArraySize a -> ShowS
showsPrec :: Int -> CArraySize a -> ShowS
$cshow :: forall a. Show a => CArraySize a -> String
show :: CArraySize a -> String
$cshowList :: forall a. Show a => [CArraySize a] -> ShowS
showList :: [CArraySize a] -> ShowS
Show, Typeable (CArraySize a)
Typeable (CArraySize a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> c (CArraySize a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CArraySize a))
-> (CArraySize a -> Constr)
-> (CArraySize a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CArraySize a)))
-> ((forall b. Data b => b -> b) -> CArraySize a -> CArraySize a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r)
-> (forall u. (forall d. Data d => d -> u) -> CArraySize a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CArraySize a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a))
-> Data (CArraySize a)
CArraySize a -> Constr
CArraySize a -> DataType
(forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
forall a. Data a => Typeable (CArraySize a)
forall a. Data a => CArraySize a -> Constr
forall a. Data a => CArraySize a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CArraySize a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CArraySize a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CArraySize a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> c (CArraySize a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CArraySize a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CArraySize a -> u
forall u. (forall d. Data d => d -> u) -> CArraySize a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CArraySize a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> c (CArraySize a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CArraySize a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> c (CArraySize a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> c (CArraySize a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CArraySize a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CArraySize a)
$ctoConstr :: forall a. Data a => CArraySize a -> Constr
toConstr :: CArraySize a -> Constr
$cdataTypeOf :: forall a. Data a => CArraySize a -> DataType
dataTypeOf :: CArraySize a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CArraySize a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CArraySize a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
gmapT :: (forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CArraySize a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CArraySize a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CArraySize a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CArraySize a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
Data,Typeable, (forall x. CArraySize a -> Rep (CArraySize a) x)
-> (forall x. Rep (CArraySize a) x -> CArraySize a)
-> Generic (CArraySize a)
forall x. Rep (CArraySize a) x -> CArraySize a
forall x. CArraySize a -> Rep (CArraySize a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CArraySize a) x -> CArraySize a
forall a x. CArraySize a -> Rep (CArraySize a) x
$cfrom :: forall a x. CArraySize a -> Rep (CArraySize a) x
from :: forall x. CArraySize a -> Rep (CArraySize a) x
$cto :: forall a x. Rep (CArraySize a) x -> CArraySize a
to :: forall x. Rep (CArraySize a) x -> CArraySize a
Generic, (forall a. CArraySize a -> Rep1 CArraySize a)
-> (forall a. Rep1 CArraySize a -> CArraySize a)
-> Generic1 CArraySize
forall a. Rep1 CArraySize a -> CArraySize a
forall a. CArraySize a -> Rep1 CArraySize a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CArraySize a -> Rep1 CArraySize a
from1 :: forall a. CArraySize a -> Rep1 CArraySize a
$cto1 :: forall a. Rep1 CArraySize a -> CArraySize a
to1 :: forall a. Rep1 CArraySize a -> CArraySize a
Generic1 )
instance NFData a => NFData (CArraySize a)
type CStat = CStatement NodeInfo
data CStatement a
= CLabel Ident (CStatement a) [CAttribute a] a
| CCase (CExpression a) (CStatement a) a
| CCases (CExpression a) (CExpression a) (CStatement a) a
| CDefault (CStatement a) a
| CExpr (Maybe (CExpression a)) a
| CCompound [Ident] [CCompoundBlockItem a] a
| CIf (CExpression a) (CStatement a) (Maybe (CStatement a)) a
| CSwitch (CExpression a) (CStatement a) a
| CWhile (CExpression a) (CStatement a) Bool a
| CFor (Either (Maybe (CExpression a)) (CDeclaration a))
(Maybe (CExpression a))
(Maybe (CExpression a))
(CStatement a)
a
| CGoto Ident a
| CGotoPtr (CExpression a) a
| CCont a
| CBreak a
| CReturn (Maybe (CExpression a)) a
| CAsm (CAssemblyStatement a) a
deriving (Int -> CStatement a -> ShowS
[CStatement a] -> ShowS
CStatement a -> String
(Int -> CStatement a -> ShowS)
-> (CStatement a -> String)
-> ([CStatement a] -> ShowS)
-> Show (CStatement a)
forall a. Show a => Int -> CStatement a -> ShowS
forall a. Show a => [CStatement a] -> ShowS
forall a. Show a => CStatement a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CStatement a -> ShowS
showsPrec :: Int -> CStatement a -> ShowS
$cshow :: forall a. Show a => CStatement a -> String
show :: CStatement a -> String
$cshowList :: forall a. Show a => [CStatement a] -> ShowS
showList :: [CStatement a] -> ShowS
Show, Typeable (CStatement a)
Typeable (CStatement a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> c (CStatement a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStatement a))
-> (CStatement a -> Constr)
-> (CStatement a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStatement a)))
-> ((forall b. Data b => b -> b) -> CStatement a -> CStatement a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r)
-> (forall u. (forall d. Data d => d -> u) -> CStatement a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CStatement a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a))
-> Data (CStatement a)
CStatement a -> Constr
CStatement a -> DataType
(forall b. Data b => b -> b) -> CStatement a -> CStatement a
forall a. Data a => Typeable (CStatement a)
forall a. Data a => CStatement a -> Constr
forall a. Data a => CStatement a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CStatement a -> CStatement a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStatement a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStatement a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStatement a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> c (CStatement a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStatement a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CStatement a -> u
forall u. (forall d. Data d => d -> u) -> CStatement a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStatement a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> c (CStatement a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStatement a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> c (CStatement a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> c (CStatement a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStatement a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStatement a)
$ctoConstr :: forall a. Data a => CStatement a -> Constr
toConstr :: CStatement a -> Constr
$cdataTypeOf :: forall a. Data a => CStatement a -> DataType
dataTypeOf :: CStatement a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStatement a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStatement a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CStatement a -> CStatement a
gmapT :: (forall b. Data b => b -> b) -> CStatement a -> CStatement a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStatement a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CStatement a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStatement a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CStatement a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
Data,Typeable, (forall x. CStatement a -> Rep (CStatement a) x)
-> (forall x. Rep (CStatement a) x -> CStatement a)
-> Generic (CStatement a)
forall x. Rep (CStatement a) x -> CStatement a
forall x. CStatement a -> Rep (CStatement a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CStatement a) x -> CStatement a
forall a x. CStatement a -> Rep (CStatement a) x
$cfrom :: forall a x. CStatement a -> Rep (CStatement a) x
from :: forall x. CStatement a -> Rep (CStatement a) x
$cto :: forall a x. Rep (CStatement a) x -> CStatement a
to :: forall x. Rep (CStatement a) x -> CStatement a
Generic )
instance NFData a => NFData (CStatement a)
instance Functor CStatement where
fmap :: forall a b. (a -> b) -> CStatement a -> CStatement b
fmap a -> b
_f (CLabel Ident
a1 CStatement a
a2 [CAttribute a]
a3 a
a4)
= Ident -> CStatement b -> [CAttribute b] -> b -> CStatement b
forall a.
Ident -> CStatement a -> [CAttribute a] -> a -> CStatement a
CLabel Ident
a1 ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) ((CAttribute a -> CAttribute b) -> [CAttribute a] -> [CAttribute b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAttribute a -> CAttribute b
forall a b. (a -> b) -> CAttribute a -> CAttribute b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAttribute a]
a3) (a -> b
_f a
a4)
fmap a -> b
_f (CCase CExpression a
a1 CStatement a
a2 a
a3) = CExpression b -> CStatement b -> b -> CStatement b
forall a. CExpression a -> CStatement a -> a -> CStatement a
CCase ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CCases CExpression a
a1 CExpression a
a2 CStatement a
a3 a
a4)
= CExpression b -> CExpression b -> CStatement b -> b -> CStatement b
forall a.
CExpression a -> CExpression a -> CStatement a -> a -> CStatement a
CCases ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a3) (a -> b
_f a
a4)
fmap a -> b
_f (CDefault CStatement a
a1 a
a2) = CStatement b -> b -> CStatement b
forall a. CStatement a -> a -> CStatement a
CDefault ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CExpr Maybe (CExpression a)
a1 a
a2) = Maybe (CExpression b) -> b -> CStatement b
forall a. Maybe (CExpression a) -> a -> CStatement a
CExpr ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CExpression a)
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CCompound [Ident]
a1 [CCompoundBlockItem a]
a2 a
a3)
= [Ident] -> [CCompoundBlockItem b] -> b -> CStatement b
forall a. [Ident] -> [CCompoundBlockItem a] -> a -> CStatement a
CCompound [Ident]
a1 ((CCompoundBlockItem a -> CCompoundBlockItem b)
-> [CCompoundBlockItem a] -> [CCompoundBlockItem b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CCompoundBlockItem a -> CCompoundBlockItem b
forall a b.
(a -> b) -> CCompoundBlockItem a -> CCompoundBlockItem b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CCompoundBlockItem a]
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CIf CExpression a
a1 CStatement a
a2 Maybe (CStatement a)
a3 a
a4)
= CExpression b
-> CStatement b -> Maybe (CStatement b) -> b -> CStatement b
forall a.
CExpression a
-> CStatement a -> Maybe (CStatement a) -> a -> CStatement a
CIf ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) ((CStatement a -> CStatement b)
-> Maybe (CStatement a) -> Maybe (CStatement b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CStatement a)
a3) (a -> b
_f a
a4)
fmap a -> b
_f (CSwitch CExpression a
a1 CStatement a
a2 a
a3)
= CExpression b -> CStatement b -> b -> CStatement b
forall a. CExpression a -> CStatement a -> a -> CStatement a
CSwitch ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CWhile CExpression a
a1 CStatement a
a2 Bool
a3 a
a4)
= CExpression b -> CStatement b -> Bool -> b -> CStatement b
forall a.
CExpression a -> CStatement a -> Bool -> a -> CStatement a
CWhile ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) Bool
a3 (a -> b
_f a
a4)
fmap a -> b
_f (CFor Either (Maybe (CExpression a)) (CDeclaration a)
a1 Maybe (CExpression a)
a2 Maybe (CExpression a)
a3 CStatement a
a4 a
a5)
= Either (Maybe (CExpression b)) (CDeclaration b)
-> Maybe (CExpression b)
-> Maybe (CExpression b)
-> CStatement b
-> b
-> CStatement b
forall a.
Either (Maybe (CExpression a)) (CDeclaration a)
-> Maybe (CExpression a)
-> Maybe (CExpression a)
-> CStatement a
-> a
-> CStatement a
CFor ((Maybe (CExpression a) -> Maybe (CExpression b))
-> (CDeclaration a -> CDeclaration b)
-> Either (Maybe (CExpression a)) (CDeclaration a)
-> Either (Maybe (CExpression b)) (CDeclaration b)
forall {a} {b} {b} {b}.
(a -> b) -> (b -> b) -> Either a b -> Either b b
mapEither ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f)) ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Either (Maybe (CExpression a)) (CDeclaration a)
a1)
((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CExpression a)
a2) ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CExpression a)
a3) ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a4)
(a -> b
_f a
a5)
where mapEither :: (a -> b) -> (b -> b) -> Either a b -> Either b b
mapEither a -> b
f1 b -> b
f2 = (a -> Either b b) -> (b -> Either b b) -> Either a b -> Either b b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (b -> Either b b
forall a b. a -> Either a b
Left (b -> Either b b) -> (a -> b) -> a -> Either b b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f1) (b -> Either b b
forall a b. b -> Either a b
Right (b -> Either b b) -> (b -> b) -> b -> Either b b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> b
f2)
fmap a -> b
_f (CGoto Ident
a1 a
a2) = Ident -> b -> CStatement b
forall a. Ident -> a -> CStatement a
CGoto Ident
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CGotoPtr CExpression a
a1 a
a2) = CExpression b -> b -> CStatement b
forall a. CExpression a -> a -> CStatement a
CGotoPtr ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CCont a
a1) = b -> CStatement b
forall a. a -> CStatement a
CCont (a -> b
_f a
a1)
fmap a -> b
_f (CBreak a
a1) = b -> CStatement b
forall a. a -> CStatement a
CBreak (a -> b
_f a
a1)
fmap a -> b
_f (CReturn Maybe (CExpression a)
a1 a
a2) = Maybe (CExpression b) -> b -> CStatement b
forall a. Maybe (CExpression a) -> a -> CStatement a
CReturn ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CExpression a)
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CAsm CAssemblyStatement a
a1 a
a2) = CAssemblyStatement b -> b -> CStatement b
forall a. CAssemblyStatement a -> a -> CStatement a
CAsm ((a -> b) -> CAssemblyStatement a -> CAssemblyStatement b
forall a b.
(a -> b) -> CAssemblyStatement a -> CAssemblyStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CAssemblyStatement a
a1) (a -> b
_f a
a2)
type CAsmStmt = CAssemblyStatement NodeInfo
data CAssemblyStatement a
= CAsmStmt
(Maybe (CTypeQualifier a))
(CStringLiteral a)
[CAssemblyOperand a]
[CAssemblyOperand a]
[CStringLiteral a]
a
deriving (Int -> CAssemblyStatement a -> ShowS
[CAssemblyStatement a] -> ShowS
CAssemblyStatement a -> String
(Int -> CAssemblyStatement a -> ShowS)
-> (CAssemblyStatement a -> String)
-> ([CAssemblyStatement a] -> ShowS)
-> Show (CAssemblyStatement a)
forall a. Show a => Int -> CAssemblyStatement a -> ShowS
forall a. Show a => [CAssemblyStatement a] -> ShowS
forall a. Show a => CAssemblyStatement a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CAssemblyStatement a -> ShowS
showsPrec :: Int -> CAssemblyStatement a -> ShowS
$cshow :: forall a. Show a => CAssemblyStatement a -> String
show :: CAssemblyStatement a -> String
$cshowList :: forall a. Show a => [CAssemblyStatement a] -> ShowS
showList :: [CAssemblyStatement a] -> ShowS
Show, Typeable (CAssemblyStatement a)
Typeable (CAssemblyStatement a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> c (CAssemblyStatement a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyStatement a))
-> (CAssemblyStatement a -> Constr)
-> (CAssemblyStatement a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyStatement a)))
-> ((forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CAssemblyStatement a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CAssemblyStatement a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a))
-> Data (CAssemblyStatement a)
CAssemblyStatement a -> Constr
CAssemblyStatement a -> DataType
(forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
forall a. Data a => Typeable (CAssemblyStatement a)
forall a. Data a => CAssemblyStatement a -> Constr
forall a. Data a => CAssemblyStatement a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAssemblyStatement a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAssemblyStatement a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyStatement a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> c (CAssemblyStatement a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyStatement a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CAssemblyStatement a -> u
forall u.
(forall d. Data d => d -> u) -> CAssemblyStatement a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyStatement a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> c (CAssemblyStatement a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyStatement a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> c (CAssemblyStatement a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> c (CAssemblyStatement a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyStatement a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyStatement a)
$ctoConstr :: forall a. Data a => CAssemblyStatement a -> Constr
toConstr :: CAssemblyStatement a -> Constr
$cdataTypeOf :: forall a. Data a => CAssemblyStatement a -> DataType
dataTypeOf :: CAssemblyStatement a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyStatement a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyStatement a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
gmapT :: (forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAssemblyStatement a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CAssemblyStatement a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAssemblyStatement a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CAssemblyStatement a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
Data,Typeable, (forall x. CAssemblyStatement a -> Rep (CAssemblyStatement a) x)
-> (forall x. Rep (CAssemblyStatement a) x -> CAssemblyStatement a)
-> Generic (CAssemblyStatement a)
forall x. Rep (CAssemblyStatement a) x -> CAssemblyStatement a
forall x. CAssemblyStatement a -> Rep (CAssemblyStatement a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CAssemblyStatement a) x -> CAssemblyStatement a
forall a x. CAssemblyStatement a -> Rep (CAssemblyStatement a) x
$cfrom :: forall a x. CAssemblyStatement a -> Rep (CAssemblyStatement a) x
from :: forall x. CAssemblyStatement a -> Rep (CAssemblyStatement a) x
$cto :: forall a x. Rep (CAssemblyStatement a) x -> CAssemblyStatement a
to :: forall x. Rep (CAssemblyStatement a) x -> CAssemblyStatement a
Generic, (forall a. CAssemblyStatement a -> Rep1 CAssemblyStatement a)
-> (forall a. Rep1 CAssemblyStatement a -> CAssemblyStatement a)
-> Generic1 CAssemblyStatement
forall a. Rep1 CAssemblyStatement a -> CAssemblyStatement a
forall a. CAssemblyStatement a -> Rep1 CAssemblyStatement a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CAssemblyStatement a -> Rep1 CAssemblyStatement a
from1 :: forall a. CAssemblyStatement a -> Rep1 CAssemblyStatement a
$cto1 :: forall a. Rep1 CAssemblyStatement a -> CAssemblyStatement a
to1 :: forall a. Rep1 CAssemblyStatement a -> CAssemblyStatement a
Generic1 )
instance NFData a => NFData (CAssemblyStatement a)
type CAsmOperand = CAssemblyOperand NodeInfo
data CAssemblyOperand a
= CAsmOperand
(Maybe Ident)
(CStringLiteral a)
(CExpression a)
a
deriving (Int -> CAssemblyOperand a -> ShowS
[CAssemblyOperand a] -> ShowS
CAssemblyOperand a -> String
(Int -> CAssemblyOperand a -> ShowS)
-> (CAssemblyOperand a -> String)
-> ([CAssemblyOperand a] -> ShowS)
-> Show (CAssemblyOperand a)
forall a. Show a => Int -> CAssemblyOperand a -> ShowS
forall a. Show a => [CAssemblyOperand a] -> ShowS
forall a. Show a => CAssemblyOperand a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CAssemblyOperand a -> ShowS
showsPrec :: Int -> CAssemblyOperand a -> ShowS
$cshow :: forall a. Show a => CAssemblyOperand a -> String
show :: CAssemblyOperand a -> String
$cshowList :: forall a. Show a => [CAssemblyOperand a] -> ShowS
showList :: [CAssemblyOperand a] -> ShowS
Show, Typeable (CAssemblyOperand a)
Typeable (CAssemblyOperand a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> c (CAssemblyOperand a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyOperand a))
-> (CAssemblyOperand a -> Constr)
-> (CAssemblyOperand a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyOperand a)))
-> ((forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CAssemblyOperand a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CAssemblyOperand a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a))
-> Data (CAssemblyOperand a)
CAssemblyOperand a -> Constr
CAssemblyOperand a -> DataType
(forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
forall a. Data a => Typeable (CAssemblyOperand a)
forall a. Data a => CAssemblyOperand a -> Constr
forall a. Data a => CAssemblyOperand a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAssemblyOperand a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAssemblyOperand a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyOperand a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> c (CAssemblyOperand a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyOperand a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CAssemblyOperand a -> u
forall u. (forall d. Data d => d -> u) -> CAssemblyOperand a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyOperand a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> c (CAssemblyOperand a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyOperand a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> c (CAssemblyOperand a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> c (CAssemblyOperand a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyOperand a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyOperand a)
$ctoConstr :: forall a. Data a => CAssemblyOperand a -> Constr
toConstr :: CAssemblyOperand a -> Constr
$cdataTypeOf :: forall a. Data a => CAssemblyOperand a -> DataType
dataTypeOf :: CAssemblyOperand a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyOperand a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAssemblyOperand a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
gmapT :: (forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAssemblyOperand a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CAssemblyOperand a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAssemblyOperand a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CAssemblyOperand a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
Data,Typeable, (forall x. CAssemblyOperand a -> Rep (CAssemblyOperand a) x)
-> (forall x. Rep (CAssemblyOperand a) x -> CAssemblyOperand a)
-> Generic (CAssemblyOperand a)
forall x. Rep (CAssemblyOperand a) x -> CAssemblyOperand a
forall x. CAssemblyOperand a -> Rep (CAssemblyOperand a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CAssemblyOperand a) x -> CAssemblyOperand a
forall a x. CAssemblyOperand a -> Rep (CAssemblyOperand a) x
$cfrom :: forall a x. CAssemblyOperand a -> Rep (CAssemblyOperand a) x
from :: forall x. CAssemblyOperand a -> Rep (CAssemblyOperand a) x
$cto :: forall a x. Rep (CAssemblyOperand a) x -> CAssemblyOperand a
to :: forall x. Rep (CAssemblyOperand a) x -> CAssemblyOperand a
Generic, (forall a. CAssemblyOperand a -> Rep1 CAssemblyOperand a)
-> (forall a. Rep1 CAssemblyOperand a -> CAssemblyOperand a)
-> Generic1 CAssemblyOperand
forall a. Rep1 CAssemblyOperand a -> CAssemblyOperand a
forall a. CAssemblyOperand a -> Rep1 CAssemblyOperand a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CAssemblyOperand a -> Rep1 CAssemblyOperand a
from1 :: forall a. CAssemblyOperand a -> Rep1 CAssemblyOperand a
$cto1 :: forall a. Rep1 CAssemblyOperand a -> CAssemblyOperand a
to1 :: forall a. Rep1 CAssemblyOperand a -> CAssemblyOperand a
Generic1 )
instance NFData a => NFData (CAssemblyOperand a)
type CBlockItem = CCompoundBlockItem NodeInfo
data CCompoundBlockItem a
= CBlockStmt (CStatement a)
| CBlockDecl (CDeclaration a)
| CNestedFunDef (CFunctionDef a)
deriving (Int -> CCompoundBlockItem a -> ShowS
[CCompoundBlockItem a] -> ShowS
CCompoundBlockItem a -> String
(Int -> CCompoundBlockItem a -> ShowS)
-> (CCompoundBlockItem a -> String)
-> ([CCompoundBlockItem a] -> ShowS)
-> Show (CCompoundBlockItem a)
forall a. Show a => Int -> CCompoundBlockItem a -> ShowS
forall a. Show a => [CCompoundBlockItem a] -> ShowS
forall a. Show a => CCompoundBlockItem a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CCompoundBlockItem a -> ShowS
showsPrec :: Int -> CCompoundBlockItem a -> ShowS
$cshow :: forall a. Show a => CCompoundBlockItem a -> String
show :: CCompoundBlockItem a -> String
$cshowList :: forall a. Show a => [CCompoundBlockItem a] -> ShowS
showList :: [CCompoundBlockItem a] -> ShowS
Show, Typeable (CCompoundBlockItem a)
Typeable (CCompoundBlockItem a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> c (CCompoundBlockItem a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CCompoundBlockItem a))
-> (CCompoundBlockItem a -> Constr)
-> (CCompoundBlockItem a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CCompoundBlockItem a)))
-> ((forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CCompoundBlockItem a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a))
-> Data (CCompoundBlockItem a)
CCompoundBlockItem a -> Constr
CCompoundBlockItem a -> DataType
(forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
forall a. Data a => Typeable (CCompoundBlockItem a)
forall a. Data a => CCompoundBlockItem a -> Constr
forall a. Data a => CCompoundBlockItem a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CCompoundBlockItem a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CCompoundBlockItem a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> c (CCompoundBlockItem a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CCompoundBlockItem a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CCompoundBlockItem a -> u
forall u.
(forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CCompoundBlockItem a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> c (CCompoundBlockItem a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CCompoundBlockItem a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> c (CCompoundBlockItem a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> c (CCompoundBlockItem a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CCompoundBlockItem a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CCompoundBlockItem a)
$ctoConstr :: forall a. Data a => CCompoundBlockItem a -> Constr
toConstr :: CCompoundBlockItem a -> Constr
$cdataTypeOf :: forall a. Data a => CCompoundBlockItem a -> DataType
dataTypeOf :: CCompoundBlockItem a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CCompoundBlockItem a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CCompoundBlockItem a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
gmapT :: (forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CCompoundBlockItem a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CCompoundBlockItem a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
Data,Typeable, (forall x. CCompoundBlockItem a -> Rep (CCompoundBlockItem a) x)
-> (forall x. Rep (CCompoundBlockItem a) x -> CCompoundBlockItem a)
-> Generic (CCompoundBlockItem a)
forall x. Rep (CCompoundBlockItem a) x -> CCompoundBlockItem a
forall x. CCompoundBlockItem a -> Rep (CCompoundBlockItem a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CCompoundBlockItem a) x -> CCompoundBlockItem a
forall a x. CCompoundBlockItem a -> Rep (CCompoundBlockItem a) x
$cfrom :: forall a x. CCompoundBlockItem a -> Rep (CCompoundBlockItem a) x
from :: forall x. CCompoundBlockItem a -> Rep (CCompoundBlockItem a) x
$cto :: forall a x. Rep (CCompoundBlockItem a) x -> CCompoundBlockItem a
to :: forall x. Rep (CCompoundBlockItem a) x -> CCompoundBlockItem a
Generic, (forall a. CCompoundBlockItem a -> Rep1 CCompoundBlockItem a)
-> (forall a. Rep1 CCompoundBlockItem a -> CCompoundBlockItem a)
-> Generic1 CCompoundBlockItem
forall a. Rep1 CCompoundBlockItem a -> CCompoundBlockItem a
forall a. CCompoundBlockItem a -> Rep1 CCompoundBlockItem a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CCompoundBlockItem a -> Rep1 CCompoundBlockItem a
from1 :: forall a. CCompoundBlockItem a -> Rep1 CCompoundBlockItem a
$cto1 :: forall a. Rep1 CCompoundBlockItem a -> CCompoundBlockItem a
to1 :: forall a. Rep1 CCompoundBlockItem a -> CCompoundBlockItem a
Generic1 )
instance NFData a => NFData (CCompoundBlockItem a)
type CDeclSpec = CDeclarationSpecifier NodeInfo
data CDeclarationSpecifier a
= CStorageSpec (CStorageSpecifier a)
| CTypeSpec (CTypeSpecifier a)
| CTypeQual (CTypeQualifier a)
| CFunSpec (CFunctionSpecifier a)
| CAlignSpec (CAlignmentSpecifier a)
deriving (Int -> CDeclarationSpecifier a -> ShowS
[CDeclarationSpecifier a] -> ShowS
CDeclarationSpecifier a -> String
(Int -> CDeclarationSpecifier a -> ShowS)
-> (CDeclarationSpecifier a -> String)
-> ([CDeclarationSpecifier a] -> ShowS)
-> Show (CDeclarationSpecifier a)
forall a. Show a => Int -> CDeclarationSpecifier a -> ShowS
forall a. Show a => [CDeclarationSpecifier a] -> ShowS
forall a. Show a => CDeclarationSpecifier a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CDeclarationSpecifier a -> ShowS
showsPrec :: Int -> CDeclarationSpecifier a -> ShowS
$cshow :: forall a. Show a => CDeclarationSpecifier a -> String
show :: CDeclarationSpecifier a -> String
$cshowList :: forall a. Show a => [CDeclarationSpecifier a] -> ShowS
showList :: [CDeclarationSpecifier a] -> ShowS
Show, Typeable (CDeclarationSpecifier a)
Typeable (CDeclarationSpecifier a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> c (CDeclarationSpecifier a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarationSpecifier a))
-> (CDeclarationSpecifier a -> Constr)
-> (CDeclarationSpecifier a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarationSpecifier a)))
-> ((forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> CDeclarationSpecifier a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a))
-> Data (CDeclarationSpecifier a)
CDeclarationSpecifier a -> Constr
CDeclarationSpecifier a -> DataType
(forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
forall a. Data a => Typeable (CDeclarationSpecifier a)
forall a. Data a => CDeclarationSpecifier a -> Constr
forall a. Data a => CDeclarationSpecifier a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDeclarationSpecifier a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarationSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> c (CDeclarationSpecifier a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarationSpecifier a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CDeclarationSpecifier a -> u
forall u.
(forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarationSpecifier a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> c (CDeclarationSpecifier a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarationSpecifier a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> c (CDeclarationSpecifier a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> c (CDeclarationSpecifier a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarationSpecifier a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarationSpecifier a)
$ctoConstr :: forall a. Data a => CDeclarationSpecifier a -> Constr
toConstr :: CDeclarationSpecifier a -> Constr
$cdataTypeOf :: forall a. Data a => CDeclarationSpecifier a -> DataType
dataTypeOf :: CDeclarationSpecifier a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarationSpecifier a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CDeclarationSpecifier a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
gmapT :: (forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CDeclarationSpecifier a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CDeclarationSpecifier a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
Data,Typeable, (forall x.
CDeclarationSpecifier a -> Rep (CDeclarationSpecifier a) x)
-> (forall x.
Rep (CDeclarationSpecifier a) x -> CDeclarationSpecifier a)
-> Generic (CDeclarationSpecifier a)
forall x.
Rep (CDeclarationSpecifier a) x -> CDeclarationSpecifier a
forall x.
CDeclarationSpecifier a -> Rep (CDeclarationSpecifier a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (CDeclarationSpecifier a) x -> CDeclarationSpecifier a
forall a x.
CDeclarationSpecifier a -> Rep (CDeclarationSpecifier a) x
$cfrom :: forall a x.
CDeclarationSpecifier a -> Rep (CDeclarationSpecifier a) x
from :: forall x.
CDeclarationSpecifier a -> Rep (CDeclarationSpecifier a) x
$cto :: forall a x.
Rep (CDeclarationSpecifier a) x -> CDeclarationSpecifier a
to :: forall x.
Rep (CDeclarationSpecifier a) x -> CDeclarationSpecifier a
Generic, (forall a. CDeclarationSpecifier a -> Rep1 CDeclarationSpecifier a)
-> (forall a.
Rep1 CDeclarationSpecifier a -> CDeclarationSpecifier a)
-> Generic1 CDeclarationSpecifier
forall a. Rep1 CDeclarationSpecifier a -> CDeclarationSpecifier a
forall a. CDeclarationSpecifier a -> Rep1 CDeclarationSpecifier a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CDeclarationSpecifier a -> Rep1 CDeclarationSpecifier a
from1 :: forall a. CDeclarationSpecifier a -> Rep1 CDeclarationSpecifier a
$cto1 :: forall a. Rep1 CDeclarationSpecifier a -> CDeclarationSpecifier a
to1 :: forall a. Rep1 CDeclarationSpecifier a -> CDeclarationSpecifier a
Generic1 )
instance NFData a => NFData (CDeclarationSpecifier a)
partitionDeclSpecs :: [CDeclarationSpecifier a]
-> ( [CStorageSpecifier a], [CAttribute a]
, [CTypeQualifier a], [CTypeSpecifier a]
, [CFunctionSpecifier a], [CAlignmentSpecifier a])
partitionDeclSpecs :: forall a.
[CDeclarationSpecifier a]
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
partitionDeclSpecs = (CDeclarationSpecifier a
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a]))
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
-> [CDeclarationSpecifier a]
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr CDeclarationSpecifier a
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
forall {a}.
CDeclarationSpecifier a
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
deals ([],[],[],[],[],[]) where
deals :: CDeclarationSpecifier a
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
-> ([CStorageSpecifier a], [CAttribute a], [CTypeQualifier a],
[CTypeSpecifier a], [CFunctionSpecifier a],
[CAlignmentSpecifier a])
deals (CStorageSpec CStorageSpecifier a
sp) ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass) = (CStorageSpecifier a
spCStorageSpecifier a
-> [CStorageSpecifier a] -> [CStorageSpecifier a]
forall a. a -> [a] -> [a]
:[CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass)
deals (CTypeQual (CAttrQual CAttribute a
attr)) ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass) = ([CStorageSpecifier a]
sts,CAttribute a
attrCAttribute a -> [CAttribute a] -> [CAttribute a]
forall a. a -> [a] -> [a]
:[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass)
deals (CTypeQual CTypeQualifier a
tq) ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass) = ([CStorageSpecifier a]
sts,[CAttribute a]
ats,CTypeQualifier a
tqCTypeQualifier a -> [CTypeQualifier a] -> [CTypeQualifier a]
forall a. a -> [a] -> [a]
:[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass)
deals (CTypeSpec CTypeSpecifier a
ts) ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass) = ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,CTypeSpecifier a
tsCTypeSpecifier a -> [CTypeSpecifier a] -> [CTypeSpecifier a]
forall a. a -> [a] -> [a]
:[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass)
deals (CFunSpec CFunctionSpecifier a
fs) ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass) = ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,CFunctionSpecifier a
fsCFunctionSpecifier a
-> [CFunctionSpecifier a] -> [CFunctionSpecifier a]
forall a. a -> [a] -> [a]
:[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass)
deals (CAlignSpec CAlignmentSpecifier a
as) ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,[CAlignmentSpecifier a]
ass) = ([CStorageSpecifier a]
sts,[CAttribute a]
ats,[CTypeQualifier a]
tqs,[CTypeSpecifier a]
tss,[CFunctionSpecifier a]
fss,CAlignmentSpecifier a
asCAlignmentSpecifier a
-> [CAlignmentSpecifier a] -> [CAlignmentSpecifier a]
forall a. a -> [a] -> [a]
:[CAlignmentSpecifier a]
ass)
type CStorageSpec = CStorageSpecifier NodeInfo
data CStorageSpecifier a
= CAuto a
| CRegister a
| CStatic a
| CExtern a
| CTypedef a
| CThread a
| CClKernel a
| CClGlobal a
| CClLocal a
deriving (Int -> CStorageSpecifier a -> ShowS
[CStorageSpecifier a] -> ShowS
CStorageSpecifier a -> String
(Int -> CStorageSpecifier a -> ShowS)
-> (CStorageSpecifier a -> String)
-> ([CStorageSpecifier a] -> ShowS)
-> Show (CStorageSpecifier a)
forall a. Show a => Int -> CStorageSpecifier a -> ShowS
forall a. Show a => [CStorageSpecifier a] -> ShowS
forall a. Show a => CStorageSpecifier a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CStorageSpecifier a -> ShowS
showsPrec :: Int -> CStorageSpecifier a -> ShowS
$cshow :: forall a. Show a => CStorageSpecifier a -> String
show :: CStorageSpecifier a -> String
$cshowList :: forall a. Show a => [CStorageSpecifier a] -> ShowS
showList :: [CStorageSpecifier a] -> ShowS
Show, CStorageSpecifier a -> CStorageSpecifier a -> Bool
(CStorageSpecifier a -> CStorageSpecifier a -> Bool)
-> (CStorageSpecifier a -> CStorageSpecifier a -> Bool)
-> Eq (CStorageSpecifier a)
forall a.
Eq a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a.
Eq a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
== :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
$c/= :: forall a.
Eq a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
/= :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
Eq,Eq (CStorageSpecifier a)
Eq (CStorageSpecifier a) =>
(CStorageSpecifier a -> CStorageSpecifier a -> Ordering)
-> (CStorageSpecifier a -> CStorageSpecifier a -> Bool)
-> (CStorageSpecifier a -> CStorageSpecifier a -> Bool)
-> (CStorageSpecifier a -> CStorageSpecifier a -> Bool)
-> (CStorageSpecifier a -> CStorageSpecifier a -> Bool)
-> (CStorageSpecifier a
-> CStorageSpecifier a -> CStorageSpecifier a)
-> (CStorageSpecifier a
-> CStorageSpecifier a -> CStorageSpecifier a)
-> Ord (CStorageSpecifier a)
CStorageSpecifier a -> CStorageSpecifier a -> Bool
CStorageSpecifier a -> CStorageSpecifier a -> Ordering
CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (CStorageSpecifier a)
forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Ordering
forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
$ccompare :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Ordering
compare :: CStorageSpecifier a -> CStorageSpecifier a -> Ordering
$c< :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
< :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
$c<= :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
<= :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
$c> :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
> :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
$c>= :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
>= :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
$cmax :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
max :: CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
$cmin :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
min :: CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
Ord,Typeable (CStorageSpecifier a)
Typeable (CStorageSpecifier a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> c (CStorageSpecifier a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStorageSpecifier a))
-> (CStorageSpecifier a -> Constr)
-> (CStorageSpecifier a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStorageSpecifier a)))
-> ((forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CStorageSpecifier a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CStorageSpecifier a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a))
-> Data (CStorageSpecifier a)
CStorageSpecifier a -> Constr
CStorageSpecifier a -> DataType
(forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
forall a. Data a => Typeable (CStorageSpecifier a)
forall a. Data a => CStorageSpecifier a -> Constr
forall a. Data a => CStorageSpecifier a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStorageSpecifier a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStorageSpecifier a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStorageSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> c (CStorageSpecifier a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStorageSpecifier a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CStorageSpecifier a -> u
forall u.
(forall d. Data d => d -> u) -> CStorageSpecifier a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStorageSpecifier a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> c (CStorageSpecifier a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStorageSpecifier a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> c (CStorageSpecifier a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> c (CStorageSpecifier a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStorageSpecifier a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStorageSpecifier a)
$ctoConstr :: forall a. Data a => CStorageSpecifier a -> Constr
toConstr :: CStorageSpecifier a -> Constr
$cdataTypeOf :: forall a. Data a => CStorageSpecifier a -> DataType
dataTypeOf :: CStorageSpecifier a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStorageSpecifier a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStorageSpecifier a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
gmapT :: (forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStorageSpecifier a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CStorageSpecifier a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStorageSpecifier a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CStorageSpecifier a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
Data,Typeable, (forall x. CStorageSpecifier a -> Rep (CStorageSpecifier a) x)
-> (forall x. Rep (CStorageSpecifier a) x -> CStorageSpecifier a)
-> Generic (CStorageSpecifier a)
forall x. Rep (CStorageSpecifier a) x -> CStorageSpecifier a
forall x. CStorageSpecifier a -> Rep (CStorageSpecifier a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CStorageSpecifier a) x -> CStorageSpecifier a
forall a x. CStorageSpecifier a -> Rep (CStorageSpecifier a) x
$cfrom :: forall a x. CStorageSpecifier a -> Rep (CStorageSpecifier a) x
from :: forall x. CStorageSpecifier a -> Rep (CStorageSpecifier a) x
$cto :: forall a x. Rep (CStorageSpecifier a) x -> CStorageSpecifier a
to :: forall x. Rep (CStorageSpecifier a) x -> CStorageSpecifier a
Generic, (forall a. CStorageSpecifier a -> Rep1 CStorageSpecifier a)
-> (forall a. Rep1 CStorageSpecifier a -> CStorageSpecifier a)
-> Generic1 CStorageSpecifier
forall a. Rep1 CStorageSpecifier a -> CStorageSpecifier a
forall a. CStorageSpecifier a -> Rep1 CStorageSpecifier a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CStorageSpecifier a -> Rep1 CStorageSpecifier a
from1 :: forall a. CStorageSpecifier a -> Rep1 CStorageSpecifier a
$cto1 :: forall a. Rep1 CStorageSpecifier a -> CStorageSpecifier a
to1 :: forall a. Rep1 CStorageSpecifier a -> CStorageSpecifier a
Generic1 )
instance NFData a => NFData (CStorageSpecifier a)
type CTypeSpec = CTypeSpecifier NodeInfo
data CTypeSpecifier a
= CVoidType a
| CCharType a
| CShortType a
| CIntType a
| CLongType a
| CFloatType a
| CDoubleType a
| CSignedType a
| CUnsigType a
| CBoolType a
| CComplexType a
| CInt128Type a
| CUInt128Type a
| CFloatNType Int Bool a
| CSUType (CStructureUnion a) a
| CEnumType (CEnumeration a) a
| CTypeDef Ident a
| CTypeOfExpr (CExpression a) a
| CTypeOfType (CDeclaration a) a
| CAtomicType (CDeclaration a) a
deriving (Int -> CTypeSpecifier a -> ShowS
[CTypeSpecifier a] -> ShowS
CTypeSpecifier a -> String
(Int -> CTypeSpecifier a -> ShowS)
-> (CTypeSpecifier a -> String)
-> ([CTypeSpecifier a] -> ShowS)
-> Show (CTypeSpecifier a)
forall a. Show a => Int -> CTypeSpecifier a -> ShowS
forall a. Show a => [CTypeSpecifier a] -> ShowS
forall a. Show a => CTypeSpecifier a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CTypeSpecifier a -> ShowS
showsPrec :: Int -> CTypeSpecifier a -> ShowS
$cshow :: forall a. Show a => CTypeSpecifier a -> String
show :: CTypeSpecifier a -> String
$cshowList :: forall a. Show a => [CTypeSpecifier a] -> ShowS
showList :: [CTypeSpecifier a] -> ShowS
Show, Typeable (CTypeSpecifier a)
Typeable (CTypeSpecifier a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTypeSpecifier a
-> c (CTypeSpecifier a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeSpecifier a))
-> (CTypeSpecifier a -> Constr)
-> (CTypeSpecifier a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeSpecifier a)))
-> ((forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CTypeSpecifier a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CTypeSpecifier a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a))
-> Data (CTypeSpecifier a)
CTypeSpecifier a -> Constr
CTypeSpecifier a -> DataType
(forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
forall a. Data a => Typeable (CTypeSpecifier a)
forall a. Data a => CTypeSpecifier a -> Constr
forall a. Data a => CTypeSpecifier a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CTypeSpecifier a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTypeSpecifier a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeSpecifier a -> c (CTypeSpecifier a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeSpecifier a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CTypeSpecifier a -> u
forall u. (forall d. Data d => d -> u) -> CTypeSpecifier a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeSpecifier a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeSpecifier a -> c (CTypeSpecifier a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeSpecifier a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeSpecifier a -> c (CTypeSpecifier a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeSpecifier a -> c (CTypeSpecifier a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeSpecifier a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeSpecifier a)
$ctoConstr :: forall a. Data a => CTypeSpecifier a -> Constr
toConstr :: CTypeSpecifier a -> Constr
$cdataTypeOf :: forall a. Data a => CTypeSpecifier a -> DataType
dataTypeOf :: CTypeSpecifier a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeSpecifier a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeSpecifier a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
gmapT :: (forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTypeSpecifier a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CTypeSpecifier a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CTypeSpecifier a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CTypeSpecifier a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
Data,Typeable, (forall x. CTypeSpecifier a -> Rep (CTypeSpecifier a) x)
-> (forall x. Rep (CTypeSpecifier a) x -> CTypeSpecifier a)
-> Generic (CTypeSpecifier a)
forall x. Rep (CTypeSpecifier a) x -> CTypeSpecifier a
forall x. CTypeSpecifier a -> Rep (CTypeSpecifier a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CTypeSpecifier a) x -> CTypeSpecifier a
forall a x. CTypeSpecifier a -> Rep (CTypeSpecifier a) x
$cfrom :: forall a x. CTypeSpecifier a -> Rep (CTypeSpecifier a) x
from :: forall x. CTypeSpecifier a -> Rep (CTypeSpecifier a) x
$cto :: forall a x. Rep (CTypeSpecifier a) x -> CTypeSpecifier a
to :: forall x. Rep (CTypeSpecifier a) x -> CTypeSpecifier a
Generic, (forall a. CTypeSpecifier a -> Rep1 CTypeSpecifier a)
-> (forall a. Rep1 CTypeSpecifier a -> CTypeSpecifier a)
-> Generic1 CTypeSpecifier
forall a. Rep1 CTypeSpecifier a -> CTypeSpecifier a
forall a. CTypeSpecifier a -> Rep1 CTypeSpecifier a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CTypeSpecifier a -> Rep1 CTypeSpecifier a
from1 :: forall a. CTypeSpecifier a -> Rep1 CTypeSpecifier a
$cto1 :: forall a. Rep1 CTypeSpecifier a -> CTypeSpecifier a
to1 :: forall a. Rep1 CTypeSpecifier a -> CTypeSpecifier a
Generic1 )
instance NFData a => NFData (CTypeSpecifier a)
isSUEDef :: CTypeSpecifier a -> Bool
isSUEDef :: forall a. CTypeSpecifier a -> Bool
isSUEDef (CSUType (CStruct CStructTag
_ Maybe Ident
_ (Just [CDeclaration a]
_) [CAttribute a]
_ a
_) a
_) = Bool
True
isSUEDef (CEnumType (CEnum Maybe Ident
_ (Just [(Ident, Maybe (CExpression a))]
_) [CAttribute a]
_ a
_) a
_) = Bool
True
isSUEDef CTypeSpecifier a
_ = Bool
False
type CTypeQual = CTypeQualifier NodeInfo
data CTypeQualifier a
= CConstQual a
| CVolatQual a
| CRestrQual a
| CAtomicQual a
| CAttrQual (CAttribute a)
| CNullableQual a
| CNonnullQual a
| CClRdOnlyQual a
| CClWrOnlyQual a
deriving (Int -> CTypeQualifier a -> ShowS
[CTypeQualifier a] -> ShowS
CTypeQualifier a -> String
(Int -> CTypeQualifier a -> ShowS)
-> (CTypeQualifier a -> String)
-> ([CTypeQualifier a] -> ShowS)
-> Show (CTypeQualifier a)
forall a. Show a => Int -> CTypeQualifier a -> ShowS
forall a. Show a => [CTypeQualifier a] -> ShowS
forall a. Show a => CTypeQualifier a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CTypeQualifier a -> ShowS
showsPrec :: Int -> CTypeQualifier a -> ShowS
$cshow :: forall a. Show a => CTypeQualifier a -> String
show :: CTypeQualifier a -> String
$cshowList :: forall a. Show a => [CTypeQualifier a] -> ShowS
showList :: [CTypeQualifier a] -> ShowS
Show, Typeable (CTypeQualifier a)
Typeable (CTypeQualifier a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTypeQualifier a
-> c (CTypeQualifier a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeQualifier a))
-> (CTypeQualifier a -> Constr)
-> (CTypeQualifier a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeQualifier a)))
-> ((forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CTypeQualifier a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CTypeQualifier a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a))
-> Data (CTypeQualifier a)
CTypeQualifier a -> Constr
CTypeQualifier a -> DataType
(forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
forall a. Data a => Typeable (CTypeQualifier a)
forall a. Data a => CTypeQualifier a -> Constr
forall a. Data a => CTypeQualifier a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CTypeQualifier a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTypeQualifier a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeQualifier a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeQualifier a -> c (CTypeQualifier a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeQualifier a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CTypeQualifier a -> u
forall u. (forall d. Data d => d -> u) -> CTypeQualifier a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeQualifier a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeQualifier a -> c (CTypeQualifier a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeQualifier a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeQualifier a -> c (CTypeQualifier a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeQualifier a -> c (CTypeQualifier a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeQualifier a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeQualifier a)
$ctoConstr :: forall a. Data a => CTypeQualifier a -> Constr
toConstr :: CTypeQualifier a -> Constr
$cdataTypeOf :: forall a. Data a => CTypeQualifier a -> DataType
dataTypeOf :: CTypeQualifier a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeQualifier a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CTypeQualifier a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
gmapT :: (forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTypeQualifier a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CTypeQualifier a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CTypeQualifier a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CTypeQualifier a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
Data,Typeable, (forall x. CTypeQualifier a -> Rep (CTypeQualifier a) x)
-> (forall x. Rep (CTypeQualifier a) x -> CTypeQualifier a)
-> Generic (CTypeQualifier a)
forall x. Rep (CTypeQualifier a) x -> CTypeQualifier a
forall x. CTypeQualifier a -> Rep (CTypeQualifier a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CTypeQualifier a) x -> CTypeQualifier a
forall a x. CTypeQualifier a -> Rep (CTypeQualifier a) x
$cfrom :: forall a x. CTypeQualifier a -> Rep (CTypeQualifier a) x
from :: forall x. CTypeQualifier a -> Rep (CTypeQualifier a) x
$cto :: forall a x. Rep (CTypeQualifier a) x -> CTypeQualifier a
to :: forall x. Rep (CTypeQualifier a) x -> CTypeQualifier a
Generic, (forall a. CTypeQualifier a -> Rep1 CTypeQualifier a)
-> (forall a. Rep1 CTypeQualifier a -> CTypeQualifier a)
-> Generic1 CTypeQualifier
forall a. Rep1 CTypeQualifier a -> CTypeQualifier a
forall a. CTypeQualifier a -> Rep1 CTypeQualifier a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CTypeQualifier a -> Rep1 CTypeQualifier a
from1 :: forall a. CTypeQualifier a -> Rep1 CTypeQualifier a
$cto1 :: forall a. Rep1 CTypeQualifier a -> CTypeQualifier a
to1 :: forall a. Rep1 CTypeQualifier a -> CTypeQualifier a
Generic1 )
instance NFData a => NFData (CTypeQualifier a)
type CFunSpec = CFunctionSpecifier NodeInfo
data CFunctionSpecifier a
= CInlineQual a
| CNoreturnQual a
deriving (Int -> CFunctionSpecifier a -> ShowS
[CFunctionSpecifier a] -> ShowS
CFunctionSpecifier a -> String
(Int -> CFunctionSpecifier a -> ShowS)
-> (CFunctionSpecifier a -> String)
-> ([CFunctionSpecifier a] -> ShowS)
-> Show (CFunctionSpecifier a)
forall a. Show a => Int -> CFunctionSpecifier a -> ShowS
forall a. Show a => [CFunctionSpecifier a] -> ShowS
forall a. Show a => CFunctionSpecifier a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CFunctionSpecifier a -> ShowS
showsPrec :: Int -> CFunctionSpecifier a -> ShowS
$cshow :: forall a. Show a => CFunctionSpecifier a -> String
show :: CFunctionSpecifier a -> String
$cshowList :: forall a. Show a => [CFunctionSpecifier a] -> ShowS
showList :: [CFunctionSpecifier a] -> ShowS
Show, Typeable (CFunctionSpecifier a)
Typeable (CFunctionSpecifier a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> c (CFunctionSpecifier a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionSpecifier a))
-> (CFunctionSpecifier a -> Constr)
-> (CFunctionSpecifier a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionSpecifier a)))
-> ((forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CFunctionSpecifier a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a))
-> Data (CFunctionSpecifier a)
CFunctionSpecifier a -> Constr
CFunctionSpecifier a -> DataType
(forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
forall a. Data a => Typeable (CFunctionSpecifier a)
forall a. Data a => CFunctionSpecifier a -> Constr
forall a. Data a => CFunctionSpecifier a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CFunctionSpecifier a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> c (CFunctionSpecifier a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionSpecifier a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CFunctionSpecifier a -> u
forall u.
(forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionSpecifier a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> c (CFunctionSpecifier a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionSpecifier a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> c (CFunctionSpecifier a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> c (CFunctionSpecifier a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionSpecifier a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionSpecifier a)
$ctoConstr :: forall a. Data a => CFunctionSpecifier a -> Constr
toConstr :: CFunctionSpecifier a -> Constr
$cdataTypeOf :: forall a. Data a => CFunctionSpecifier a -> DataType
dataTypeOf :: CFunctionSpecifier a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionSpecifier a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CFunctionSpecifier a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
gmapT :: (forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CFunctionSpecifier a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CFunctionSpecifier a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
Data,Typeable, (forall x. CFunctionSpecifier a -> Rep (CFunctionSpecifier a) x)
-> (forall x. Rep (CFunctionSpecifier a) x -> CFunctionSpecifier a)
-> Generic (CFunctionSpecifier a)
forall x. Rep (CFunctionSpecifier a) x -> CFunctionSpecifier a
forall x. CFunctionSpecifier a -> Rep (CFunctionSpecifier a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CFunctionSpecifier a) x -> CFunctionSpecifier a
forall a x. CFunctionSpecifier a -> Rep (CFunctionSpecifier a) x
$cfrom :: forall a x. CFunctionSpecifier a -> Rep (CFunctionSpecifier a) x
from :: forall x. CFunctionSpecifier a -> Rep (CFunctionSpecifier a) x
$cto :: forall a x. Rep (CFunctionSpecifier a) x -> CFunctionSpecifier a
to :: forall x. Rep (CFunctionSpecifier a) x -> CFunctionSpecifier a
Generic, (forall a. CFunctionSpecifier a -> Rep1 CFunctionSpecifier a)
-> (forall a. Rep1 CFunctionSpecifier a -> CFunctionSpecifier a)
-> Generic1 CFunctionSpecifier
forall a. Rep1 CFunctionSpecifier a -> CFunctionSpecifier a
forall a. CFunctionSpecifier a -> Rep1 CFunctionSpecifier a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CFunctionSpecifier a -> Rep1 CFunctionSpecifier a
from1 :: forall a. CFunctionSpecifier a -> Rep1 CFunctionSpecifier a
$cto1 :: forall a. Rep1 CFunctionSpecifier a -> CFunctionSpecifier a
to1 :: forall a. Rep1 CFunctionSpecifier a -> CFunctionSpecifier a
Generic1 )
instance NFData a => NFData (CFunctionSpecifier a)
type CAlignSpec = CAlignmentSpecifier NodeInfo
data CAlignmentSpecifier a
= CAlignAsType (CDeclaration a) a
| CAlignAsExpr (CExpression a) a
deriving (Int -> CAlignmentSpecifier a -> ShowS
[CAlignmentSpecifier a] -> ShowS
CAlignmentSpecifier a -> String
(Int -> CAlignmentSpecifier a -> ShowS)
-> (CAlignmentSpecifier a -> String)
-> ([CAlignmentSpecifier a] -> ShowS)
-> Show (CAlignmentSpecifier a)
forall a. Show a => Int -> CAlignmentSpecifier a -> ShowS
forall a. Show a => [CAlignmentSpecifier a] -> ShowS
forall a. Show a => CAlignmentSpecifier a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CAlignmentSpecifier a -> ShowS
showsPrec :: Int -> CAlignmentSpecifier a -> ShowS
$cshow :: forall a. Show a => CAlignmentSpecifier a -> String
show :: CAlignmentSpecifier a -> String
$cshowList :: forall a. Show a => [CAlignmentSpecifier a] -> ShowS
showList :: [CAlignmentSpecifier a] -> ShowS
Show, Typeable (CAlignmentSpecifier a)
Typeable (CAlignmentSpecifier a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> c (CAlignmentSpecifier a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAlignmentSpecifier a))
-> (CAlignmentSpecifier a -> Constr)
-> (CAlignmentSpecifier a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAlignmentSpecifier a)))
-> ((forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CAlignmentSpecifier a
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CAlignmentSpecifier a
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CAlignmentSpecifier a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a))
-> Data (CAlignmentSpecifier a)
CAlignmentSpecifier a -> Constr
CAlignmentSpecifier a -> DataType
(forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
forall a. Data a => Typeable (CAlignmentSpecifier a)
forall a. Data a => CAlignmentSpecifier a -> Constr
forall a. Data a => CAlignmentSpecifier a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAlignmentSpecifier a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAlignmentSpecifier a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> c (CAlignmentSpecifier a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAlignmentSpecifier a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CAlignmentSpecifier a -> u
forall u.
(forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAlignmentSpecifier a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> c (CAlignmentSpecifier a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAlignmentSpecifier a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> c (CAlignmentSpecifier a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> c (CAlignmentSpecifier a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAlignmentSpecifier a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAlignmentSpecifier a)
$ctoConstr :: forall a. Data a => CAlignmentSpecifier a -> Constr
toConstr :: CAlignmentSpecifier a -> Constr
$cdataTypeOf :: forall a. Data a => CAlignmentSpecifier a -> DataType
dataTypeOf :: CAlignmentSpecifier a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAlignmentSpecifier a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAlignmentSpecifier a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
gmapT :: (forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAlignmentSpecifier a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CAlignmentSpecifier a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
Data,Typeable, (forall x. CAlignmentSpecifier a -> Rep (CAlignmentSpecifier a) x)
-> (forall x.
Rep (CAlignmentSpecifier a) x -> CAlignmentSpecifier a)
-> Generic (CAlignmentSpecifier a)
forall x. Rep (CAlignmentSpecifier a) x -> CAlignmentSpecifier a
forall x. CAlignmentSpecifier a -> Rep (CAlignmentSpecifier a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CAlignmentSpecifier a) x -> CAlignmentSpecifier a
forall a x. CAlignmentSpecifier a -> Rep (CAlignmentSpecifier a) x
$cfrom :: forall a x. CAlignmentSpecifier a -> Rep (CAlignmentSpecifier a) x
from :: forall x. CAlignmentSpecifier a -> Rep (CAlignmentSpecifier a) x
$cto :: forall a x. Rep (CAlignmentSpecifier a) x -> CAlignmentSpecifier a
to :: forall x. Rep (CAlignmentSpecifier a) x -> CAlignmentSpecifier a
Generic, (forall a. CAlignmentSpecifier a -> Rep1 CAlignmentSpecifier a)
-> (forall a. Rep1 CAlignmentSpecifier a -> CAlignmentSpecifier a)
-> Generic1 CAlignmentSpecifier
forall a. Rep1 CAlignmentSpecifier a -> CAlignmentSpecifier a
forall a. CAlignmentSpecifier a -> Rep1 CAlignmentSpecifier a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CAlignmentSpecifier a -> Rep1 CAlignmentSpecifier a
from1 :: forall a. CAlignmentSpecifier a -> Rep1 CAlignmentSpecifier a
$cto1 :: forall a. Rep1 CAlignmentSpecifier a -> CAlignmentSpecifier a
to1 :: forall a. Rep1 CAlignmentSpecifier a -> CAlignmentSpecifier a
Generic1 )
instance NFData a => NFData (CAlignmentSpecifier a)
type CStructUnion = CStructureUnion NodeInfo
data CStructureUnion a
= CStruct
CStructTag
(Maybe Ident)
(Maybe [CDeclaration a])
[CAttribute a]
a
deriving (Int -> CStructureUnion a -> ShowS
[CStructureUnion a] -> ShowS
CStructureUnion a -> String
(Int -> CStructureUnion a -> ShowS)
-> (CStructureUnion a -> String)
-> ([CStructureUnion a] -> ShowS)
-> Show (CStructureUnion a)
forall a. Show a => Int -> CStructureUnion a -> ShowS
forall a. Show a => [CStructureUnion a] -> ShowS
forall a. Show a => CStructureUnion a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CStructureUnion a -> ShowS
showsPrec :: Int -> CStructureUnion a -> ShowS
$cshow :: forall a. Show a => CStructureUnion a -> String
show :: CStructureUnion a -> String
$cshowList :: forall a. Show a => [CStructureUnion a] -> ShowS
showList :: [CStructureUnion a] -> ShowS
Show, Typeable (CStructureUnion a)
Typeable (CStructureUnion a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> c (CStructureUnion a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStructureUnion a))
-> (CStructureUnion a -> Constr)
-> (CStructureUnion a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStructureUnion a)))
-> ((forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CStructureUnion a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CStructureUnion a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a))
-> Data (CStructureUnion a)
CStructureUnion a -> Constr
CStructureUnion a -> DataType
(forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
forall a. Data a => Typeable (CStructureUnion a)
forall a. Data a => CStructureUnion a -> Constr
forall a. Data a => CStructureUnion a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStructureUnion a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStructureUnion a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStructureUnion a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> c (CStructureUnion a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStructureUnion a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CStructureUnion a -> u
forall u. (forall d. Data d => d -> u) -> CStructureUnion a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStructureUnion a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> c (CStructureUnion a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStructureUnion a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> c (CStructureUnion a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> c (CStructureUnion a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStructureUnion a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStructureUnion a)
$ctoConstr :: forall a. Data a => CStructureUnion a -> Constr
toConstr :: CStructureUnion a -> Constr
$cdataTypeOf :: forall a. Data a => CStructureUnion a -> DataType
dataTypeOf :: CStructureUnion a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStructureUnion a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStructureUnion a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
gmapT :: (forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStructureUnion a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CStructureUnion a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStructureUnion a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CStructureUnion a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
Data,Typeable, (forall x. CStructureUnion a -> Rep (CStructureUnion a) x)
-> (forall x. Rep (CStructureUnion a) x -> CStructureUnion a)
-> Generic (CStructureUnion a)
forall x. Rep (CStructureUnion a) x -> CStructureUnion a
forall x. CStructureUnion a -> Rep (CStructureUnion a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CStructureUnion a) x -> CStructureUnion a
forall a x. CStructureUnion a -> Rep (CStructureUnion a) x
$cfrom :: forall a x. CStructureUnion a -> Rep (CStructureUnion a) x
from :: forall x. CStructureUnion a -> Rep (CStructureUnion a) x
$cto :: forall a x. Rep (CStructureUnion a) x -> CStructureUnion a
to :: forall x. Rep (CStructureUnion a) x -> CStructureUnion a
Generic, (forall a. CStructureUnion a -> Rep1 CStructureUnion a)
-> (forall a. Rep1 CStructureUnion a -> CStructureUnion a)
-> Generic1 CStructureUnion
forall a. Rep1 CStructureUnion a -> CStructureUnion a
forall a. CStructureUnion a -> Rep1 CStructureUnion a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CStructureUnion a -> Rep1 CStructureUnion a
from1 :: forall a. CStructureUnion a -> Rep1 CStructureUnion a
$cto1 :: forall a. Rep1 CStructureUnion a -> CStructureUnion a
to1 :: forall a. Rep1 CStructureUnion a -> CStructureUnion a
Generic1 )
instance NFData a => NFData (CStructureUnion a)
data CStructTag = CStructTag
| CUnionTag
deriving (Int -> CStructTag -> ShowS
[CStructTag] -> ShowS
CStructTag -> String
(Int -> CStructTag -> ShowS)
-> (CStructTag -> String)
-> ([CStructTag] -> ShowS)
-> Show CStructTag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CStructTag -> ShowS
showsPrec :: Int -> CStructTag -> ShowS
$cshow :: CStructTag -> String
show :: CStructTag -> String
$cshowList :: [CStructTag] -> ShowS
showList :: [CStructTag] -> ShowS
Show, CStructTag -> CStructTag -> Bool
(CStructTag -> CStructTag -> Bool)
-> (CStructTag -> CStructTag -> Bool) -> Eq CStructTag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CStructTag -> CStructTag -> Bool
== :: CStructTag -> CStructTag -> Bool
$c/= :: CStructTag -> CStructTag -> Bool
/= :: CStructTag -> CStructTag -> Bool
Eq,Typeable CStructTag
Typeable CStructTag =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CStructTag)
-> (CStructTag -> Constr)
-> (CStructTag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CStructTag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CStructTag))
-> ((forall b. Data b => b -> b) -> CStructTag -> CStructTag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r)
-> (forall u. (forall d. Data d => d -> u) -> CStructTag -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CStructTag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag)
-> Data CStructTag
CStructTag -> Constr
CStructTag -> DataType
(forall b. Data b => b -> b) -> CStructTag -> CStructTag
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CStructTag -> u
forall u. (forall d. Data d => d -> u) -> CStructTag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CStructTag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CStructTag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CStructTag)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CStructTag
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CStructTag
$ctoConstr :: CStructTag -> Constr
toConstr :: CStructTag -> Constr
$cdataTypeOf :: CStructTag -> DataType
dataTypeOf :: CStructTag -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CStructTag)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CStructTag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CStructTag)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CStructTag)
$cgmapT :: (forall b. Data b => b -> b) -> CStructTag -> CStructTag
gmapT :: (forall b. Data b => b -> b) -> CStructTag -> CStructTag
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CStructTag -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CStructTag -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CStructTag -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CStructTag -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
Data,Typeable, (forall x. CStructTag -> Rep CStructTag x)
-> (forall x. Rep CStructTag x -> CStructTag) -> Generic CStructTag
forall x. Rep CStructTag x -> CStructTag
forall x. CStructTag -> Rep CStructTag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CStructTag -> Rep CStructTag x
from :: forall x. CStructTag -> Rep CStructTag x
$cto :: forall x. Rep CStructTag x -> CStructTag
to :: forall x. Rep CStructTag x -> CStructTag
Generic)
instance NFData CStructTag
type CEnum = CEnumeration NodeInfo
data CEnumeration a
= CEnum
(Maybe Ident)
(Maybe [(Ident,
Maybe (CExpression a))])
[CAttribute a]
a
deriving (Int -> CEnumeration a -> ShowS
[CEnumeration a] -> ShowS
CEnumeration a -> String
(Int -> CEnumeration a -> ShowS)
-> (CEnumeration a -> String)
-> ([CEnumeration a] -> ShowS)
-> Show (CEnumeration a)
forall a. Show a => Int -> CEnumeration a -> ShowS
forall a. Show a => [CEnumeration a] -> ShowS
forall a. Show a => CEnumeration a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CEnumeration a -> ShowS
showsPrec :: Int -> CEnumeration a -> ShowS
$cshow :: forall a. Show a => CEnumeration a -> String
show :: CEnumeration a -> String
$cshowList :: forall a. Show a => [CEnumeration a] -> ShowS
showList :: [CEnumeration a] -> ShowS
Show, Typeable (CEnumeration a)
Typeable (CEnumeration a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> c (CEnumeration a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CEnumeration a))
-> (CEnumeration a -> Constr)
-> (CEnumeration a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CEnumeration a)))
-> ((forall b. Data b => b -> b)
-> CEnumeration a -> CEnumeration a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CEnumeration a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CEnumeration a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a))
-> Data (CEnumeration a)
CEnumeration a -> Constr
CEnumeration a -> DataType
(forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
forall a. Data a => Typeable (CEnumeration a)
forall a. Data a => CEnumeration a -> Constr
forall a. Data a => CEnumeration a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CEnumeration a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CEnumeration a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CEnumeration a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> c (CEnumeration a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CEnumeration a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CEnumeration a -> u
forall u. (forall d. Data d => d -> u) -> CEnumeration a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CEnumeration a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> c (CEnumeration a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CEnumeration a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> c (CEnumeration a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> c (CEnumeration a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CEnumeration a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CEnumeration a)
$ctoConstr :: forall a. Data a => CEnumeration a -> Constr
toConstr :: CEnumeration a -> Constr
$cdataTypeOf :: forall a. Data a => CEnumeration a -> DataType
dataTypeOf :: CEnumeration a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CEnumeration a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CEnumeration a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
gmapT :: (forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CEnumeration a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CEnumeration a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CEnumeration a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CEnumeration a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
Data,Typeable, (forall x. CEnumeration a -> Rep (CEnumeration a) x)
-> (forall x. Rep (CEnumeration a) x -> CEnumeration a)
-> Generic (CEnumeration a)
forall x. Rep (CEnumeration a) x -> CEnumeration a
forall x. CEnumeration a -> Rep (CEnumeration a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CEnumeration a) x -> CEnumeration a
forall a x. CEnumeration a -> Rep (CEnumeration a) x
$cfrom :: forall a x. CEnumeration a -> Rep (CEnumeration a) x
from :: forall x. CEnumeration a -> Rep (CEnumeration a) x
$cto :: forall a x. Rep (CEnumeration a) x -> CEnumeration a
to :: forall x. Rep (CEnumeration a) x -> CEnumeration a
Generic, (forall a. CEnumeration a -> Rep1 CEnumeration a)
-> (forall a. Rep1 CEnumeration a -> CEnumeration a)
-> Generic1 CEnumeration
forall a. Rep1 CEnumeration a -> CEnumeration a
forall a. CEnumeration a -> Rep1 CEnumeration a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CEnumeration a -> Rep1 CEnumeration a
from1 :: forall a. CEnumeration a -> Rep1 CEnumeration a
$cto1 :: forall a. Rep1 CEnumeration a -> CEnumeration a
to1 :: forall a. Rep1 CEnumeration a -> CEnumeration a
Generic1 )
instance NFData a => NFData (CEnumeration a)
type CInit = CInitializer NodeInfo
data CInitializer a
= CInitExpr (CExpression a) a
| CInitList (CInitializerList a) a
deriving (Int -> CInitializer a -> ShowS
[CInitializer a] -> ShowS
CInitializer a -> String
(Int -> CInitializer a -> ShowS)
-> (CInitializer a -> String)
-> ([CInitializer a] -> ShowS)
-> Show (CInitializer a)
forall a. Show a => Int -> CInitializer a -> ShowS
forall a. Show a => [CInitializer a] -> ShowS
forall a. Show a => CInitializer a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CInitializer a -> ShowS
showsPrec :: Int -> CInitializer a -> ShowS
$cshow :: forall a. Show a => CInitializer a -> String
show :: CInitializer a -> String
$cshowList :: forall a. Show a => [CInitializer a] -> ShowS
showList :: [CInitializer a] -> ShowS
Show, Typeable (CInitializer a)
Typeable (CInitializer a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> c (CInitializer a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CInitializer a))
-> (CInitializer a -> Constr)
-> (CInitializer a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CInitializer a)))
-> ((forall b. Data b => b -> b)
-> CInitializer a -> CInitializer a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CInitializer a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CInitializer a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a))
-> Data (CInitializer a)
CInitializer a -> Constr
CInitializer a -> DataType
(forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
forall a. Data a => Typeable (CInitializer a)
forall a. Data a => CInitializer a -> Constr
forall a. Data a => CInitializer a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CInitializer a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CInitializer a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CInitializer a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> c (CInitializer a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CInitializer a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CInitializer a -> u
forall u. (forall d. Data d => d -> u) -> CInitializer a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CInitializer a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> c (CInitializer a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CInitializer a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> c (CInitializer a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> c (CInitializer a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CInitializer a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CInitializer a)
$ctoConstr :: forall a. Data a => CInitializer a -> Constr
toConstr :: CInitializer a -> Constr
$cdataTypeOf :: forall a. Data a => CInitializer a -> DataType
dataTypeOf :: CInitializer a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CInitializer a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CInitializer a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
gmapT :: (forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CInitializer a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CInitializer a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CInitializer a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CInitializer a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
Data,Typeable, (forall x. CInitializer a -> Rep (CInitializer a) x)
-> (forall x. Rep (CInitializer a) x -> CInitializer a)
-> Generic (CInitializer a)
forall x. Rep (CInitializer a) x -> CInitializer a
forall x. CInitializer a -> Rep (CInitializer a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CInitializer a) x -> CInitializer a
forall a x. CInitializer a -> Rep (CInitializer a) x
$cfrom :: forall a x. CInitializer a -> Rep (CInitializer a) x
from :: forall x. CInitializer a -> Rep (CInitializer a) x
$cto :: forall a x. Rep (CInitializer a) x -> CInitializer a
to :: forall x. Rep (CInitializer a) x -> CInitializer a
Generic )
instance NFData a => NFData (CInitializer a)
instance Functor CInitializer where
fmap :: forall a b. (a -> b) -> CInitializer a -> CInitializer b
fmap a -> b
_f (CInitExpr CExpression a
a1 a
a2) = CExpression b -> b -> CInitializer b
forall a. CExpression a -> a -> CInitializer a
CInitExpr ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CInitList CInitializerList a
a1 a
a2) = CInitializerList b -> b -> CInitializer b
forall a. CInitializerList a -> a -> CInitializer a
CInitList ((a -> b) -> CInitializerList a -> CInitializerList b
forall a b. (a -> b) -> CInitializerList a -> CInitializerList b
fmapInitList a -> b
_f CInitializerList a
a1) (a -> b
_f a
a2)
fmapInitList :: (a->b) -> (CInitializerList a) -> (CInitializerList b)
fmapInitList :: forall a b. (a -> b) -> CInitializerList a -> CInitializerList b
fmapInitList a -> b
_f = (([CPartDesignator a], CInitializer a)
-> ([CPartDesignator b], CInitializer b))
-> [([CPartDesignator a], CInitializer a)]
-> [([CPartDesignator b], CInitializer b)]
forall a b. (a -> b) -> [a] -> [b]
map (\([CPartDesignator a]
desigs, CInitializer a
initializer) -> ((CPartDesignator a -> CPartDesignator b)
-> [CPartDesignator a] -> [CPartDesignator b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CPartDesignator a -> CPartDesignator b
forall a b. (a -> b) -> CPartDesignator a -> CPartDesignator b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CPartDesignator a]
desigs, (a -> b) -> CInitializer a -> CInitializer b
forall a b. (a -> b) -> CInitializer a -> CInitializer b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CInitializer a
initializer))
type CInitList = CInitializerList NodeInfo
type CInitializerList a = [([CPartDesignator a], CInitializer a)]
type CDesignator = CPartDesignator NodeInfo
data CPartDesignator a
= CArrDesig (CExpression a) a
| CMemberDesig Ident a
| CRangeDesig (CExpression a) (CExpression a) a
deriving (Int -> CPartDesignator a -> ShowS
[CPartDesignator a] -> ShowS
CPartDesignator a -> String
(Int -> CPartDesignator a -> ShowS)
-> (CPartDesignator a -> String)
-> ([CPartDesignator a] -> ShowS)
-> Show (CPartDesignator a)
forall a. Show a => Int -> CPartDesignator a -> ShowS
forall a. Show a => [CPartDesignator a] -> ShowS
forall a. Show a => CPartDesignator a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CPartDesignator a -> ShowS
showsPrec :: Int -> CPartDesignator a -> ShowS
$cshow :: forall a. Show a => CPartDesignator a -> String
show :: CPartDesignator a -> String
$cshowList :: forall a. Show a => [CPartDesignator a] -> ShowS
showList :: [CPartDesignator a] -> ShowS
Show, Typeable (CPartDesignator a)
Typeable (CPartDesignator a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> c (CPartDesignator a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CPartDesignator a))
-> (CPartDesignator a -> Constr)
-> (CPartDesignator a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CPartDesignator a)))
-> ((forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CPartDesignator a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CPartDesignator a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a))
-> Data (CPartDesignator a)
CPartDesignator a -> Constr
CPartDesignator a -> DataType
(forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
forall a. Data a => Typeable (CPartDesignator a)
forall a. Data a => CPartDesignator a -> Constr
forall a. Data a => CPartDesignator a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CPartDesignator a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CPartDesignator a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CPartDesignator a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> c (CPartDesignator a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CPartDesignator a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CPartDesignator a -> u
forall u. (forall d. Data d => d -> u) -> CPartDesignator a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CPartDesignator a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> c (CPartDesignator a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CPartDesignator a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> c (CPartDesignator a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> c (CPartDesignator a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CPartDesignator a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CPartDesignator a)
$ctoConstr :: forall a. Data a => CPartDesignator a -> Constr
toConstr :: CPartDesignator a -> Constr
$cdataTypeOf :: forall a. Data a => CPartDesignator a -> DataType
dataTypeOf :: CPartDesignator a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CPartDesignator a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CPartDesignator a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
gmapT :: (forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CPartDesignator a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CPartDesignator a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CPartDesignator a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CPartDesignator a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
Data,Typeable, (forall x. CPartDesignator a -> Rep (CPartDesignator a) x)
-> (forall x. Rep (CPartDesignator a) x -> CPartDesignator a)
-> Generic (CPartDesignator a)
forall x. Rep (CPartDesignator a) x -> CPartDesignator a
forall x. CPartDesignator a -> Rep (CPartDesignator a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CPartDesignator a) x -> CPartDesignator a
forall a x. CPartDesignator a -> Rep (CPartDesignator a) x
$cfrom :: forall a x. CPartDesignator a -> Rep (CPartDesignator a) x
from :: forall x. CPartDesignator a -> Rep (CPartDesignator a) x
$cto :: forall a x. Rep (CPartDesignator a) x -> CPartDesignator a
to :: forall x. Rep (CPartDesignator a) x -> CPartDesignator a
Generic )
instance NFData a => NFData (CPartDesignator a)
type CAttr = CAttribute NodeInfo
data CAttribute a = CAttr Ident [CExpression a] a
deriving (Int -> CAttribute a -> ShowS
[CAttribute a] -> ShowS
CAttribute a -> String
(Int -> CAttribute a -> ShowS)
-> (CAttribute a -> String)
-> ([CAttribute a] -> ShowS)
-> Show (CAttribute a)
forall a. Show a => Int -> CAttribute a -> ShowS
forall a. Show a => [CAttribute a] -> ShowS
forall a. Show a => CAttribute a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CAttribute a -> ShowS
showsPrec :: Int -> CAttribute a -> ShowS
$cshow :: forall a. Show a => CAttribute a -> String
show :: CAttribute a -> String
$cshowList :: forall a. Show a => [CAttribute a] -> ShowS
showList :: [CAttribute a] -> ShowS
Show, Typeable (CAttribute a)
Typeable (CAttribute a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> c (CAttribute a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAttribute a))
-> (CAttribute a -> Constr)
-> (CAttribute a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAttribute a)))
-> ((forall b. Data b => b -> b) -> CAttribute a -> CAttribute a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r)
-> (forall u. (forall d. Data d => d -> u) -> CAttribute a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CAttribute a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a))
-> Data (CAttribute a)
CAttribute a -> Constr
CAttribute a -> DataType
(forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
forall a. Data a => Typeable (CAttribute a)
forall a. Data a => CAttribute a -> Constr
forall a. Data a => CAttribute a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAttribute a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAttribute a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAttribute a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> c (CAttribute a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAttribute a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CAttribute a -> u
forall u. (forall d. Data d => d -> u) -> CAttribute a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAttribute a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> c (CAttribute a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAttribute a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> c (CAttribute a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> c (CAttribute a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAttribute a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAttribute a)
$ctoConstr :: forall a. Data a => CAttribute a -> Constr
toConstr :: CAttribute a -> Constr
$cdataTypeOf :: forall a. Data a => CAttribute a -> DataType
dataTypeOf :: CAttribute a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAttribute a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CAttribute a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
gmapT :: (forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAttribute a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CAttribute a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CAttribute a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CAttribute a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
Data,Typeable, (forall x. CAttribute a -> Rep (CAttribute a) x)
-> (forall x. Rep (CAttribute a) x -> CAttribute a)
-> Generic (CAttribute a)
forall x. Rep (CAttribute a) x -> CAttribute a
forall x. CAttribute a -> Rep (CAttribute a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CAttribute a) x -> CAttribute a
forall a x. CAttribute a -> Rep (CAttribute a) x
$cfrom :: forall a x. CAttribute a -> Rep (CAttribute a) x
from :: forall x. CAttribute a -> Rep (CAttribute a) x
$cto :: forall a x. Rep (CAttribute a) x -> CAttribute a
to :: forall x. Rep (CAttribute a) x -> CAttribute a
Generic, (forall a. CAttribute a -> Rep1 CAttribute a)
-> (forall a. Rep1 CAttribute a -> CAttribute a)
-> Generic1 CAttribute
forall a. Rep1 CAttribute a -> CAttribute a
forall a. CAttribute a -> Rep1 CAttribute a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CAttribute a -> Rep1 CAttribute a
from1 :: forall a. CAttribute a -> Rep1 CAttribute a
$cto1 :: forall a. Rep1 CAttribute a -> CAttribute a
to1 :: forall a. Rep1 CAttribute a -> CAttribute a
Generic1 )
instance NFData a => NFData (CAttribute a)
type CExpr = CExpression NodeInfo
data CExpression a
= CComma [CExpression a]
a
| CAssign CAssignOp
(CExpression a)
(CExpression a)
a
| CCond (CExpression a)
(Maybe (CExpression a))
(CExpression a)
a
| CBinary CBinaryOp
(CExpression a)
(CExpression a)
a
| CCast (CDeclaration a)
(CExpression a)
a
| CUnary CUnaryOp
(CExpression a)
a
| CSizeofExpr (CExpression a)
a
| CSizeofType (CDeclaration a)
a
| CAlignofExpr (CExpression a)
a
| CAlignofType (CDeclaration a)
a
| CComplexReal (CExpression a)
a
| CComplexImag (CExpression a)
a
| CIndex (CExpression a)
(CExpression a)
a
| CCall (CExpression a)
[CExpression a]
a
| CMember (CExpression a)
Ident
Bool
a
| CVar Ident
a
| CConst (CConstant a)
| CCompoundLit (CDeclaration a)
(CInitializerList a)
a
| CGenericSelection (CExpression a) [(Maybe (CDeclaration a), CExpression a)] a
| CStatExpr (CStatement a) a
| CLabAddrExpr Ident a
| CBuiltinExpr (CBuiltinThing a)
deriving (Typeable (CExpression a)
Typeable (CExpression a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> c (CExpression a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExpression a))
-> (CExpression a -> Constr)
-> (CExpression a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExpression a)))
-> ((forall b. Data b => b -> b) -> CExpression a -> CExpression a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r)
-> (forall u. (forall d. Data d => d -> u) -> CExpression a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CExpression a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a))
-> Data (CExpression a)
CExpression a -> Constr
CExpression a -> DataType
(forall b. Data b => b -> b) -> CExpression a -> CExpression a
forall a. Data a => Typeable (CExpression a)
forall a. Data a => CExpression a -> Constr
forall a. Data a => CExpression a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CExpression a -> CExpression a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CExpression a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CExpression a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExpression a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> c (CExpression a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExpression a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CExpression a -> u
forall u. (forall d. Data d => d -> u) -> CExpression a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExpression a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> c (CExpression a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExpression a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> c (CExpression a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> c (CExpression a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExpression a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExpression a)
$ctoConstr :: forall a. Data a => CExpression a -> Constr
toConstr :: CExpression a -> Constr
$cdataTypeOf :: forall a. Data a => CExpression a -> DataType
dataTypeOf :: CExpression a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExpression a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CExpression a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CExpression a -> CExpression a
gmapT :: (forall b. Data b => b -> b) -> CExpression a -> CExpression a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CExpression a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CExpression a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CExpression a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CExpression a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
Data,Typeable,Int -> CExpression a -> ShowS
[CExpression a] -> ShowS
CExpression a -> String
(Int -> CExpression a -> ShowS)
-> (CExpression a -> String)
-> ([CExpression a] -> ShowS)
-> Show (CExpression a)
forall a. Show a => Int -> CExpression a -> ShowS
forall a. Show a => [CExpression a] -> ShowS
forall a. Show a => CExpression a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CExpression a -> ShowS
showsPrec :: Int -> CExpression a -> ShowS
$cshow :: forall a. Show a => CExpression a -> String
show :: CExpression a -> String
$cshowList :: forall a. Show a => [CExpression a] -> ShowS
showList :: [CExpression a] -> ShowS
Show, (forall x. CExpression a -> Rep (CExpression a) x)
-> (forall x. Rep (CExpression a) x -> CExpression a)
-> Generic (CExpression a)
forall x. Rep (CExpression a) x -> CExpression a
forall x. CExpression a -> Rep (CExpression a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CExpression a) x -> CExpression a
forall a x. CExpression a -> Rep (CExpression a) x
$cfrom :: forall a x. CExpression a -> Rep (CExpression a) x
from :: forall x. CExpression a -> Rep (CExpression a) x
$cto :: forall a x. Rep (CExpression a) x -> CExpression a
to :: forall x. Rep (CExpression a) x -> CExpression a
Generic )
instance NFData a => NFData (CExpression a)
instance Functor CExpression where
fmap :: forall a b. (a -> b) -> CExpression a -> CExpression b
fmap a -> b
_f (CComma [CExpression a]
a1 a
a2) = [CExpression b] -> b -> CExpression b
forall a. [CExpression a] -> a -> CExpression a
CComma ((CExpression a -> CExpression b)
-> [CExpression a] -> [CExpression b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CExpression a]
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CAssign CAssignOp
a1 CExpression a
a2 CExpression a
a3 a
a4)
= CAssignOp -> CExpression b -> CExpression b -> b -> CExpression b
forall a.
CAssignOp -> CExpression a -> CExpression a -> a -> CExpression a
CAssign CAssignOp
a1 ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
fmap a -> b
_f (CCond CExpression a
a1 Maybe (CExpression a)
a2 CExpression a
a3 a
a4)
= CExpression b
-> Maybe (CExpression b) -> CExpression b -> b -> CExpression b
forall a.
CExpression a
-> Maybe (CExpression a) -> CExpression a -> a -> CExpression a
CCond ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CExpression a)
a2) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
fmap a -> b
_f (CBinary CBinaryOp
a1 CExpression a
a2 CExpression a
a3 a
a4)
= CBinaryOp -> CExpression b -> CExpression b -> b -> CExpression b
forall a.
CBinaryOp -> CExpression a -> CExpression a -> a -> CExpression a
CBinary CBinaryOp
a1 ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
fmap a -> b
_f (CCast CDeclaration a
a1 CExpression a
a2 a
a3) = CDeclaration b -> CExpression b -> b -> CExpression b
forall a. CDeclaration a -> CExpression a -> a -> CExpression a
CCast ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CUnary CUnaryOp
a1 CExpression a
a2 a
a3) = CUnaryOp -> CExpression b -> b -> CExpression b
forall a. CUnaryOp -> CExpression a -> a -> CExpression a
CUnary CUnaryOp
a1 ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CSizeofExpr CExpression a
a1 a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CSizeofExpr ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CSizeofType CDeclaration a
a1 a
a2) = CDeclaration b -> b -> CExpression b
forall a. CDeclaration a -> a -> CExpression a
CSizeofType ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CAlignofExpr CExpression a
a1 a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CAlignofExpr ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CAlignofType CDeclaration a
a1 a
a2) = CDeclaration b -> b -> CExpression b
forall a. CDeclaration a -> a -> CExpression a
CAlignofType ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CComplexReal CExpression a
a1 a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CComplexReal ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CComplexImag CExpression a
a1 a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CComplexImag ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CIndex CExpression a
a1 CExpression a
a2 a
a3)
= CExpression b -> CExpression b -> b -> CExpression b
forall a. CExpression a -> CExpression a -> a -> CExpression a
CIndex ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CCall CExpression a
a1 [CExpression a]
a2 a
a3)
= CExpression b -> [CExpression b] -> b -> CExpression b
forall a. CExpression a -> [CExpression a] -> a -> CExpression a
CCall ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((CExpression a -> CExpression b)
-> [CExpression a] -> [CExpression b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CExpression a]
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CMember CExpression a
a1 Ident
a2 Bool
a3 a
a4) = CExpression b -> Ident -> Bool -> b -> CExpression b
forall a. CExpression a -> Ident -> Bool -> a -> CExpression a
CMember ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) Ident
a2 Bool
a3 (a -> b
_f a
a4)
fmap a -> b
_f (CVar Ident
a1 a
a2) = Ident -> b -> CExpression b
forall a. Ident -> a -> CExpression a
CVar Ident
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CConst CConstant a
a1) = CConstant b -> CExpression b
forall a. CConstant a -> CExpression a
CConst ((a -> b) -> CConstant a -> CConstant b
forall a b. (a -> b) -> CConstant a -> CConstant b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CConstant a
a1)
fmap a -> b
_f (CCompoundLit CDeclaration a
a1 CInitializerList a
a2 a
a3)
= CDeclaration b -> CInitializerList b -> b -> CExpression b
forall a.
CDeclaration a -> CInitializerList a -> a -> CExpression a
CCompoundLit ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) ((a -> b) -> CInitializerList a -> CInitializerList b
forall a b. (a -> b) -> CInitializerList a -> CInitializerList b
fmapInitList a -> b
_f CInitializerList a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CStatExpr CStatement a
a1 a
a2) = CStatement b -> b -> CExpression b
forall a. CStatement a -> a -> CExpression a
CStatExpr ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CLabAddrExpr Ident
a1 a
a2) = Ident -> b -> CExpression b
forall a. Ident -> a -> CExpression a
CLabAddrExpr Ident
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CBuiltinExpr CBuiltinThing a
a1) = CBuiltinThing b -> CExpression b
forall a. CBuiltinThing a -> CExpression a
CBuiltinExpr ((a -> b) -> CBuiltinThing a -> CBuiltinThing b
forall a b. (a -> b) -> CBuiltinThing a -> CBuiltinThing b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CBuiltinThing a
a1)
fmap a -> b
_f (CGenericSelection CExpression a
expr [(Maybe (CDeclaration a), CExpression a)]
list a
annot) =
CExpression b
-> [(Maybe (CDeclaration b), CExpression b)] -> b -> CExpression b
forall a.
CExpression a
-> [(Maybe (CDeclaration a), CExpression a)] -> a -> CExpression a
CGenericSelection ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
expr) (((Maybe (CDeclaration a), CExpression a)
-> (Maybe (CDeclaration b), CExpression b))
-> [(Maybe (CDeclaration a), CExpression a)]
-> [(Maybe (CDeclaration b), CExpression b)]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe (CDeclaration a), CExpression a)
-> (Maybe (CDeclaration b), CExpression b)
forall {f :: * -> *} {f :: * -> *} {f :: * -> *}.
(Functor f, Functor f, Functor f) =>
(f (f a), f a) -> (f (f b), f b)
fmap_helper [(Maybe (CDeclaration a), CExpression a)]
list) (a -> b
_f a
annot)
where
fmap_helper :: (f (f a), f a) -> (f (f b), f b)
fmap_helper (f (f a)
ma1, f a
a2) = ((f a -> f b) -> f (f a) -> f (f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> f a -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) f (f a)
ma1, (a -> b) -> f a -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f f a
a2)
type CBuiltin = CBuiltinThing NodeInfo
data CBuiltinThing a
= CBuiltinVaArg (CExpression a) (CDeclaration a) a
| CBuiltinOffsetOf (CDeclaration a) [CPartDesignator a] a
| CBuiltinTypesCompatible (CDeclaration a) (CDeclaration a) a
| CBuiltinConvertVector (CExpression a) (CDeclaration a) a
| CBuiltinBitCast (CDeclaration a) (CExpression a) a
deriving (Int -> CBuiltinThing a -> ShowS
[CBuiltinThing a] -> ShowS
CBuiltinThing a -> String
(Int -> CBuiltinThing a -> ShowS)
-> (CBuiltinThing a -> String)
-> ([CBuiltinThing a] -> ShowS)
-> Show (CBuiltinThing a)
forall a. Show a => Int -> CBuiltinThing a -> ShowS
forall a. Show a => [CBuiltinThing a] -> ShowS
forall a. Show a => CBuiltinThing a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CBuiltinThing a -> ShowS
showsPrec :: Int -> CBuiltinThing a -> ShowS
$cshow :: forall a. Show a => CBuiltinThing a -> String
show :: CBuiltinThing a -> String
$cshowList :: forall a. Show a => [CBuiltinThing a] -> ShowS
showList :: [CBuiltinThing a] -> ShowS
Show, Typeable (CBuiltinThing a)
Typeable (CBuiltinThing a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> c (CBuiltinThing a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CBuiltinThing a))
-> (CBuiltinThing a -> Constr)
-> (CBuiltinThing a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CBuiltinThing a)))
-> ((forall b. Data b => b -> b)
-> CBuiltinThing a -> CBuiltinThing a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CBuiltinThing a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CBuiltinThing a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a))
-> Data (CBuiltinThing a)
CBuiltinThing a -> Constr
CBuiltinThing a -> DataType
(forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
forall a. Data a => Typeable (CBuiltinThing a)
forall a. Data a => CBuiltinThing a -> Constr
forall a. Data a => CBuiltinThing a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CBuiltinThing a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CBuiltinThing a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CBuiltinThing a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> c (CBuiltinThing a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CBuiltinThing a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CBuiltinThing a -> u
forall u. (forall d. Data d => d -> u) -> CBuiltinThing a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CBuiltinThing a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> c (CBuiltinThing a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CBuiltinThing a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> c (CBuiltinThing a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> c (CBuiltinThing a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CBuiltinThing a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CBuiltinThing a)
$ctoConstr :: forall a. Data a => CBuiltinThing a -> Constr
toConstr :: CBuiltinThing a -> Constr
$cdataTypeOf :: forall a. Data a => CBuiltinThing a -> DataType
dataTypeOf :: CBuiltinThing a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CBuiltinThing a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CBuiltinThing a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
gmapT :: (forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CBuiltinThing a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CBuiltinThing a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CBuiltinThing a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CBuiltinThing a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
Data,Typeable, (forall x. CBuiltinThing a -> Rep (CBuiltinThing a) x)
-> (forall x. Rep (CBuiltinThing a) x -> CBuiltinThing a)
-> Generic (CBuiltinThing a)
forall x. Rep (CBuiltinThing a) x -> CBuiltinThing a
forall x. CBuiltinThing a -> Rep (CBuiltinThing a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CBuiltinThing a) x -> CBuiltinThing a
forall a x. CBuiltinThing a -> Rep (CBuiltinThing a) x
$cfrom :: forall a x. CBuiltinThing a -> Rep (CBuiltinThing a) x
from :: forall x. CBuiltinThing a -> Rep (CBuiltinThing a) x
$cto :: forall a x. Rep (CBuiltinThing a) x -> CBuiltinThing a
to :: forall x. Rep (CBuiltinThing a) x -> CBuiltinThing a
Generic )
instance NFData a => NFData (CBuiltinThing a)
type CConst = CConstant NodeInfo
data CConstant a
= CIntConst CInteger a
| CCharConst CChar a
| CFloatConst CFloat a
| CStrConst CString a
deriving (Int -> CConstant a -> ShowS
[CConstant a] -> ShowS
CConstant a -> String
(Int -> CConstant a -> ShowS)
-> (CConstant a -> String)
-> ([CConstant a] -> ShowS)
-> Show (CConstant a)
forall a. Show a => Int -> CConstant a -> ShowS
forall a. Show a => [CConstant a] -> ShowS
forall a. Show a => CConstant a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CConstant a -> ShowS
showsPrec :: Int -> CConstant a -> ShowS
$cshow :: forall a. Show a => CConstant a -> String
show :: CConstant a -> String
$cshowList :: forall a. Show a => [CConstant a] -> ShowS
showList :: [CConstant a] -> ShowS
Show, Typeable (CConstant a)
Typeable (CConstant a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> c (CConstant a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CConstant a))
-> (CConstant a -> Constr)
-> (CConstant a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CConstant a)))
-> ((forall b. Data b => b -> b) -> CConstant a -> CConstant a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r)
-> (forall u. (forall d. Data d => d -> u) -> CConstant a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CConstant a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a))
-> Data (CConstant a)
CConstant a -> Constr
CConstant a -> DataType
(forall b. Data b => b -> b) -> CConstant a -> CConstant a
forall a. Data a => Typeable (CConstant a)
forall a. Data a => CConstant a -> Constr
forall a. Data a => CConstant a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> CConstant a -> CConstant a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CConstant a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CConstant a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CConstant a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> c (CConstant a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CConstant a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CConstant a -> u
forall u. (forall d. Data d => d -> u) -> CConstant a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CConstant a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> c (CConstant a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CConstant a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> c (CConstant a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> c (CConstant a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CConstant a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CConstant a)
$ctoConstr :: forall a. Data a => CConstant a -> Constr
toConstr :: CConstant a -> Constr
$cdataTypeOf :: forall a. Data a => CConstant a -> DataType
dataTypeOf :: CConstant a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CConstant a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CConstant a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CConstant a -> CConstant a
gmapT :: (forall b. Data b => b -> b) -> CConstant a -> CConstant a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CConstant a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CConstant a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CConstant a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CConstant a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
Data,Typeable, (forall x. CConstant a -> Rep (CConstant a) x)
-> (forall x. Rep (CConstant a) x -> CConstant a)
-> Generic (CConstant a)
forall x. Rep (CConstant a) x -> CConstant a
forall x. CConstant a -> Rep (CConstant a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CConstant a) x -> CConstant a
forall a x. CConstant a -> Rep (CConstant a) x
$cfrom :: forall a x. CConstant a -> Rep (CConstant a) x
from :: forall x. CConstant a -> Rep (CConstant a) x
$cto :: forall a x. Rep (CConstant a) x -> CConstant a
to :: forall x. Rep (CConstant a) x -> CConstant a
Generic, (forall a. CConstant a -> Rep1 CConstant a)
-> (forall a. Rep1 CConstant a -> CConstant a)
-> Generic1 CConstant
forall a. Rep1 CConstant a -> CConstant a
forall a. CConstant a -> Rep1 CConstant a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CConstant a -> Rep1 CConstant a
from1 :: forall a. CConstant a -> Rep1 CConstant a
$cto1 :: forall a. Rep1 CConstant a -> CConstant a
to1 :: forall a. Rep1 CConstant a -> CConstant a
Generic1 )
instance NFData a => NFData (CConstant a)
type CStrLit = CStringLiteral NodeInfo
data CStringLiteral a = CStrLit CString a
deriving (Int -> CStringLiteral a -> ShowS
[CStringLiteral a] -> ShowS
CStringLiteral a -> String
(Int -> CStringLiteral a -> ShowS)
-> (CStringLiteral a -> String)
-> ([CStringLiteral a] -> ShowS)
-> Show (CStringLiteral a)
forall a. Show a => Int -> CStringLiteral a -> ShowS
forall a. Show a => [CStringLiteral a] -> ShowS
forall a. Show a => CStringLiteral a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> CStringLiteral a -> ShowS
showsPrec :: Int -> CStringLiteral a -> ShowS
$cshow :: forall a. Show a => CStringLiteral a -> String
show :: CStringLiteral a -> String
$cshowList :: forall a. Show a => [CStringLiteral a] -> ShowS
showList :: [CStringLiteral a] -> ShowS
Show, Typeable (CStringLiteral a)
Typeable (CStringLiteral a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStringLiteral a
-> c (CStringLiteral a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStringLiteral a))
-> (CStringLiteral a -> Constr)
-> (CStringLiteral a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStringLiteral a)))
-> ((forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CStringLiteral a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CStringLiteral a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a))
-> Data (CStringLiteral a)
CStringLiteral a -> Constr
CStringLiteral a -> DataType
(forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
forall a. Data a => Typeable (CStringLiteral a)
forall a. Data a => CStringLiteral a -> Constr
forall a. Data a => CStringLiteral a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStringLiteral a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStringLiteral a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStringLiteral a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStringLiteral a -> c (CStringLiteral a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStringLiteral a))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CStringLiteral a -> u
forall u. (forall d. Data d => d -> u) -> CStringLiteral a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStringLiteral a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStringLiteral a -> c (CStringLiteral a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStringLiteral a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStringLiteral a -> c (CStringLiteral a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStringLiteral a -> c (CStringLiteral a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStringLiteral a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStringLiteral a)
$ctoConstr :: forall a. Data a => CStringLiteral a -> Constr
toConstr :: CStringLiteral a -> Constr
$cdataTypeOf :: forall a. Data a => CStringLiteral a -> DataType
dataTypeOf :: CStringLiteral a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStringLiteral a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CStringLiteral a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
gmapT :: (forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStringLiteral a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CStringLiteral a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> CStringLiteral a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CStringLiteral a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
Data,Typeable, (forall x. CStringLiteral a -> Rep (CStringLiteral a) x)
-> (forall x. Rep (CStringLiteral a) x -> CStringLiteral a)
-> Generic (CStringLiteral a)
forall x. Rep (CStringLiteral a) x -> CStringLiteral a
forall x. CStringLiteral a -> Rep (CStringLiteral a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CStringLiteral a) x -> CStringLiteral a
forall a x. CStringLiteral a -> Rep (CStringLiteral a) x
$cfrom :: forall a x. CStringLiteral a -> Rep (CStringLiteral a) x
from :: forall x. CStringLiteral a -> Rep (CStringLiteral a) x
$cto :: forall a x. Rep (CStringLiteral a) x -> CStringLiteral a
to :: forall x. Rep (CStringLiteral a) x -> CStringLiteral a
Generic, (forall a. CStringLiteral a -> Rep1 CStringLiteral a)
-> (forall a. Rep1 CStringLiteral a -> CStringLiteral a)
-> Generic1 CStringLiteral
forall a. Rep1 CStringLiteral a -> CStringLiteral a
forall a. CStringLiteral a -> Rep1 CStringLiteral a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a. CStringLiteral a -> Rep1 CStringLiteral a
from1 :: forall a. CStringLiteral a -> Rep1 CStringLiteral a
$cto1 :: forall a. Rep1 CStringLiteral a -> CStringLiteral a
to1 :: forall a. Rep1 CStringLiteral a -> CStringLiteral a
Generic1 )
instance NFData a => NFData (CStringLiteral a)
cstringOfLit :: CStringLiteral a -> CString
cstringOfLit :: forall a. CStringLiteral a -> CString
cstringOfLit (CStrLit CString
cstr a
_) = CString
cstr
liftStrLit :: CStringLiteral a -> CConstant a
liftStrLit :: forall a. CStringLiteral a -> CConstant a
liftStrLit (CStrLit CString
str a
at) = CString -> a -> CConstant a
forall a. CString -> a -> CConstant a
CStrConst CString
str a
at
class (Functor ast) => Annotated ast where
annotation :: ast a -> a
amap :: (a->a) -> ast a -> ast a
instance CNode t1 => CNode (CTranslationUnit t1) where
nodeInfo :: CTranslationUnit t1 -> NodeInfo
nodeInfo (CTranslUnit [CExternalDeclaration t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CTranslationUnit t1) where
posOf :: CTranslationUnit t1 -> Position
posOf CTranslationUnit t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CTranslationUnit t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTranslationUnit t1
x)
instance Functor CTranslationUnit where
fmap :: forall a b. (a -> b) -> CTranslationUnit a -> CTranslationUnit b
fmap a -> b
_f (CTranslUnit [CExternalDeclaration a]
a1 a
a2)
= [CExternalDeclaration b] -> b -> CTranslationUnit b
forall a. [CExternalDeclaration a] -> a -> CTranslationUnit a
CTranslUnit ((CExternalDeclaration a -> CExternalDeclaration b)
-> [CExternalDeclaration a] -> [CExternalDeclaration b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExternalDeclaration a -> CExternalDeclaration b
forall a b.
(a -> b) -> CExternalDeclaration a -> CExternalDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CExternalDeclaration a]
a1) (a -> b
_f a
a2)
instance Annotated CTranslationUnit where
annotation :: forall a. CTranslationUnit a -> a
annotation (CTranslUnit [CExternalDeclaration a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CTranslationUnit a -> CTranslationUnit a
amap a -> a
f (CTranslUnit [CExternalDeclaration a]
a_1 a
a_2) = [CExternalDeclaration a] -> a -> CTranslationUnit a
forall a. [CExternalDeclaration a] -> a -> CTranslationUnit a
CTranslUnit [CExternalDeclaration a]
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CExternalDeclaration t1) where
nodeInfo :: CExternalDeclaration t1 -> NodeInfo
nodeInfo (CDeclExt CDeclaration t1
d) = CDeclaration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclaration t1
d
nodeInfo (CFDefExt CFunctionDef t1
d) = CFunctionDef t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionDef t1
d
nodeInfo (CAsmExt CStringLiteral t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CExternalDeclaration t1) where
posOf :: CExternalDeclaration t1 -> Position
posOf CExternalDeclaration t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CExternalDeclaration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CExternalDeclaration t1
x)
instance Functor CExternalDeclaration where
fmap :: forall a b.
(a -> b) -> CExternalDeclaration a -> CExternalDeclaration b
fmap a -> b
_f (CDeclExt CDeclaration a
a1) = CDeclaration b -> CExternalDeclaration b
forall a. CDeclaration a -> CExternalDeclaration a
CDeclExt ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1)
fmap a -> b
_f (CFDefExt CFunctionDef a
a1) = CFunctionDef b -> CExternalDeclaration b
forall a. CFunctionDef a -> CExternalDeclaration a
CFDefExt ((a -> b) -> CFunctionDef a -> CFunctionDef b
forall a b. (a -> b) -> CFunctionDef a -> CFunctionDef b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CFunctionDef a
a1)
fmap a -> b
_f (CAsmExt CStringLiteral a
a1 a
a2) = CStringLiteral b -> b -> CExternalDeclaration b
forall a. CStringLiteral a -> a -> CExternalDeclaration a
CAsmExt ((a -> b) -> CStringLiteral a -> CStringLiteral b
forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStringLiteral a
a1) (a -> b
_f a
a2)
instance Annotated CExternalDeclaration where
annotation :: forall a. CExternalDeclaration a -> a
annotation (CDeclExt CDeclaration a
n) = CDeclaration a -> a
forall a. CDeclaration a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CDeclaration a
n
annotation (CFDefExt CFunctionDef a
n) = CFunctionDef a -> a
forall a. CFunctionDef a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CFunctionDef a
n
annotation (CAsmExt CStringLiteral a
_ a
n) = a
n
amap :: forall a.
(a -> a) -> CExternalDeclaration a -> CExternalDeclaration a
amap a -> a
f (CDeclExt CDeclaration a
n) = CDeclaration a -> CExternalDeclaration a
forall a. CDeclaration a -> CExternalDeclaration a
CDeclExt ((a -> a) -> CDeclaration a -> CDeclaration a
forall a. (a -> a) -> CDeclaration a -> CDeclaration a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CDeclaration a
n)
amap a -> a
f (CFDefExt CFunctionDef a
n) = CFunctionDef a -> CExternalDeclaration a
forall a. CFunctionDef a -> CExternalDeclaration a
CFDefExt ((a -> a) -> CFunctionDef a -> CFunctionDef a
forall a. (a -> a) -> CFunctionDef a -> CFunctionDef a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CFunctionDef a
n)
amap a -> a
f (CAsmExt CStringLiteral a
a_1 a
a_2) = CStringLiteral a -> a -> CExternalDeclaration a
forall a. CStringLiteral a -> a -> CExternalDeclaration a
CAsmExt CStringLiteral a
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CFunctionDef t1) where
nodeInfo :: CFunctionDef t1 -> NodeInfo
nodeInfo (CFunDef [CDeclarationSpecifier t1]
_ CDeclarator t1
_ [CDeclaration t1]
_ CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CFunctionDef t1) where
posOf :: CFunctionDef t1 -> Position
posOf CFunctionDef t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CFunctionDef t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionDef t1
x)
instance Functor CFunctionDef where
fmap :: forall a b. (a -> b) -> CFunctionDef a -> CFunctionDef b
fmap a -> b
_f (CFunDef [CDeclarationSpecifier a]
a1 CDeclarator a
a2 [CDeclaration a]
a3 CStatement a
a4 a
a5)
= [CDeclarationSpecifier b]
-> CDeclarator b
-> [CDeclaration b]
-> CStatement b
-> b
-> CFunctionDef b
forall a.
[CDeclarationSpecifier a]
-> CDeclarator a
-> [CDeclaration a]
-> CStatement a
-> a
-> CFunctionDef a
CFunDef ((CDeclarationSpecifier a -> CDeclarationSpecifier b)
-> [CDeclarationSpecifier a] -> [CDeclarationSpecifier b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CDeclarationSpecifier a -> CDeclarationSpecifier b
forall a b.
(a -> b) -> CDeclarationSpecifier a -> CDeclarationSpecifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CDeclarationSpecifier a]
a1) ((a -> b) -> CDeclarator a -> CDeclarator b
forall a b. (a -> b) -> CDeclarator a -> CDeclarator b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclarator a
a2) ((CDeclaration a -> CDeclaration b)
-> [CDeclaration a] -> [CDeclaration b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CDeclaration a]
a3)
((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a4)
(a -> b
_f a
a5)
instance Annotated CFunctionDef where
annotation :: forall a. CFunctionDef a -> a
annotation (CFunDef [CDeclarationSpecifier a]
_ CDeclarator a
_ [CDeclaration a]
_ CStatement a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CFunctionDef a -> CFunctionDef a
amap a -> a
f (CFunDef [CDeclarationSpecifier a]
a_1 CDeclarator a
a_2 [CDeclaration a]
a_3 CStatement a
a_4 a
a_5)
= [CDeclarationSpecifier a]
-> CDeclarator a
-> [CDeclaration a]
-> CStatement a
-> a
-> CFunctionDef a
forall a.
[CDeclarationSpecifier a]
-> CDeclarator a
-> [CDeclaration a]
-> CStatement a
-> a
-> CFunctionDef a
CFunDef [CDeclarationSpecifier a]
a_1 CDeclarator a
a_2 [CDeclaration a]
a_3 CStatement a
a_4 (a -> a
f a
a_5)
instance CNode t1 => CNode (CDeclaration t1) where
nodeInfo :: CDeclaration t1 -> NodeInfo
nodeInfo (CDecl [CDeclarationSpecifier t1]
_ [(Maybe (CDeclarator t1), Maybe (CInitializer t1),
Maybe (CExpression t1))]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CStaticAssert CExpression t1
_ CStringLiteral t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CDeclaration t1) where
posOf :: CDeclaration t1 -> Position
posOf CDeclaration t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CDeclaration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclaration t1
x)
instance Annotated CDeclaration where
annotation :: forall a. CDeclaration a -> a
annotation (CDecl [CDeclarationSpecifier a]
_ [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
_ a
n) = a
n
annotation (CStaticAssert CExpression a
_ CStringLiteral a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CDeclaration a -> CDeclaration a
amap a -> a
f (CDecl [CDeclarationSpecifier a]
a_1 [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
a_2 a
a_3) = [CDeclarationSpecifier a]
-> [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
-> a
-> CDeclaration a
forall a.
[CDeclarationSpecifier a]
-> [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
-> a
-> CDeclaration a
CDecl [CDeclarationSpecifier a]
a_1 [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
a_2 (a -> a
f a
a_3)
amap a -> a
f (CStaticAssert CExpression a
a_1 CStringLiteral a
a_2 a
a_3) = CExpression a -> CStringLiteral a -> a -> CDeclaration a
forall a. CExpression a -> CStringLiteral a -> a -> CDeclaration a
CStaticAssert CExpression a
a_1 CStringLiteral a
a_2 (a -> a
f a
a_3)
instance CNode t1 => CNode (CDeclarator t1) where
nodeInfo :: CDeclarator t1 -> NodeInfo
nodeInfo (CDeclr Maybe Ident
_ [CDerivedDeclarator t1]
_ Maybe (CStringLiteral t1)
_ [CAttribute t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CDeclarator t1) where
posOf :: CDeclarator t1 -> Position
posOf CDeclarator t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CDeclarator t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclarator t1
x)
instance Functor CDeclarator where
fmap :: forall a b. (a -> b) -> CDeclarator a -> CDeclarator b
fmap a -> b
_f (CDeclr Maybe Ident
a1 [CDerivedDeclarator a]
a2 Maybe (CStringLiteral a)
a3 [CAttribute a]
a4 a
a5)
= Maybe Ident
-> [CDerivedDeclarator b]
-> Maybe (CStringLiteral b)
-> [CAttribute b]
-> b
-> CDeclarator b
forall a.
Maybe Ident
-> [CDerivedDeclarator a]
-> Maybe (CStringLiteral a)
-> [CAttribute a]
-> a
-> CDeclarator a
CDeclr Maybe Ident
a1 ((CDerivedDeclarator a -> CDerivedDeclarator b)
-> [CDerivedDeclarator a] -> [CDerivedDeclarator b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CDerivedDeclarator a -> CDerivedDeclarator b
forall a b.
(a -> b) -> CDerivedDeclarator a -> CDerivedDeclarator b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CDerivedDeclarator a]
a2) ((CStringLiteral a -> CStringLiteral b)
-> Maybe (CStringLiteral a) -> Maybe (CStringLiteral b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CStringLiteral a -> CStringLiteral b
forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CStringLiteral a)
a3)
((CAttribute a -> CAttribute b) -> [CAttribute a] -> [CAttribute b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAttribute a -> CAttribute b
forall a b. (a -> b) -> CAttribute a -> CAttribute b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAttribute a]
a4)
(a -> b
_f a
a5)
instance Annotated CDeclarator where
annotation :: forall a. CDeclarator a -> a
annotation (CDeclr Maybe Ident
_ [CDerivedDeclarator a]
_ Maybe (CStringLiteral a)
_ [CAttribute a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CDeclarator a -> CDeclarator a
amap a -> a
f (CDeclr Maybe Ident
a_1 [CDerivedDeclarator a]
a_2 Maybe (CStringLiteral a)
a_3 [CAttribute a]
a_4 a
a_5)
= Maybe Ident
-> [CDerivedDeclarator a]
-> Maybe (CStringLiteral a)
-> [CAttribute a]
-> a
-> CDeclarator a
forall a.
Maybe Ident
-> [CDerivedDeclarator a]
-> Maybe (CStringLiteral a)
-> [CAttribute a]
-> a
-> CDeclarator a
CDeclr Maybe Ident
a_1 [CDerivedDeclarator a]
a_2 Maybe (CStringLiteral a)
a_3 [CAttribute a]
a_4 (a -> a
f a
a_5)
instance CNode t1 => CNode (CDerivedDeclarator t1) where
nodeInfo :: CDerivedDeclarator t1 -> NodeInfo
nodeInfo (CPtrDeclr [CTypeQualifier t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CArrDeclr [CTypeQualifier t1]
_ CArraySize t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CFunDeclr Either [Ident] ([CDeclaration t1], Bool)
_ [CAttribute t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CDerivedDeclarator t1) where
posOf :: CDerivedDeclarator t1 -> Position
posOf CDerivedDeclarator t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CDerivedDeclarator t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDerivedDeclarator t1
x)
instance Annotated CDerivedDeclarator where
annotation :: forall a. CDerivedDeclarator a -> a
annotation (CPtrDeclr [CTypeQualifier a]
_ a
n) = a
n
annotation (CArrDeclr [CTypeQualifier a]
_ CArraySize a
_ a
n) = a
n
annotation (CFunDeclr Either [Ident] ([CDeclaration a], Bool)
_ [CAttribute a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CDerivedDeclarator a -> CDerivedDeclarator a
amap a -> a
f (CPtrDeclr [CTypeQualifier a]
a_1 a
a_2) = [CTypeQualifier a] -> a -> CDerivedDeclarator a
forall a. [CTypeQualifier a] -> a -> CDerivedDeclarator a
CPtrDeclr [CTypeQualifier a]
a_1 (a -> a
f a
a_2)
amap a -> a
f (CArrDeclr [CTypeQualifier a]
a_1 CArraySize a
a_2 a
a_3) = [CTypeQualifier a] -> CArraySize a -> a -> CDerivedDeclarator a
forall a.
[CTypeQualifier a] -> CArraySize a -> a -> CDerivedDeclarator a
CArrDeclr [CTypeQualifier a]
a_1 CArraySize a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CFunDeclr Either [Ident] ([CDeclaration a], Bool)
a_1 [CAttribute a]
a_2 a
a_3) = Either [Ident] ([CDeclaration a], Bool)
-> [CAttribute a] -> a -> CDerivedDeclarator a
forall a.
Either [Ident] ([CDeclaration a], Bool)
-> [CAttribute a] -> a -> CDerivedDeclarator a
CFunDeclr Either [Ident] ([CDeclaration a], Bool)
a_1 [CAttribute a]
a_2 (a -> a
f a
a_3)
instance Functor CArraySize where
fmap :: forall a b. (a -> b) -> CArraySize a -> CArraySize b
fmap a -> b
_ (CNoArrSize Bool
a1) = Bool -> CArraySize b
forall a. Bool -> CArraySize a
CNoArrSize Bool
a1
fmap a -> b
_f (CArrSize Bool
a1 CExpression a
a2) = Bool -> CExpression b -> CArraySize b
forall a. Bool -> CExpression a -> CArraySize a
CArrSize Bool
a1 ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2)
instance CNode t1 => CNode (CStatement t1) where
nodeInfo :: CStatement t1 -> NodeInfo
nodeInfo (CLabel Ident
_ CStatement t1
_ [CAttribute t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCase CExpression t1
_ CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCases CExpression t1
_ CExpression t1
_ CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CDefault CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CExpr Maybe (CExpression t1)
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCompound [Ident]
_ [CCompoundBlockItem t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CIf CExpression t1
_ CStatement t1
_ Maybe (CStatement t1)
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CSwitch CExpression t1
_ CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CWhile CExpression t1
_ CStatement t1
_ Bool
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CFor Either (Maybe (CExpression t1)) (CDeclaration t1)
_ Maybe (CExpression t1)
_ Maybe (CExpression t1)
_ CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CGoto Ident
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CGotoPtr CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCont t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CBreak t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CReturn Maybe (CExpression t1)
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAsm CAssemblyStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CStatement t1) where
posOf :: CStatement t1 -> Position
posOf CStatement t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CStatement t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStatement t1
x)
instance Annotated CStatement where
annotation :: forall a. CStatement a -> a
annotation (CLabel Ident
_ CStatement a
_ [CAttribute a]
_ a
n) = a
n
annotation (CCase CExpression a
_ CStatement a
_ a
n) = a
n
annotation (CCases CExpression a
_ CExpression a
_ CStatement a
_ a
n) = a
n
annotation (CDefault CStatement a
_ a
n) = a
n
annotation (CExpr Maybe (CExpression a)
_ a
n) = a
n
annotation (CCompound [Ident]
_ [CCompoundBlockItem a]
_ a
n) = a
n
annotation (CIf CExpression a
_ CStatement a
_ Maybe (CStatement a)
_ a
n) = a
n
annotation (CSwitch CExpression a
_ CStatement a
_ a
n) = a
n
annotation (CWhile CExpression a
_ CStatement a
_ Bool
_ a
n) = a
n
annotation (CFor Either (Maybe (CExpression a)) (CDeclaration a)
_ Maybe (CExpression a)
_ Maybe (CExpression a)
_ CStatement a
_ a
n) = a
n
annotation (CGoto Ident
_ a
n) = a
n
annotation (CGotoPtr CExpression a
_ a
n) = a
n
annotation (CCont a
n) = a
n
annotation (CBreak a
n) = a
n
annotation (CReturn Maybe (CExpression a)
_ a
n) = a
n
annotation (CAsm CAssemblyStatement a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CStatement a -> CStatement a
amap a -> a
f (CLabel Ident
a_1 CStatement a
a_2 [CAttribute a]
a_3 a
a_4) = Ident -> CStatement a -> [CAttribute a] -> a -> CStatement a
forall a.
Ident -> CStatement a -> [CAttribute a] -> a -> CStatement a
CLabel Ident
a_1 CStatement a
a_2 [CAttribute a]
a_3 (a -> a
f a
a_4)
amap a -> a
f (CCase CExpression a
a_1 CStatement a
a_2 a
a_3) = CExpression a -> CStatement a -> a -> CStatement a
forall a. CExpression a -> CStatement a -> a -> CStatement a
CCase CExpression a
a_1 CStatement a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CCases CExpression a
a_1 CExpression a
a_2 CStatement a
a_3 a
a_4) = CExpression a -> CExpression a -> CStatement a -> a -> CStatement a
forall a.
CExpression a -> CExpression a -> CStatement a -> a -> CStatement a
CCases CExpression a
a_1 CExpression a
a_2 CStatement a
a_3 (a -> a
f a
a_4)
amap a -> a
f (CDefault CStatement a
a_1 a
a_2) = CStatement a -> a -> CStatement a
forall a. CStatement a -> a -> CStatement a
CDefault CStatement a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CExpr Maybe (CExpression a)
a_1 a
a_2) = Maybe (CExpression a) -> a -> CStatement a
forall a. Maybe (CExpression a) -> a -> CStatement a
CExpr Maybe (CExpression a)
a_1 (a -> a
f a
a_2)
amap a -> a
f (CCompound [Ident]
a_1 [CCompoundBlockItem a]
a_2 a
a_3) = [Ident] -> [CCompoundBlockItem a] -> a -> CStatement a
forall a. [Ident] -> [CCompoundBlockItem a] -> a -> CStatement a
CCompound [Ident]
a_1 [CCompoundBlockItem a]
a_2 (a -> a
f a
a_3)
amap a -> a
f (CIf CExpression a
a_1 CStatement a
a_2 Maybe (CStatement a)
a_3 a
a_4) = CExpression a
-> CStatement a -> Maybe (CStatement a) -> a -> CStatement a
forall a.
CExpression a
-> CStatement a -> Maybe (CStatement a) -> a -> CStatement a
CIf CExpression a
a_1 CStatement a
a_2 Maybe (CStatement a)
a_3 (a -> a
f a
a_4)
amap a -> a
f (CSwitch CExpression a
a_1 CStatement a
a_2 a
a_3) = CExpression a -> CStatement a -> a -> CStatement a
forall a. CExpression a -> CStatement a -> a -> CStatement a
CSwitch CExpression a
a_1 CStatement a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CWhile CExpression a
a_1 CStatement a
a_2 Bool
a_3 a
a_4) = CExpression a -> CStatement a -> Bool -> a -> CStatement a
forall a.
CExpression a -> CStatement a -> Bool -> a -> CStatement a
CWhile CExpression a
a_1 CStatement a
a_2 Bool
a_3 (a -> a
f a
a_4)
amap a -> a
f (CFor Either (Maybe (CExpression a)) (CDeclaration a)
a_1 Maybe (CExpression a)
a_2 Maybe (CExpression a)
a_3 CStatement a
a_4 a
a_5) = Either (Maybe (CExpression a)) (CDeclaration a)
-> Maybe (CExpression a)
-> Maybe (CExpression a)
-> CStatement a
-> a
-> CStatement a
forall a.
Either (Maybe (CExpression a)) (CDeclaration a)
-> Maybe (CExpression a)
-> Maybe (CExpression a)
-> CStatement a
-> a
-> CStatement a
CFor Either (Maybe (CExpression a)) (CDeclaration a)
a_1 Maybe (CExpression a)
a_2 Maybe (CExpression a)
a_3 CStatement a
a_4 (a -> a
f a
a_5)
amap a -> a
f (CGoto Ident
a_1 a
a_2) = Ident -> a -> CStatement a
forall a. Ident -> a -> CStatement a
CGoto Ident
a_1 (a -> a
f a
a_2)
amap a -> a
f (CGotoPtr CExpression a
a_1 a
a_2) = CExpression a -> a -> CStatement a
forall a. CExpression a -> a -> CStatement a
CGotoPtr CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CCont a
a_1) = a -> CStatement a
forall a. a -> CStatement a
CCont (a -> a
f a
a_1)
amap a -> a
f (CBreak a
a_1) = a -> CStatement a
forall a. a -> CStatement a
CBreak (a -> a
f a
a_1)
amap a -> a
f (CReturn Maybe (CExpression a)
a_1 a
a_2) = Maybe (CExpression a) -> a -> CStatement a
forall a. Maybe (CExpression a) -> a -> CStatement a
CReturn Maybe (CExpression a)
a_1 (a -> a
f a
a_2)
amap a -> a
f (CAsm CAssemblyStatement a
a_1 a
a_2) = CAssemblyStatement a -> a -> CStatement a
forall a. CAssemblyStatement a -> a -> CStatement a
CAsm CAssemblyStatement a
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CAssemblyStatement t1) where
nodeInfo :: CAssemblyStatement t1 -> NodeInfo
nodeInfo (CAsmStmt Maybe (CTypeQualifier t1)
_ CStringLiteral t1
_ [CAssemblyOperand t1]
_ [CAssemblyOperand t1]
_ [CStringLiteral t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CAssemblyStatement t1) where
posOf :: CAssemblyStatement t1 -> Position
posOf CAssemblyStatement t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CAssemblyStatement t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAssemblyStatement t1
x)
instance Functor CAssemblyStatement where
fmap :: forall a b.
(a -> b) -> CAssemblyStatement a -> CAssemblyStatement b
fmap a -> b
_f (CAsmStmt Maybe (CTypeQualifier a)
a1 CStringLiteral a
a2 [CAssemblyOperand a]
a3 [CAssemblyOperand a]
a4 [CStringLiteral a]
a5 a
a6)
= Maybe (CTypeQualifier b)
-> CStringLiteral b
-> [CAssemblyOperand b]
-> [CAssemblyOperand b]
-> [CStringLiteral b]
-> b
-> CAssemblyStatement b
forall a.
Maybe (CTypeQualifier a)
-> CStringLiteral a
-> [CAssemblyOperand a]
-> [CAssemblyOperand a]
-> [CStringLiteral a]
-> a
-> CAssemblyStatement a
CAsmStmt ((CTypeQualifier a -> CTypeQualifier b)
-> Maybe (CTypeQualifier a) -> Maybe (CTypeQualifier b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall a b. (a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) Maybe (CTypeQualifier a)
a1) ((a -> b) -> CStringLiteral a -> CStringLiteral b
forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStringLiteral a
a2) ((CAssemblyOperand a -> CAssemblyOperand b)
-> [CAssemblyOperand a] -> [CAssemblyOperand b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAssemblyOperand a -> CAssemblyOperand b
forall a b. (a -> b) -> CAssemblyOperand a -> CAssemblyOperand b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAssemblyOperand a]
a3)
((CAssemblyOperand a -> CAssemblyOperand b)
-> [CAssemblyOperand a] -> [CAssemblyOperand b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAssemblyOperand a -> CAssemblyOperand b
forall a b. (a -> b) -> CAssemblyOperand a -> CAssemblyOperand b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAssemblyOperand a]
a4)
((CStringLiteral a -> CStringLiteral b)
-> [CStringLiteral a] -> [CStringLiteral b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CStringLiteral a -> CStringLiteral b
forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CStringLiteral a]
a5)
(a -> b
_f a
a6)
instance Annotated CAssemblyStatement where
annotation :: forall a. CAssemblyStatement a -> a
annotation (CAsmStmt Maybe (CTypeQualifier a)
_ CStringLiteral a
_ [CAssemblyOperand a]
_ [CAssemblyOperand a]
_ [CStringLiteral a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CAssemblyStatement a -> CAssemblyStatement a
amap a -> a
f (CAsmStmt Maybe (CTypeQualifier a)
a_1 CStringLiteral a
a_2 [CAssemblyOperand a]
a_3 [CAssemblyOperand a]
a_4 [CStringLiteral a]
a_5 a
a_6)
= Maybe (CTypeQualifier a)
-> CStringLiteral a
-> [CAssemblyOperand a]
-> [CAssemblyOperand a]
-> [CStringLiteral a]
-> a
-> CAssemblyStatement a
forall a.
Maybe (CTypeQualifier a)
-> CStringLiteral a
-> [CAssemblyOperand a]
-> [CAssemblyOperand a]
-> [CStringLiteral a]
-> a
-> CAssemblyStatement a
CAsmStmt Maybe (CTypeQualifier a)
a_1 CStringLiteral a
a_2 [CAssemblyOperand a]
a_3 [CAssemblyOperand a]
a_4 [CStringLiteral a]
a_5 (a -> a
f a
a_6)
instance CNode t1 => CNode (CAssemblyOperand t1) where
nodeInfo :: CAssemblyOperand t1 -> NodeInfo
nodeInfo (CAsmOperand Maybe Ident
_ CStringLiteral t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CAssemblyOperand t1) where
posOf :: CAssemblyOperand t1 -> Position
posOf CAssemblyOperand t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CAssemblyOperand t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAssemblyOperand t1
x)
instance Functor CAssemblyOperand where
fmap :: forall a b. (a -> b) -> CAssemblyOperand a -> CAssemblyOperand b
fmap a -> b
_f (CAsmOperand Maybe Ident
a1 CStringLiteral a
a2 CExpression a
a3 a
a4)
= Maybe Ident
-> CStringLiteral b -> CExpression b -> b -> CAssemblyOperand b
forall a.
Maybe Ident
-> CStringLiteral a -> CExpression a -> a -> CAssemblyOperand a
CAsmOperand Maybe Ident
a1 ((a -> b) -> CStringLiteral a -> CStringLiteral b
forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStringLiteral a
a2) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
instance Annotated CAssemblyOperand where
annotation :: forall a. CAssemblyOperand a -> a
annotation (CAsmOperand Maybe Ident
_ CStringLiteral a
_ CExpression a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CAssemblyOperand a -> CAssemblyOperand a
amap a -> a
f (CAsmOperand Maybe Ident
a_1 CStringLiteral a
a_2 CExpression a
a_3 a
a_4)
= Maybe Ident
-> CStringLiteral a -> CExpression a -> a -> CAssemblyOperand a
forall a.
Maybe Ident
-> CStringLiteral a -> CExpression a -> a -> CAssemblyOperand a
CAsmOperand Maybe Ident
a_1 CStringLiteral a
a_2 CExpression a
a_3 (a -> a
f a
a_4)
instance CNode t1 => CNode (CCompoundBlockItem t1) where
nodeInfo :: CCompoundBlockItem t1 -> NodeInfo
nodeInfo (CBlockStmt CStatement t1
d) = CStatement t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStatement t1
d
nodeInfo (CBlockDecl CDeclaration t1
d) = CDeclaration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclaration t1
d
nodeInfo (CNestedFunDef CFunctionDef t1
d) = CFunctionDef t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionDef t1
d
instance CNode t1 => Pos (CCompoundBlockItem t1) where
posOf :: CCompoundBlockItem t1 -> Position
posOf CCompoundBlockItem t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CCompoundBlockItem t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CCompoundBlockItem t1
x)
instance Functor CCompoundBlockItem where
fmap :: forall a b.
(a -> b) -> CCompoundBlockItem a -> CCompoundBlockItem b
fmap a -> b
_f (CBlockStmt CStatement a
a1) = CStatement b -> CCompoundBlockItem b
forall a. CStatement a -> CCompoundBlockItem a
CBlockStmt ((a -> b) -> CStatement a -> CStatement b
forall a b. (a -> b) -> CStatement a -> CStatement b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a1)
fmap a -> b
_f (CBlockDecl CDeclaration a
a1) = CDeclaration b -> CCompoundBlockItem b
forall a. CDeclaration a -> CCompoundBlockItem a
CBlockDecl ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1)
fmap a -> b
_f (CNestedFunDef CFunctionDef a
a1) = CFunctionDef b -> CCompoundBlockItem b
forall a. CFunctionDef a -> CCompoundBlockItem a
CNestedFunDef ((a -> b) -> CFunctionDef a -> CFunctionDef b
forall a b. (a -> b) -> CFunctionDef a -> CFunctionDef b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CFunctionDef a
a1)
instance Annotated CCompoundBlockItem where
annotation :: forall a. CCompoundBlockItem a -> a
annotation (CBlockStmt CStatement a
n) = CStatement a -> a
forall a. CStatement a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CStatement a
n
annotation (CBlockDecl CDeclaration a
n) = CDeclaration a -> a
forall a. CDeclaration a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CDeclaration a
n
annotation (CNestedFunDef CFunctionDef a
n) = CFunctionDef a -> a
forall a. CFunctionDef a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CFunctionDef a
n
amap :: forall a. (a -> a) -> CCompoundBlockItem a -> CCompoundBlockItem a
amap a -> a
f (CBlockStmt CStatement a
n) = CStatement a -> CCompoundBlockItem a
forall a. CStatement a -> CCompoundBlockItem a
CBlockStmt ((a -> a) -> CStatement a -> CStatement a
forall a. (a -> a) -> CStatement a -> CStatement a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CStatement a
n)
amap a -> a
f (CBlockDecl CDeclaration a
n) = CDeclaration a -> CCompoundBlockItem a
forall a. CDeclaration a -> CCompoundBlockItem a
CBlockDecl ((a -> a) -> CDeclaration a -> CDeclaration a
forall a. (a -> a) -> CDeclaration a -> CDeclaration a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CDeclaration a
n)
amap a -> a
f (CNestedFunDef CFunctionDef a
n) = CFunctionDef a -> CCompoundBlockItem a
forall a. CFunctionDef a -> CCompoundBlockItem a
CNestedFunDef ((a -> a) -> CFunctionDef a -> CFunctionDef a
forall a. (a -> a) -> CFunctionDef a -> CFunctionDef a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CFunctionDef a
n)
instance CNode t1 => CNode (CDeclarationSpecifier t1) where
nodeInfo :: CDeclarationSpecifier t1 -> NodeInfo
nodeInfo (CStorageSpec CStorageSpecifier t1
d) = CStorageSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStorageSpecifier t1
d
nodeInfo (CTypeSpec CTypeSpecifier t1
d) = CTypeSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTypeSpecifier t1
d
nodeInfo (CTypeQual CTypeQualifier t1
d) = CTypeQualifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTypeQualifier t1
d
nodeInfo (CFunSpec CFunctionSpecifier t1
d) = CFunctionSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionSpecifier t1
d
nodeInfo (CAlignSpec CAlignmentSpecifier t1
d) = CAlignmentSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAlignmentSpecifier t1
d
instance CNode t1 => Pos (CDeclarationSpecifier t1) where
posOf :: CDeclarationSpecifier t1 -> Position
posOf CDeclarationSpecifier t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CDeclarationSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclarationSpecifier t1
x)
instance Functor CDeclarationSpecifier where
fmap :: forall a b.
(a -> b) -> CDeclarationSpecifier a -> CDeclarationSpecifier b
fmap a -> b
_f (CStorageSpec CStorageSpecifier a
a1) = CStorageSpecifier b -> CDeclarationSpecifier b
forall a. CStorageSpecifier a -> CDeclarationSpecifier a
CStorageSpec ((a -> b) -> CStorageSpecifier a -> CStorageSpecifier b
forall a b. (a -> b) -> CStorageSpecifier a -> CStorageSpecifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStorageSpecifier a
a1)
fmap a -> b
_f (CTypeSpec CTypeSpecifier a
a1) = CTypeSpecifier b -> CDeclarationSpecifier b
forall a. CTypeSpecifier a -> CDeclarationSpecifier a
CTypeSpec ((a -> b) -> CTypeSpecifier a -> CTypeSpecifier b
forall a b. (a -> b) -> CTypeSpecifier a -> CTypeSpecifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CTypeSpecifier a
a1)
fmap a -> b
_f (CTypeQual CTypeQualifier a
a1) = CTypeQualifier b -> CDeclarationSpecifier b
forall a. CTypeQualifier a -> CDeclarationSpecifier a
CTypeQual ((a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall a b. (a -> b) -> CTypeQualifier a -> CTypeQualifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CTypeQualifier a
a1)
fmap a -> b
_f (CFunSpec CFunctionSpecifier a
a1) = CFunctionSpecifier b -> CDeclarationSpecifier b
forall a. CFunctionSpecifier a -> CDeclarationSpecifier a
CFunSpec ((a -> b) -> CFunctionSpecifier a -> CFunctionSpecifier b
forall a b.
(a -> b) -> CFunctionSpecifier a -> CFunctionSpecifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CFunctionSpecifier a
a1)
fmap a -> b
_f (CAlignSpec CAlignmentSpecifier a
a1) = CAlignmentSpecifier b -> CDeclarationSpecifier b
forall a. CAlignmentSpecifier a -> CDeclarationSpecifier a
CAlignSpec ((a -> b) -> CAlignmentSpecifier a -> CAlignmentSpecifier b
forall a b.
(a -> b) -> CAlignmentSpecifier a -> CAlignmentSpecifier b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CAlignmentSpecifier a
a1)
instance Annotated CDeclarationSpecifier where
annotation :: forall a. CDeclarationSpecifier a -> a
annotation (CStorageSpec CStorageSpecifier a
n) = CStorageSpecifier a -> a
forall a. CStorageSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CStorageSpecifier a
n
annotation (CTypeSpec CTypeSpecifier a
n) = CTypeSpecifier a -> a
forall a. CTypeSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CTypeSpecifier a
n
annotation (CTypeQual CTypeQualifier a
n) = CTypeQualifier a -> a
forall a. CTypeQualifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CTypeQualifier a
n
annotation (CFunSpec CFunctionSpecifier a
n) = CFunctionSpecifier a -> a
forall a. CFunctionSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CFunctionSpecifier a
n
annotation (CAlignSpec CAlignmentSpecifier a
n) = CAlignmentSpecifier a -> a
forall a. CAlignmentSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CAlignmentSpecifier a
n
amap :: forall a.
(a -> a) -> CDeclarationSpecifier a -> CDeclarationSpecifier a
amap a -> a
f (CStorageSpec CStorageSpecifier a
n) = CStorageSpecifier a -> CDeclarationSpecifier a
forall a. CStorageSpecifier a -> CDeclarationSpecifier a
CStorageSpec ((a -> a) -> CStorageSpecifier a -> CStorageSpecifier a
forall a. (a -> a) -> CStorageSpecifier a -> CStorageSpecifier a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CStorageSpecifier a
n)
amap a -> a
f (CTypeSpec CTypeSpecifier a
n) = CTypeSpecifier a -> CDeclarationSpecifier a
forall a. CTypeSpecifier a -> CDeclarationSpecifier a
CTypeSpec ((a -> a) -> CTypeSpecifier a -> CTypeSpecifier a
forall a. (a -> a) -> CTypeSpecifier a -> CTypeSpecifier a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CTypeSpecifier a
n)
amap a -> a
f (CTypeQual CTypeQualifier a
n) = CTypeQualifier a -> CDeclarationSpecifier a
forall a. CTypeQualifier a -> CDeclarationSpecifier a
CTypeQual ((a -> a) -> CTypeQualifier a -> CTypeQualifier a
forall a. (a -> a) -> CTypeQualifier a -> CTypeQualifier a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CTypeQualifier a
n)
amap a -> a
f (CFunSpec CFunctionSpecifier a
n) = CFunctionSpecifier a -> CDeclarationSpecifier a
forall a. CFunctionSpecifier a -> CDeclarationSpecifier a
CFunSpec ((a -> a) -> CFunctionSpecifier a -> CFunctionSpecifier a
forall a. (a -> a) -> CFunctionSpecifier a -> CFunctionSpecifier a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CFunctionSpecifier a
n)
amap a -> a
f (CAlignSpec CAlignmentSpecifier a
n) = CAlignmentSpecifier a -> CDeclarationSpecifier a
forall a. CAlignmentSpecifier a -> CDeclarationSpecifier a
CAlignSpec ((a -> a) -> CAlignmentSpecifier a -> CAlignmentSpecifier a
forall a.
(a -> a) -> CAlignmentSpecifier a -> CAlignmentSpecifier a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CAlignmentSpecifier a
n)
instance CNode t1 => CNode (CStorageSpecifier t1) where
nodeInfo :: CStorageSpecifier t1 -> NodeInfo
nodeInfo (CAuto t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CRegister t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CStatic t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CExtern t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CTypedef t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CThread t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClKernel t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClGlobal t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClLocal t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
instance CNode t1 => Pos (CStorageSpecifier t1) where
posOf :: CStorageSpecifier t1 -> Position
posOf CStorageSpecifier t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CStorageSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStorageSpecifier t1
x)
instance Functor CStorageSpecifier where
fmap :: forall a b. (a -> b) -> CStorageSpecifier a -> CStorageSpecifier b
fmap a -> b
_f (CAuto a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CAuto (a -> b
_f a
a1)
fmap a -> b
_f (CRegister a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CRegister (a -> b
_f a
a1)
fmap a -> b
_f (CStatic a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CStatic (a -> b
_f a
a1)
fmap a -> b
_f (CExtern a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CExtern (a -> b
_f a
a1)
fmap a -> b
_f (CTypedef a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CTypedef (a -> b
_f a
a1)
fmap a -> b
_f (CThread a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CThread (a -> b
_f a
a1)
fmap a -> b
_f (CClKernel a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CClKernel (a -> b
_f a
a1)
fmap a -> b
_f (CClGlobal a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CClGlobal (a -> b
_f a
a1)
fmap a -> b
_f (CClLocal a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CClLocal (a -> b
_f a
a1)
instance Annotated CStorageSpecifier where
annotation :: forall a. CStorageSpecifier a -> a
annotation (CAuto a
n) = a
n
annotation (CRegister a
n) = a
n
annotation (CStatic a
n) = a
n
annotation (CExtern a
n) = a
n
annotation (CTypedef a
n) = a
n
annotation (CThread a
n) = a
n
annotation (CClKernel a
n) = a
n
annotation (CClGlobal a
n) = a
n
annotation (CClLocal a
n) = a
n
amap :: forall a. (a -> a) -> CStorageSpecifier a -> CStorageSpecifier a
amap a -> a
f (CAuto a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CAuto (a -> a
f a
a_1)
amap a -> a
f (CRegister a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CRegister (a -> a
f a
a_1)
amap a -> a
f (CStatic a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CStatic (a -> a
f a
a_1)
amap a -> a
f (CExtern a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CExtern (a -> a
f a
a_1)
amap a -> a
f (CTypedef a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CTypedef (a -> a
f a
a_1)
amap a -> a
f (CThread a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CThread (a -> a
f a
a_1)
amap a -> a
f (CClKernel a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CClKernel (a -> a
f a
a_1)
amap a -> a
f (CClGlobal a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CClGlobal (a -> a
f a
a_1)
amap a -> a
f (CClLocal a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CClLocal (a -> a
f a
a_1)
instance CNode t1 => CNode (CTypeSpecifier t1) where
nodeInfo :: CTypeSpecifier t1 -> NodeInfo
nodeInfo (CVoidType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CCharType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CShortType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CIntType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CLongType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CFloatType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CFloatNType Int
_ Bool
_ t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CDoubleType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CSignedType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CUnsigType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CBoolType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CComplexType t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CInt128Type t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CUInt128Type t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CSUType CStructureUnion t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CEnumType CEnumeration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CTypeDef Ident
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CTypeOfExpr CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CTypeOfType CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAtomicType CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CTypeSpecifier t1) where
posOf :: CTypeSpecifier t1 -> Position
posOf CTypeSpecifier t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CTypeSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTypeSpecifier t1
x)
instance Functor CTypeSpecifier where
fmap :: forall a b. (a -> b) -> CTypeSpecifier a -> CTypeSpecifier b
fmap a -> b
_f (CVoidType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CVoidType (a -> b
_f a
a1)
fmap a -> b
_f (CCharType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CCharType (a -> b
_f a
a1)
fmap a -> b
_f (CShortType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CShortType (a -> b
_f a
a1)
fmap a -> b
_f (CIntType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CIntType (a -> b
_f a
a1)
fmap a -> b
_f (CLongType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CLongType (a -> b
_f a
a1)
fmap a -> b
_f (CFloatType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CFloatType (a -> b
_f a
a1)
fmap a -> b
_f (CFloatNType Int
n Bool
x a
a1) = Int -> Bool -> b -> CTypeSpecifier b
forall a. Int -> Bool -> a -> CTypeSpecifier a
CFloatNType Int
n Bool
x (a -> b
_f a
a1)
fmap a -> b
_f (CDoubleType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CDoubleType (a -> b
_f a
a1)
fmap a -> b
_f (CSignedType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CSignedType (a -> b
_f a
a1)
fmap a -> b
_f (CUnsigType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CUnsigType (a -> b
_f a
a1)
fmap a -> b
_f (CBoolType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CBoolType (a -> b
_f a
a1)
fmap a -> b
_f (CComplexType a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CComplexType (a -> b
_f a
a1)
fmap a -> b
_f (CInt128Type a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CInt128Type (a -> b
_f a
a1)
fmap a -> b
_f (CUInt128Type a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CUInt128Type (a -> b
_f a
a1)
fmap a -> b
_f (CSUType CStructureUnion a
a1 a
a2) = CStructureUnion b -> b -> CTypeSpecifier b
forall a. CStructureUnion a -> a -> CTypeSpecifier a
CSUType ((a -> b) -> CStructureUnion a -> CStructureUnion b
forall a b. (a -> b) -> CStructureUnion a -> CStructureUnion b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStructureUnion a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CEnumType CEnumeration a
a1 a
a2) = CEnumeration b -> b -> CTypeSpecifier b
forall a. CEnumeration a -> a -> CTypeSpecifier a
CEnumType ((a -> b) -> CEnumeration a -> CEnumeration b
forall a b. (a -> b) -> CEnumeration a -> CEnumeration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CEnumeration a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CTypeDef Ident
a1 a
a2) = Ident -> b -> CTypeSpecifier b
forall a. Ident -> a -> CTypeSpecifier a
CTypeDef Ident
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CTypeOfExpr CExpression a
a1 a
a2) = CExpression b -> b -> CTypeSpecifier b
forall a. CExpression a -> a -> CTypeSpecifier a
CTypeOfExpr ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CTypeOfType CDeclaration a
a1 a
a2) = CDeclaration b -> b -> CTypeSpecifier b
forall a. CDeclaration a -> a -> CTypeSpecifier a
CTypeOfType ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CAtomicType CDeclaration a
a1 a
a2) = CDeclaration b -> b -> CTypeSpecifier b
forall a. CDeclaration a -> a -> CTypeSpecifier a
CAtomicType ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) (a -> b
_f a
a2)
instance Annotated CTypeSpecifier where
annotation :: forall a. CTypeSpecifier a -> a
annotation (CVoidType a
n) = a
n
annotation (CCharType a
n) = a
n
annotation (CShortType a
n) = a
n
annotation (CIntType a
n) = a
n
annotation (CLongType a
n) = a
n
annotation (CFloatType a
n) = a
n
annotation (CFloatNType Int
_ Bool
_ a
n) = a
n
annotation (CDoubleType a
n) = a
n
annotation (CSignedType a
n) = a
n
annotation (CUnsigType a
n) = a
n
annotation (CBoolType a
n) = a
n
annotation (CComplexType a
n) = a
n
annotation (CInt128Type a
n) = a
n
annotation (CUInt128Type a
n) = a
n
annotation (CSUType CStructureUnion a
_ a
n) = a
n
annotation (CEnumType CEnumeration a
_ a
n) = a
n
annotation (CTypeDef Ident
_ a
n) = a
n
annotation (CTypeOfExpr CExpression a
_ a
n) = a
n
annotation (CTypeOfType CDeclaration a
_ a
n) = a
n
annotation (CAtomicType CDeclaration a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CTypeSpecifier a -> CTypeSpecifier a
amap a -> a
f (CVoidType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CVoidType (a -> a
f a
a_1)
amap a -> a
f (CCharType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CCharType (a -> a
f a
a_1)
amap a -> a
f (CShortType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CShortType (a -> a
f a
a_1)
amap a -> a
f (CIntType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CIntType (a -> a
f a
a_1)
amap a -> a
f (CLongType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CLongType (a -> a
f a
a_1)
amap a -> a
f (CFloatType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CFloatType (a -> a
f a
a_1)
amap a -> a
f (CFloatNType Int
n Bool
x a
a_1) = Int -> Bool -> a -> CTypeSpecifier a
forall a. Int -> Bool -> a -> CTypeSpecifier a
CFloatNType Int
n Bool
x (a -> a
f a
a_1)
amap a -> a
f (CDoubleType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CDoubleType (a -> a
f a
a_1)
amap a -> a
f (CSignedType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CSignedType (a -> a
f a
a_1)
amap a -> a
f (CUnsigType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CUnsigType (a -> a
f a
a_1)
amap a -> a
f (CBoolType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CBoolType (a -> a
f a
a_1)
amap a -> a
f (CComplexType a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CComplexType (a -> a
f a
a_1)
amap a -> a
f (CInt128Type a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CInt128Type (a -> a
f a
a_1)
amap a -> a
f (CUInt128Type a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CUInt128Type (a -> a
f a
a_1)
amap a -> a
f (CSUType CStructureUnion a
a_1 a
a_2) = CStructureUnion a -> a -> CTypeSpecifier a
forall a. CStructureUnion a -> a -> CTypeSpecifier a
CSUType CStructureUnion a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CEnumType CEnumeration a
a_1 a
a_2) = CEnumeration a -> a -> CTypeSpecifier a
forall a. CEnumeration a -> a -> CTypeSpecifier a
CEnumType CEnumeration a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CTypeDef Ident
a_1 a
a_2) = Ident -> a -> CTypeSpecifier a
forall a. Ident -> a -> CTypeSpecifier a
CTypeDef Ident
a_1 (a -> a
f a
a_2)
amap a -> a
f (CTypeOfExpr CExpression a
a_1 a
a_2) = CExpression a -> a -> CTypeSpecifier a
forall a. CExpression a -> a -> CTypeSpecifier a
CTypeOfExpr CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CTypeOfType CDeclaration a
a_1 a
a_2) = CDeclaration a -> a -> CTypeSpecifier a
forall a. CDeclaration a -> a -> CTypeSpecifier a
CTypeOfType CDeclaration a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CAtomicType CDeclaration a
a_1 a
a_2) = CDeclaration a -> a -> CTypeSpecifier a
forall a. CDeclaration a -> a -> CTypeSpecifier a
CAtomicType CDeclaration a
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CTypeQualifier t1) where
nodeInfo :: CTypeQualifier t1 -> NodeInfo
nodeInfo (CConstQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CVolatQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CRestrQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CAtomicQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CAttrQual CAttribute t1
d) = CAttribute t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAttribute t1
d
nodeInfo (CNullableQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CNonnullQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClRdOnlyQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClWrOnlyQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
instance CNode t1 => Pos (CTypeQualifier t1) where
posOf :: CTypeQualifier t1 -> Position
posOf CTypeQualifier t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CTypeQualifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTypeQualifier t1
x)
instance Functor CTypeQualifier where
fmap :: forall a b. (a -> b) -> CTypeQualifier a -> CTypeQualifier b
fmap a -> b
_f (CConstQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CConstQual (a -> b
_f a
a1)
fmap a -> b
_f (CVolatQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CVolatQual (a -> b
_f a
a1)
fmap a -> b
_f (CRestrQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CRestrQual (a -> b
_f a
a1)
fmap a -> b
_f (CAtomicQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CAtomicQual (a -> b
_f a
a1)
fmap a -> b
_f (CAttrQual CAttribute a
a1) = CAttribute b -> CTypeQualifier b
forall a. CAttribute a -> CTypeQualifier a
CAttrQual ((a -> b) -> CAttribute a -> CAttribute b
forall a b. (a -> b) -> CAttribute a -> CAttribute b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CAttribute a
a1)
fmap a -> b
_f (CNullableQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CNullableQual (a -> b
_f a
a1)
fmap a -> b
_f (CNonnullQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CNonnullQual (a -> b
_f a
a1)
fmap a -> b
_f (CClRdOnlyQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CClRdOnlyQual (a -> b
_f a
a1)
fmap a -> b
_f (CClWrOnlyQual a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CClWrOnlyQual (a -> b
_f a
a1)
instance Annotated CTypeQualifier where
annotation :: forall a. CTypeQualifier a -> a
annotation (CConstQual a
n) = a
n
annotation (CVolatQual a
n) = a
n
annotation (CRestrQual a
n) = a
n
annotation (CAtomicQual a
n) = a
n
annotation (CAttrQual CAttribute a
n) = CAttribute a -> a
forall a. CAttribute a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CAttribute a
n
annotation (CNullableQual a
n) = a
n
annotation (CNonnullQual a
n) = a
n
annotation (CClRdOnlyQual a
n) = a
n
annotation (CClWrOnlyQual a
n) = a
n
amap :: forall a. (a -> a) -> CTypeQualifier a -> CTypeQualifier a
amap a -> a
f (CConstQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CConstQual (a -> a
f a
a_1)
amap a -> a
f (CVolatQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CVolatQual (a -> a
f a
a_1)
amap a -> a
f (CRestrQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CRestrQual (a -> a
f a
a_1)
amap a -> a
f (CAtomicQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CAtomicQual (a -> a
f a
a_1)
amap a -> a
f (CAttrQual CAttribute a
n) = CAttribute a -> CTypeQualifier a
forall a. CAttribute a -> CTypeQualifier a
CAttrQual ((a -> a) -> CAttribute a -> CAttribute a
forall a. (a -> a) -> CAttribute a -> CAttribute a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CAttribute a
n)
amap a -> a
f (CNullableQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CNullableQual (a -> a
f a
a_1)
amap a -> a
f (CNonnullQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CNonnullQual (a -> a
f a
a_1)
amap a -> a
f (CClRdOnlyQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CClRdOnlyQual (a -> a
f a
a_1)
amap a -> a
f (CClWrOnlyQual a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CClWrOnlyQual (a -> a
f a
a_1)
instance CNode t1 => CNode (CFunctionSpecifier t1) where
nodeInfo :: CFunctionSpecifier t1 -> NodeInfo
nodeInfo (CInlineQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CNoreturnQual t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
instance CNode t1 => Pos (CFunctionSpecifier t1) where
posOf :: CFunctionSpecifier t1 -> Position
posOf CFunctionSpecifier t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CFunctionSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionSpecifier t1
x)
instance Functor CFunctionSpecifier where
fmap :: forall a b.
(a -> b) -> CFunctionSpecifier a -> CFunctionSpecifier b
fmap a -> b
_f (CInlineQual a
a1) = b -> CFunctionSpecifier b
forall a. a -> CFunctionSpecifier a
CInlineQual (a -> b
_f a
a1)
fmap a -> b
_f (CNoreturnQual a
a1) = b -> CFunctionSpecifier b
forall a. a -> CFunctionSpecifier a
CNoreturnQual (a -> b
_f a
a1)
instance Annotated CFunctionSpecifier where
annotation :: forall a. CFunctionSpecifier a -> a
annotation (CInlineQual a
n) = a
n
annotation (CNoreturnQual a
n) = a
n
amap :: forall a. (a -> a) -> CFunctionSpecifier a -> CFunctionSpecifier a
amap a -> a
f (CInlineQual a
a_1) = a -> CFunctionSpecifier a
forall a. a -> CFunctionSpecifier a
CInlineQual (a -> a
f a
a_1)
amap a -> a
f (CNoreturnQual a
a_1) = a -> CFunctionSpecifier a
forall a. a -> CFunctionSpecifier a
CNoreturnQual (a -> a
f a
a_1)
instance CNode t1 => CNode (CAlignmentSpecifier t1) where
nodeInfo :: CAlignmentSpecifier t1 -> NodeInfo
nodeInfo (CAlignAsType CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAlignAsExpr CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CAlignmentSpecifier t1) where
posOf :: CAlignmentSpecifier t1 -> Position
posOf CAlignmentSpecifier t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CAlignmentSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAlignmentSpecifier t1
x)
instance Functor CAlignmentSpecifier where
fmap :: forall a b.
(a -> b) -> CAlignmentSpecifier a -> CAlignmentSpecifier b
fmap a -> b
_f (CAlignAsType CDeclaration a
a1 a
a2) = CDeclaration b -> b -> CAlignmentSpecifier b
forall a. CDeclaration a -> a -> CAlignmentSpecifier a
CAlignAsType ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CAlignAsExpr CExpression a
a1 a
a2) = CExpression b -> b -> CAlignmentSpecifier b
forall a. CExpression a -> a -> CAlignmentSpecifier a
CAlignAsExpr ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
instance Annotated CAlignmentSpecifier where
annotation :: forall a. CAlignmentSpecifier a -> a
annotation (CAlignAsType CDeclaration a
_ a
n) = a
n
annotation (CAlignAsExpr CExpression a
_ a
n) = a
n
amap :: forall a.
(a -> a) -> CAlignmentSpecifier a -> CAlignmentSpecifier a
amap a -> a
f (CAlignAsType CDeclaration a
a_1 a
a_2) = CDeclaration a -> a -> CAlignmentSpecifier a
forall a. CDeclaration a -> a -> CAlignmentSpecifier a
CAlignAsType CDeclaration a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CAlignAsExpr CExpression a
a_1 a
a_2) = CExpression a -> a -> CAlignmentSpecifier a
forall a. CExpression a -> a -> CAlignmentSpecifier a
CAlignAsExpr CExpression a
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CStructureUnion t1) where
nodeInfo :: CStructureUnion t1 -> NodeInfo
nodeInfo (CStruct CStructTag
_ Maybe Ident
_ Maybe [CDeclaration t1]
_ [CAttribute t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CStructureUnion t1) where
posOf :: CStructureUnion t1 -> Position
posOf CStructureUnion t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CStructureUnion t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStructureUnion t1
x)
instance Functor CStructureUnion where
fmap :: forall a b. (a -> b) -> CStructureUnion a -> CStructureUnion b
fmap a -> b
_f (CStruct CStructTag
a1 Maybe Ident
a2 Maybe [CDeclaration a]
a3 [CAttribute a]
a4 a
a5)
= CStructTag
-> Maybe Ident
-> Maybe [CDeclaration b]
-> [CAttribute b]
-> b
-> CStructureUnion b
forall a.
CStructTag
-> Maybe Ident
-> Maybe [CDeclaration a]
-> [CAttribute a]
-> a
-> CStructureUnion a
CStruct CStructTag
a1 Maybe Ident
a2 (([CDeclaration a] -> [CDeclaration b])
-> Maybe [CDeclaration a] -> Maybe [CDeclaration b]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CDeclaration a -> CDeclaration b)
-> [CDeclaration a] -> [CDeclaration b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f)) Maybe [CDeclaration a]
a3) ((CAttribute a -> CAttribute b) -> [CAttribute a] -> [CAttribute b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAttribute a -> CAttribute b
forall a b. (a -> b) -> CAttribute a -> CAttribute b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAttribute a]
a4)
(a -> b
_f a
a5)
instance Annotated CStructureUnion where
annotation :: forall a. CStructureUnion a -> a
annotation (CStruct CStructTag
_ Maybe Ident
_ Maybe [CDeclaration a]
_ [CAttribute a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CStructureUnion a -> CStructureUnion a
amap a -> a
f (CStruct CStructTag
a_1 Maybe Ident
a_2 Maybe [CDeclaration a]
a_3 [CAttribute a]
a_4 a
a_5)
= CStructTag
-> Maybe Ident
-> Maybe [CDeclaration a]
-> [CAttribute a]
-> a
-> CStructureUnion a
forall a.
CStructTag
-> Maybe Ident
-> Maybe [CDeclaration a]
-> [CAttribute a]
-> a
-> CStructureUnion a
CStruct CStructTag
a_1 Maybe Ident
a_2 Maybe [CDeclaration a]
a_3 [CAttribute a]
a_4 (a -> a
f a
a_5)
instance CNode t1 => CNode (CEnumeration t1) where
nodeInfo :: CEnumeration t1 -> NodeInfo
nodeInfo (CEnum Maybe Ident
_ Maybe [(Ident, Maybe (CExpression t1))]
_ [CAttribute t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CEnumeration t1) where
posOf :: CEnumeration t1 -> Position
posOf CEnumeration t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CEnumeration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CEnumeration t1
x)
instance Functor CEnumeration where
fmap :: forall a b. (a -> b) -> CEnumeration a -> CEnumeration b
fmap a -> b
_f (CEnum Maybe Ident
a1 Maybe [(Ident, Maybe (CExpression a))]
a2 [CAttribute a]
a3 a
a4)
= Maybe Ident
-> Maybe [(Ident, Maybe (CExpression b))]
-> [CAttribute b]
-> b
-> CEnumeration b
forall a.
Maybe Ident
-> Maybe [(Ident, Maybe (CExpression a))]
-> [CAttribute a]
-> a
-> CEnumeration a
CEnum Maybe Ident
a1 (([(Ident, Maybe (CExpression a))]
-> [(Ident, Maybe (CExpression b))])
-> Maybe [(Ident, Maybe (CExpression a))]
-> Maybe [(Ident, Maybe (CExpression b))]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Ident, Maybe (CExpression a)) -> (Ident, Maybe (CExpression b)))
-> [(Ident, Maybe (CExpression a))]
-> [(Ident, Maybe (CExpression b))]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe (CExpression a) -> Maybe (CExpression b))
-> (Ident, Maybe (CExpression a)) -> (Ident, Maybe (CExpression b))
forall a b. (a -> b) -> (Ident, a) -> (Ident, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f)))) Maybe [(Ident, Maybe (CExpression a))]
a2)
((CAttribute a -> CAttribute b) -> [CAttribute a] -> [CAttribute b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CAttribute a -> CAttribute b
forall a b. (a -> b) -> CAttribute a -> CAttribute b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CAttribute a]
a3)
(a -> b
_f a
a4)
instance Annotated CEnumeration where
annotation :: forall a. CEnumeration a -> a
annotation (CEnum Maybe Ident
_ Maybe [(Ident, Maybe (CExpression a))]
_ [CAttribute a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CEnumeration a -> CEnumeration a
amap a -> a
f (CEnum Maybe Ident
a_1 Maybe [(Ident, Maybe (CExpression a))]
a_2 [CAttribute a]
a_3 a
a_4) = Maybe Ident
-> Maybe [(Ident, Maybe (CExpression a))]
-> [CAttribute a]
-> a
-> CEnumeration a
forall a.
Maybe Ident
-> Maybe [(Ident, Maybe (CExpression a))]
-> [CAttribute a]
-> a
-> CEnumeration a
CEnum Maybe Ident
a_1 Maybe [(Ident, Maybe (CExpression a))]
a_2 [CAttribute a]
a_3 (a -> a
f a
a_4)
instance CNode t1 => CNode (CInitializer t1) where
nodeInfo :: CInitializer t1 -> NodeInfo
nodeInfo (CInitExpr CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CInitList CInitializerList t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CInitializer t1) where
posOf :: CInitializer t1 -> Position
posOf CInitializer t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CInitializer t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CInitializer t1
x)
instance Annotated CInitializer where
annotation :: forall a. CInitializer a -> a
annotation (CInitExpr CExpression a
_ a
n) = a
n
annotation (CInitList CInitializerList a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CInitializer a -> CInitializer a
amap a -> a
f (CInitExpr CExpression a
a_1 a
a_2) = CExpression a -> a -> CInitializer a
forall a. CExpression a -> a -> CInitializer a
CInitExpr CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CInitList CInitializerList a
a_1 a
a_2) = CInitializerList a -> a -> CInitializer a
forall a. CInitializerList a -> a -> CInitializer a
CInitList CInitializerList a
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CPartDesignator t1) where
nodeInfo :: CPartDesignator t1 -> NodeInfo
nodeInfo (CArrDesig CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CMemberDesig Ident
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CRangeDesig CExpression t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CPartDesignator t1) where
posOf :: CPartDesignator t1 -> Position
posOf CPartDesignator t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CPartDesignator t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CPartDesignator t1
x)
instance Functor CPartDesignator where
fmap :: forall a b. (a -> b) -> CPartDesignator a -> CPartDesignator b
fmap a -> b
_f (CArrDesig CExpression a
a1 a
a2) = CExpression b -> b -> CPartDesignator b
forall a. CExpression a -> a -> CPartDesignator a
CArrDesig ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) (a -> b
_f a
a2)
fmap a -> b
_f (CMemberDesig Ident
a1 a
a2) = Ident -> b -> CPartDesignator b
forall a. Ident -> a -> CPartDesignator a
CMemberDesig Ident
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CRangeDesig CExpression a
a1 CExpression a
a2 a
a3)
= CExpression b -> CExpression b -> b -> CPartDesignator b
forall a. CExpression a -> CExpression a -> a -> CPartDesignator a
CRangeDesig ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
instance Annotated CPartDesignator where
annotation :: forall a. CPartDesignator a -> a
annotation (CArrDesig CExpression a
_ a
n) = a
n
annotation (CMemberDesig Ident
_ a
n) = a
n
annotation (CRangeDesig CExpression a
_ CExpression a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CPartDesignator a -> CPartDesignator a
amap a -> a
f (CArrDesig CExpression a
a_1 a
a_2) = CExpression a -> a -> CPartDesignator a
forall a. CExpression a -> a -> CPartDesignator a
CArrDesig CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CMemberDesig Ident
a_1 a
a_2) = Ident -> a -> CPartDesignator a
forall a. Ident -> a -> CPartDesignator a
CMemberDesig Ident
a_1 (a -> a
f a
a_2)
amap a -> a
f (CRangeDesig CExpression a
a_1 CExpression a
a_2 a
a_3) = CExpression a -> CExpression a -> a -> CPartDesignator a
forall a. CExpression a -> CExpression a -> a -> CPartDesignator a
CRangeDesig CExpression a
a_1 CExpression a
a_2 (a -> a
f a
a_3)
instance CNode t1 => CNode (CAttribute t1) where
nodeInfo :: CAttribute t1 -> NodeInfo
nodeInfo (CAttr Ident
_ [CExpression t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CAttribute t1) where
posOf :: CAttribute t1 -> Position
posOf CAttribute t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CAttribute t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAttribute t1
x)
instance Functor CAttribute where
fmap :: forall a b. (a -> b) -> CAttribute a -> CAttribute b
fmap a -> b
_f (CAttr Ident
a1 [CExpression a]
a2 a
a3) = Ident -> [CExpression b] -> b -> CAttribute b
forall a. Ident -> [CExpression a] -> a -> CAttribute a
CAttr Ident
a1 ((CExpression a -> CExpression b)
-> [CExpression a] -> [CExpression b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CExpression a]
a2) (a -> b
_f a
a3)
instance Annotated CAttribute where
annotation :: forall a. CAttribute a -> a
annotation (CAttr Ident
_ [CExpression a]
_ a
n) = a
n
amap :: forall a. (a -> a) -> CAttribute a -> CAttribute a
amap a -> a
f (CAttr Ident
a_1 [CExpression a]
a_2 a
a_3) = Ident -> [CExpression a] -> a -> CAttribute a
forall a. Ident -> [CExpression a] -> a -> CAttribute a
CAttr Ident
a_1 [CExpression a]
a_2 (a -> a
f a
a_3)
instance CNode t1 => CNode (CExpression t1) where
nodeInfo :: CExpression t1 -> NodeInfo
nodeInfo (CComma [CExpression t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAssign CAssignOp
_ CExpression t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCond CExpression t1
_ Maybe (CExpression t1)
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBinary CBinaryOp
_ CExpression t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCast CDeclaration t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CUnary CUnaryOp
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CSizeofExpr CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CSizeofType CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAlignofExpr CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAlignofType CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CComplexReal CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CComplexImag CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CIndex CExpression t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCall CExpression t1
_ [CExpression t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CMember CExpression t1
_ Ident
_ Bool
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CVar Ident
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CConst CConstant t1
d) = CConstant t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CConstant t1
d
nodeInfo (CCompoundLit CDeclaration t1
_ CInitializerList t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CGenericSelection CExpression t1
_ [(Maybe (CDeclaration t1), CExpression t1)]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CStatExpr CStatement t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CLabAddrExpr Ident
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinExpr CBuiltinThing t1
d) = CBuiltinThing t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CBuiltinThing t1
d
instance CNode t1 => Pos (CExpression t1) where
posOf :: CExpression t1 -> Position
posOf CExpression t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CExpression t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CExpression t1
x)
instance Annotated CExpression where
annotation :: forall a. CExpression a -> a
annotation (CComma [CExpression a]
_ a
n) = a
n
annotation (CAssign CAssignOp
_ CExpression a
_ CExpression a
_ a
n) = a
n
annotation (CCond CExpression a
_ Maybe (CExpression a)
_ CExpression a
_ a
n) = a
n
annotation (CBinary CBinaryOp
_ CExpression a
_ CExpression a
_ a
n) = a
n
annotation (CCast CDeclaration a
_ CExpression a
_ a
n) = a
n
annotation (CUnary CUnaryOp
_ CExpression a
_ a
n) = a
n
annotation (CSizeofExpr CExpression a
_ a
n) = a
n
annotation (CSizeofType CDeclaration a
_ a
n) = a
n
annotation (CAlignofExpr CExpression a
_ a
n) = a
n
annotation (CAlignofType CDeclaration a
_ a
n) = a
n
annotation (CComplexReal CExpression a
_ a
n) = a
n
annotation (CComplexImag CExpression a
_ a
n) = a
n
annotation (CIndex CExpression a
_ CExpression a
_ a
n) = a
n
annotation (CCall CExpression a
_ [CExpression a]
_ a
n) = a
n
annotation (CMember CExpression a
_ Ident
_ Bool
_ a
n) = a
n
annotation (CVar Ident
_ a
n) = a
n
annotation (CConst CConstant a
n) = CConstant a -> a
forall a. CConstant a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CConstant a
n
annotation (CCompoundLit CDeclaration a
_ CInitializerList a
_ a
n) = a
n
annotation (CGenericSelection CExpression a
_ [(Maybe (CDeclaration a), CExpression a)]
_ a
n) = a
n
annotation (CStatExpr CStatement a
_ a
n) = a
n
annotation (CLabAddrExpr Ident
_ a
n) = a
n
annotation (CBuiltinExpr CBuiltinThing a
n) = CBuiltinThing a -> a
forall a. CBuiltinThing a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CBuiltinThing a
n
amap :: forall a. (a -> a) -> CExpression a -> CExpression a
amap a -> a
f (CComma [CExpression a]
a_1 a
a_2) = [CExpression a] -> a -> CExpression a
forall a. [CExpression a] -> a -> CExpression a
CComma [CExpression a]
a_1 (a -> a
f a
a_2)
amap a -> a
f (CAssign CAssignOp
a_1 CExpression a
a_2 CExpression a
a_3 a
a_4) = CAssignOp -> CExpression a -> CExpression a -> a -> CExpression a
forall a.
CAssignOp -> CExpression a -> CExpression a -> a -> CExpression a
CAssign CAssignOp
a_1 CExpression a
a_2 CExpression a
a_3 (a -> a
f a
a_4)
amap a -> a
f (CCond CExpression a
a_1 Maybe (CExpression a)
a_2 CExpression a
a_3 a
a_4) = CExpression a
-> Maybe (CExpression a) -> CExpression a -> a -> CExpression a
forall a.
CExpression a
-> Maybe (CExpression a) -> CExpression a -> a -> CExpression a
CCond CExpression a
a_1 Maybe (CExpression a)
a_2 CExpression a
a_3 (a -> a
f a
a_4)
amap a -> a
f (CBinary CBinaryOp
a_1 CExpression a
a_2 CExpression a
a_3 a
a_4) = CBinaryOp -> CExpression a -> CExpression a -> a -> CExpression a
forall a.
CBinaryOp -> CExpression a -> CExpression a -> a -> CExpression a
CBinary CBinaryOp
a_1 CExpression a
a_2 CExpression a
a_3 (a -> a
f a
a_4)
amap a -> a
f (CCast CDeclaration a
a_1 CExpression a
a_2 a
a_3) = CDeclaration a -> CExpression a -> a -> CExpression a
forall a. CDeclaration a -> CExpression a -> a -> CExpression a
CCast CDeclaration a
a_1 CExpression a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CUnary CUnaryOp
a_1 CExpression a
a_2 a
a_3) = CUnaryOp -> CExpression a -> a -> CExpression a
forall a. CUnaryOp -> CExpression a -> a -> CExpression a
CUnary CUnaryOp
a_1 CExpression a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CSizeofExpr CExpression a
a_1 a
a_2) = CExpression a -> a -> CExpression a
forall a. CExpression a -> a -> CExpression a
CSizeofExpr CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CSizeofType CDeclaration a
a_1 a
a_2) = CDeclaration a -> a -> CExpression a
forall a. CDeclaration a -> a -> CExpression a
CSizeofType CDeclaration a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CAlignofExpr CExpression a
a_1 a
a_2) = CExpression a -> a -> CExpression a
forall a. CExpression a -> a -> CExpression a
CAlignofExpr CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CAlignofType CDeclaration a
a_1 a
a_2) = CDeclaration a -> a -> CExpression a
forall a. CDeclaration a -> a -> CExpression a
CAlignofType CDeclaration a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CComplexReal CExpression a
a_1 a
a_2) = CExpression a -> a -> CExpression a
forall a. CExpression a -> a -> CExpression a
CComplexReal CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CComplexImag CExpression a
a_1 a
a_2) = CExpression a -> a -> CExpression a
forall a. CExpression a -> a -> CExpression a
CComplexImag CExpression a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CIndex CExpression a
a_1 CExpression a
a_2 a
a_3) = CExpression a -> CExpression a -> a -> CExpression a
forall a. CExpression a -> CExpression a -> a -> CExpression a
CIndex CExpression a
a_1 CExpression a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CCall CExpression a
a_1 [CExpression a]
a_2 a
a_3) = CExpression a -> [CExpression a] -> a -> CExpression a
forall a. CExpression a -> [CExpression a] -> a -> CExpression a
CCall CExpression a
a_1 [CExpression a]
a_2 (a -> a
f a
a_3)
amap a -> a
f (CMember CExpression a
a_1 Ident
a_2 Bool
a_3 a
a_4) = CExpression a -> Ident -> Bool -> a -> CExpression a
forall a. CExpression a -> Ident -> Bool -> a -> CExpression a
CMember CExpression a
a_1 Ident
a_2 Bool
a_3 (a -> a
f a
a_4)
amap a -> a
f (CVar Ident
a_1 a
a_2) = Ident -> a -> CExpression a
forall a. Ident -> a -> CExpression a
CVar Ident
a_1 (a -> a
f a
a_2)
amap a -> a
f (CConst CConstant a
n) = CConstant a -> CExpression a
forall a. CConstant a -> CExpression a
CConst ((a -> a) -> CConstant a -> CConstant a
forall a. (a -> a) -> CConstant a -> CConstant a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CConstant a
n)
amap a -> a
f (CCompoundLit CDeclaration a
a_1 CInitializerList a
a_2 a
a_3) = CDeclaration a -> CInitializerList a -> a -> CExpression a
forall a.
CDeclaration a -> CInitializerList a -> a -> CExpression a
CCompoundLit CDeclaration a
a_1 CInitializerList a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CGenericSelection CExpression a
a_1 [(Maybe (CDeclaration a), CExpression a)]
a_2 a
a_3)
= CExpression a
-> [(Maybe (CDeclaration a), CExpression a)] -> a -> CExpression a
forall a.
CExpression a
-> [(Maybe (CDeclaration a), CExpression a)] -> a -> CExpression a
CGenericSelection CExpression a
a_1 [(Maybe (CDeclaration a), CExpression a)]
a_2 (a -> a
f a
a_3)
amap a -> a
f (CStatExpr CStatement a
a_1 a
a_2) = CStatement a -> a -> CExpression a
forall a. CStatement a -> a -> CExpression a
CStatExpr CStatement a
a_1 (a -> a
f a
a_2)
amap a -> a
f (CLabAddrExpr Ident
a_1 a
a_2) = Ident -> a -> CExpression a
forall a. Ident -> a -> CExpression a
CLabAddrExpr Ident
a_1 (a -> a
f a
a_2)
amap a -> a
f (CBuiltinExpr CBuiltinThing a
n) = CBuiltinThing a -> CExpression a
forall a. CBuiltinThing a -> CExpression a
CBuiltinExpr ((a -> a) -> CBuiltinThing a -> CBuiltinThing a
forall a. (a -> a) -> CBuiltinThing a -> CBuiltinThing a
forall (ast :: * -> *) a.
Annotated ast =>
(a -> a) -> ast a -> ast a
amap a -> a
f CBuiltinThing a
n)
instance CNode t1 => CNode (CBuiltinThing t1) where
nodeInfo :: CBuiltinThing t1 -> NodeInfo
nodeInfo (CBuiltinVaArg CExpression t1
_ CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinOffsetOf CDeclaration t1
_ [CPartDesignator t1]
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinTypesCompatible CDeclaration t1
_ CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinConvertVector CExpression t1
_ CDeclaration t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinBitCast CDeclaration t1
_ CExpression t1
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CBuiltinThing t1) where
posOf :: CBuiltinThing t1 -> Position
posOf CBuiltinThing t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CBuiltinThing t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CBuiltinThing t1
x)
instance Functor CBuiltinThing where
fmap :: forall a b. (a -> b) -> CBuiltinThing a -> CBuiltinThing b
fmap a -> b
_f (CBuiltinVaArg CExpression a
a1 CDeclaration a
a2 a
a3)
= CExpression b -> CDeclaration b -> b -> CBuiltinThing b
forall a. CExpression a -> CDeclaration a -> a -> CBuiltinThing a
CBuiltinVaArg ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CBuiltinOffsetOf CDeclaration a
a1 [CPartDesignator a]
a2 a
a3)
= CDeclaration b -> [CPartDesignator b] -> b -> CBuiltinThing b
forall a.
CDeclaration a -> [CPartDesignator a] -> a -> CBuiltinThing a
CBuiltinOffsetOf ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) ((CPartDesignator a -> CPartDesignator b)
-> [CPartDesignator a] -> [CPartDesignator b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> CPartDesignator a -> CPartDesignator b
forall a b. (a -> b) -> CPartDesignator a -> CPartDesignator b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f) [CPartDesignator a]
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CBuiltinTypesCompatible CDeclaration a
a1 CDeclaration a
a2 a
a3)
= CDeclaration b -> CDeclaration b -> b -> CBuiltinThing b
forall a. CDeclaration a -> CDeclaration a -> a -> CBuiltinThing a
CBuiltinTypesCompatible ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CBuiltinConvertVector CExpression a
a1 CDeclaration a
a2 a
a3)
= CExpression b -> CDeclaration b -> b -> CBuiltinThing b
forall a. CExpression a -> CDeclaration a -> a -> CBuiltinThing a
CBuiltinConvertVector ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a1) ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a2) (a -> b
_f a
a3)
fmap a -> b
_f (CBuiltinBitCast CDeclaration a
a1 CExpression a
a2 a
a3)
= CDeclaration b -> CExpression b -> b -> CBuiltinThing b
forall a. CDeclaration a -> CExpression a -> a -> CBuiltinThing a
CBuiltinBitCast ((a -> b) -> CDeclaration a -> CDeclaration b
forall a b. (a -> b) -> CDeclaration a -> CDeclaration b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a1) ((a -> b) -> CExpression a -> CExpression b
forall a b. (a -> b) -> CExpression a -> CExpression b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
instance Annotated CBuiltinThing where
annotation :: forall a. CBuiltinThing a -> a
annotation (CBuiltinVaArg CExpression a
_ CDeclaration a
_ a
n) = a
n
annotation (CBuiltinOffsetOf CDeclaration a
_ [CPartDesignator a]
_ a
n) = a
n
annotation (CBuiltinTypesCompatible CDeclaration a
_ CDeclaration a
_ a
n) = a
n
annotation (CBuiltinConvertVector CExpression a
_ CDeclaration a
_ a
n) = a
n
annotation (CBuiltinBitCast CDeclaration a
_ CExpression a
_ a
n) = a
n
amap :: forall a. (a -> a) -> CBuiltinThing a -> CBuiltinThing a
amap a -> a
f (CBuiltinVaArg CExpression a
a_1 CDeclaration a
a_2 a
a_3) = CExpression a -> CDeclaration a -> a -> CBuiltinThing a
forall a. CExpression a -> CDeclaration a -> a -> CBuiltinThing a
CBuiltinVaArg CExpression a
a_1 CDeclaration a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CBuiltinOffsetOf CDeclaration a
a_1 [CPartDesignator a]
a_2 a
a_3)
= CDeclaration a -> [CPartDesignator a] -> a -> CBuiltinThing a
forall a.
CDeclaration a -> [CPartDesignator a] -> a -> CBuiltinThing a
CBuiltinOffsetOf CDeclaration a
a_1 [CPartDesignator a]
a_2 (a -> a
f a
a_3)
amap a -> a
f (CBuiltinTypesCompatible CDeclaration a
a_1 CDeclaration a
a_2 a
a_3)
= CDeclaration a -> CDeclaration a -> a -> CBuiltinThing a
forall a. CDeclaration a -> CDeclaration a -> a -> CBuiltinThing a
CBuiltinTypesCompatible CDeclaration a
a_1 CDeclaration a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CBuiltinConvertVector CExpression a
a_1 CDeclaration a
a_2 a
a_3) =
CExpression a -> CDeclaration a -> a -> CBuiltinThing a
forall a. CExpression a -> CDeclaration a -> a -> CBuiltinThing a
CBuiltinConvertVector CExpression a
a_1 CDeclaration a
a_2 (a -> a
f a
a_3)
amap a -> a
f (CBuiltinBitCast CDeclaration a
a_1 CExpression a
a_2 a
a_3) =
CDeclaration a -> CExpression a -> a -> CBuiltinThing a
forall a. CDeclaration a -> CExpression a -> a -> CBuiltinThing a
CBuiltinBitCast CDeclaration a
a_1 CExpression a
a_2 (a -> a
f a
a_3)
instance CNode t1 => CNode (CConstant t1) where
nodeInfo :: CConstant t1 -> NodeInfo
nodeInfo (CIntConst CInteger
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCharConst CChar
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CFloatConst CFloat
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CStrConst CString
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CConstant t1) where
posOf :: CConstant t1 -> Position
posOf CConstant t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CConstant t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CConstant t1
x)
instance Functor CConstant where
fmap :: forall a b. (a -> b) -> CConstant a -> CConstant b
fmap a -> b
_f (CIntConst CInteger
a1 a
a2) = CInteger -> b -> CConstant b
forall a. CInteger -> a -> CConstant a
CIntConst CInteger
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CCharConst CChar
a1 a
a2) = CChar -> b -> CConstant b
forall a. CChar -> a -> CConstant a
CCharConst CChar
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CFloatConst CFloat
a1 a
a2) = CFloat -> b -> CConstant b
forall a. CFloat -> a -> CConstant a
CFloatConst CFloat
a1 (a -> b
_f a
a2)
fmap a -> b
_f (CStrConst CString
a1 a
a2) = CString -> b -> CConstant b
forall a. CString -> a -> CConstant a
CStrConst CString
a1 (a -> b
_f a
a2)
instance Annotated CConstant where
annotation :: forall a. CConstant a -> a
annotation (CIntConst CInteger
_ a
n) = a
n
annotation (CCharConst CChar
_ a
n) = a
n
annotation (CFloatConst CFloat
_ a
n) = a
n
annotation (CStrConst CString
_ a
n) = a
n
amap :: forall a. (a -> a) -> CConstant a -> CConstant a
amap a -> a
f (CIntConst CInteger
a_1 a
a_2) = CInteger -> a -> CConstant a
forall a. CInteger -> a -> CConstant a
CIntConst CInteger
a_1 (a -> a
f a
a_2)
amap a -> a
f (CCharConst CChar
a_1 a
a_2) = CChar -> a -> CConstant a
forall a. CChar -> a -> CConstant a
CCharConst CChar
a_1 (a -> a
f a
a_2)
amap a -> a
f (CFloatConst CFloat
a_1 a
a_2) = CFloat -> a -> CConstant a
forall a. CFloat -> a -> CConstant a
CFloatConst CFloat
a_1 (a -> a
f a
a_2)
amap a -> a
f (CStrConst CString
a_1 a
a_2) = CString -> a -> CConstant a
forall a. CString -> a -> CConstant a
CStrConst CString
a_1 (a -> a
f a
a_2)
instance CNode t1 => CNode (CStringLiteral t1) where
nodeInfo :: CStringLiteral t1 -> NodeInfo
nodeInfo (CStrLit CString
_ t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
instance CNode t1 => Pos (CStringLiteral t1) where
posOf :: CStringLiteral t1 -> Position
posOf CStringLiteral t1
x = NodeInfo -> Position
forall a. Pos a => a -> Position
posOf (CStringLiteral t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStringLiteral t1
x)
instance Functor CStringLiteral where
fmap :: forall a b. (a -> b) -> CStringLiteral a -> CStringLiteral b
fmap a -> b
_f (CStrLit CString
a1 a
a2) = CString -> b -> CStringLiteral b
forall a. CString -> a -> CStringLiteral a
CStrLit CString
a1 (a -> b
_f a
a2)
instance Annotated CStringLiteral where
annotation :: forall a. CStringLiteral a -> a
annotation (CStrLit CString
_ a
n) = a
n
amap :: forall a. (a -> a) -> CStringLiteral a -> CStringLiteral a
amap a -> a
f (CStrLit CString
a_1 a
a_2) = CString -> a -> CStringLiteral a
forall a. CString -> a -> CStringLiteral a
CStrLit CString
a_1 (a -> a
f a
a_2)