{-# 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.Generics hiding (Generic)
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
showList :: [CTranslationUnit a] -> ShowS
$cshowList :: forall a. Show a => [CTranslationUnit a] -> ShowS
show :: CTranslationUnit a -> String
$cshow :: forall a. Show a => CTranslationUnit a -> String
showsPrec :: Int -> CTranslationUnit a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CTranslationUnit a -> ShowS
Show, Typeable (CTranslationUnit a)
DataType
Constr
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 -> DataType
CTranslationUnit a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
(forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> c (CTranslationUnit a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTranslationUnit a)
forall a. Data a => Typeable (CTranslationUnit a)
forall a. Data a => CTranslationUnit a -> DataType
forall a. Data a => CTranslationUnit a -> Constr
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))
$cCTranslUnit :: Constr
$tCTranslationUnit :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTranslationUnit a -> m (CTranslationUnit a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CTranslationUnit a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTranslationUnit a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTranslationUnit a -> r
gmapT :: (forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTranslationUnit a -> CTranslationUnit a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTranslationUnit a))
dataTypeOf :: CTranslationUnit a -> DataType
$cdataTypeOf :: forall a. Data a => CTranslationUnit a -> DataType
toConstr :: CTranslationUnit a -> Constr
$ctoConstr :: forall a. Data a => CTranslationUnit a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CTranslationUnit a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CTranslationUnit a) x -> CTranslationUnit a
$cfrom :: forall a x. CTranslationUnit a -> Rep (CTranslationUnit a) x
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
$cto1 :: forall a. Rep1 CTranslationUnit a -> CTranslationUnit a
$cfrom1 :: forall a. CTranslationUnit a -> Rep1 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
showList :: [CExternalDeclaration a] -> ShowS
$cshowList :: forall a. Show a => [CExternalDeclaration a] -> ShowS
show :: CExternalDeclaration a -> String
$cshow :: forall a. Show a => CExternalDeclaration a -> String
showsPrec :: Int -> CExternalDeclaration a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CExternalDeclaration a -> ShowS
Show, Typeable (CExternalDeclaration a)
DataType
Constr
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 -> DataType
CExternalDeclaration a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
(forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> c (CExternalDeclaration a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExternalDeclaration a)
forall a. Data a => Typeable (CExternalDeclaration a)
forall a. Data a => CExternalDeclaration a -> DataType
forall a. Data a => CExternalDeclaration a -> Constr
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))
$cCAsmExt :: Constr
$cCFDefExt :: Constr
$cCDeclExt :: Constr
$tCExternalDeclaration :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CExternalDeclaration a -> m (CExternalDeclaration a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CExternalDeclaration a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CExternalDeclaration a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CExternalDeclaration a
-> r
gmapT :: (forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CExternalDeclaration a -> CExternalDeclaration a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CExternalDeclaration a))
dataTypeOf :: CExternalDeclaration a -> DataType
$cdataTypeOf :: forall a. Data a => CExternalDeclaration a -> DataType
toConstr :: CExternalDeclaration a -> Constr
$ctoConstr :: forall a. Data a => CExternalDeclaration a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CExternalDeclaration a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x.
Rep (CExternalDeclaration a) x -> CExternalDeclaration a
$cfrom :: forall a x.
CExternalDeclaration a -> Rep (CExternalDeclaration a) x
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
$cto1 :: forall a. Rep1 CExternalDeclaration a -> CExternalDeclaration a
$cfrom1 :: forall a. CExternalDeclaration a -> Rep1 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
showList :: [CFunctionDef a] -> ShowS
$cshowList :: forall a. Show a => [CFunctionDef a] -> ShowS
show :: CFunctionDef a -> String
$cshow :: forall a. Show a => CFunctionDef a -> String
showsPrec :: Int -> CFunctionDef a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CFunctionDef a -> ShowS
Show, Typeable (CFunctionDef a)
DataType
Constr
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 -> DataType
CFunctionDef a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
(forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> c (CFunctionDef a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionDef a)
forall a. Data a => Typeable (CFunctionDef a)
forall a. Data a => CFunctionDef a -> DataType
forall a. Data a => CFunctionDef a -> Constr
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))
$cCFunDef :: Constr
$tCFunctionDef :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CFunctionDef a -> m (CFunctionDef a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CFunctionDef a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CFunctionDef a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionDef a -> r
gmapT :: (forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CFunctionDef a -> CFunctionDef a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionDef a))
dataTypeOf :: CFunctionDef a -> DataType
$cdataTypeOf :: forall a. Data a => CFunctionDef a -> DataType
toConstr :: CFunctionDef a -> Constr
$ctoConstr :: forall a. Data a => CFunctionDef a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CFunctionDef a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CFunctionDef a) x -> CFunctionDef a
$cfrom :: forall a x. CFunctionDef a -> Rep (CFunctionDef a) x
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
$cto1 :: forall a. Rep1 CFunctionDef a -> CFunctionDef a
$cfrom1 :: forall a. CFunctionDef a -> Rep1 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
showList :: [CDeclaration a] -> ShowS
$cshowList :: forall a. Show a => [CDeclaration a] -> ShowS
show :: CDeclaration a -> String
$cshow :: forall a. Show a => CDeclaration a -> String
showsPrec :: Int -> CDeclaration a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CDeclaration a -> ShowS
Show, Typeable (CDeclaration a)
DataType
Constr
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 -> DataType
CDeclaration a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
(forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> c (CDeclaration a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclaration a)
forall a. Data a => Typeable (CDeclaration a)
forall a. Data a => CDeclaration a -> DataType
forall a. Data a => CDeclaration a -> Constr
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))
$cCStaticAssert :: Constr
$cCDecl :: Constr
$tCDeclaration :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclaration a -> m (CDeclaration a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CDeclaration a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclaration a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclaration a -> r
gmapT :: (forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CDeclaration a -> CDeclaration a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclaration a))
dataTypeOf :: CDeclaration a -> DataType
$cdataTypeOf :: forall a. Data a => CDeclaration a -> DataType
toConstr :: CDeclaration a -> Constr
$ctoConstr :: forall a. Data a => CDeclaration a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclaration a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CDeclaration a) x -> CDeclaration a
$cfrom :: forall a x. CDeclaration a -> Rep (CDeclaration a) x
Generic )
instance NFData a => NFData (CDeclaration a)
instance Functor CDeclaration where
fmap :: (a -> b) -> CDeclaration a -> CDeclaration b
fmap f :: a -> b
f (CDecl specs :: [CDeclarationSpecifier a]
specs declarators :: [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
declarators annot :: 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 (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 (a :: f (f a)
a,b :: f (f a)
b,c :: f (f a)
c) = ((f a -> f b) -> f (f a) -> f (f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 f :: a -> b
f (CStaticAssert expression :: CExpression a
expression strlit :: CStringLiteral a
strlit annot :: 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 (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 (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
showList :: [CDeclarator a] -> ShowS
$cshowList :: forall a. Show a => [CDeclarator a] -> ShowS
show :: CDeclarator a -> String
$cshow :: forall a. Show a => CDeclarator a -> String
showsPrec :: Int -> CDeclarator a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CDeclarator a -> ShowS
Show, Typeable (CDeclarator a)
DataType
Constr
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 -> DataType
CDeclarator a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
(forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> c (CDeclarator a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarator a)
forall a. Data a => Typeable (CDeclarator a)
forall a. Data a => CDeclarator a -> DataType
forall a. Data a => CDeclarator a -> Constr
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))
$cCDeclr :: Constr
$tCDeclarator :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclarator a -> m (CDeclarator a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CDeclarator a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclarator a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDeclarator a -> r
gmapT :: (forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CDeclarator a -> CDeclarator a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDeclarator a))
dataTypeOf :: CDeclarator a -> DataType
$cdataTypeOf :: forall a. Data a => CDeclarator a -> DataType
toConstr :: CDeclarator a -> Constr
$ctoConstr :: forall a. Data a => CDeclarator a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CDeclarator a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CDeclarator a) x -> CDeclarator a
$cfrom :: forall a x. CDeclarator a -> Rep (CDeclarator a) x
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
$cto1 :: forall a. Rep1 CDeclarator a -> CDeclarator a
$cfrom1 :: forall a. CDeclarator a -> Rep1 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
showList :: [CDerivedDeclarator a] -> ShowS
$cshowList :: forall a. Show a => [CDerivedDeclarator a] -> ShowS
show :: CDerivedDeclarator a -> String
$cshow :: forall a. Show a => CDerivedDeclarator a -> String
showsPrec :: Int -> CDerivedDeclarator a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CDerivedDeclarator a -> ShowS
Show, Typeable (CDerivedDeclarator a)
DataType
Constr
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 -> DataType
CDerivedDeclarator a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
(forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> c (CDerivedDeclarator a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDerivedDeclarator a)
forall a. Data a => Typeable (CDerivedDeclarator a)
forall a. Data a => CDerivedDeclarator a -> DataType
forall a. Data a => CDerivedDeclarator a -> Constr
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))
$cCFunDeclr :: Constr
$cCArrDeclr :: Constr
$cCPtrDeclr :: Constr
$tCDerivedDeclarator :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDerivedDeclarator a -> m (CDerivedDeclarator a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDerivedDeclarator a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CDerivedDeclarator a -> r
gmapT :: (forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CDerivedDeclarator a -> CDerivedDeclarator a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CDerivedDeclarator a))
dataTypeOf :: CDerivedDeclarator a -> DataType
$cdataTypeOf :: forall a. Data a => CDerivedDeclarator a -> DataType
toConstr :: CDerivedDeclarator a -> Constr
$ctoConstr :: forall a. Data a => CDerivedDeclarator a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDerivedDeclarator a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CDerivedDeclarator a) x -> CDerivedDeclarator a
$cfrom :: forall a x. CDerivedDeclarator a -> Rep (CDerivedDeclarator a) x
Generic )
instance NFData a => NFData (CDerivedDeclarator a)
instance Functor CDerivedDeclarator where
fmap :: (a -> b) -> CDerivedDeclarator a -> CDerivedDeclarator b
fmap _f :: a -> b
_f (CPtrDeclr a1 :: [CTypeQualifier a]
a1 a2 :: a
a2) = [CTypeQualifier b] -> b -> CDerivedDeclarator b
forall a. [CTypeQualifier a] -> a -> CDerivedDeclarator a
CPtrDeclr ((CTypeQualifier a -> CTypeQualifier b)
-> [CTypeQualifier a] -> [CTypeQualifier b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CArrDeclr a1 :: [CTypeQualifier a]
a1 a2 :: CArraySize a
a2 a3 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CArraySize a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CFunDeclr a1 :: Either [Ident] ([CDeclaration a], Bool)
a1 a2 :: [CAttribute a]
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 f :: t -> a
f (a :: t
a,b :: 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
showList :: [CArraySize a] -> ShowS
$cshowList :: forall a. Show a => [CArraySize a] -> ShowS
show :: CArraySize a -> String
$cshow :: forall a. Show a => CArraySize a -> String
showsPrec :: Int -> CArraySize a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CArraySize a -> ShowS
Show, Typeable (CArraySize a)
DataType
Constr
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 -> DataType
CArraySize a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
(forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> c (CArraySize a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CArraySize a)
forall a. Data a => Typeable (CArraySize a)
forall a. Data a => CArraySize a -> DataType
forall a. Data a => CArraySize a -> Constr
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))
$cCArrSize :: Constr
$cCNoArrSize :: Constr
$tCArraySize :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CArraySize a -> m (CArraySize a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CArraySize a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CArraySize a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CArraySize a -> r
gmapT :: (forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CArraySize a -> CArraySize a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CArraySize a))
dataTypeOf :: CArraySize a -> DataType
$cdataTypeOf :: forall a. Data a => CArraySize a -> DataType
toConstr :: CArraySize a -> Constr
$ctoConstr :: forall a. Data a => CArraySize a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CArraySize a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CArraySize a) x -> CArraySize a
$cfrom :: forall a x. CArraySize a -> Rep (CArraySize a) x
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
$cto1 :: forall a. Rep1 CArraySize a -> CArraySize a
$cfrom1 :: forall a. CArraySize a -> Rep1 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
showList :: [CStatement a] -> ShowS
$cshowList :: forall a. Show a => [CStatement a] -> ShowS
show :: CStatement a -> String
$cshow :: forall a. Show a => CStatement a -> String
showsPrec :: Int -> CStatement a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CStatement a -> ShowS
Show, Typeable (CStatement a)
DataType
Constr
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 -> DataType
CStatement a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
(forall b. Data b => b -> b) -> CStatement a -> CStatement a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> c (CStatement a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStatement a)
forall a. Data a => Typeable (CStatement a)
forall a. Data a => CStatement a -> DataType
forall a. Data a => CStatement a -> Constr
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))
$cCAsm :: Constr
$cCReturn :: Constr
$cCBreak :: Constr
$cCCont :: Constr
$cCGotoPtr :: Constr
$cCGoto :: Constr
$cCFor :: Constr
$cCWhile :: Constr
$cCSwitch :: Constr
$cCIf :: Constr
$cCCompound :: Constr
$cCExpr :: Constr
$cCDefault :: Constr
$cCCases :: Constr
$cCCase :: Constr
$cCLabel :: Constr
$tCStatement :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CStatement a -> m (CStatement a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CStatement a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStatement a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStatement a -> r
gmapT :: (forall b. Data b => b -> b) -> CStatement a -> CStatement a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CStatement a -> CStatement a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStatement a))
dataTypeOf :: CStatement a -> DataType
$cdataTypeOf :: forall a. Data a => CStatement a -> DataType
toConstr :: CStatement a -> Constr
$ctoConstr :: forall a. Data a => CStatement a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStatement a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CStatement a) x -> CStatement a
$cfrom :: forall a x. CStatement a -> Rep (CStatement a) x
Generic )
instance NFData a => NFData (CStatement a)
instance Functor CStatement where
fmap :: (a -> b) -> CStatement a -> CStatement b
fmap _f :: a -> b
_f (CLabel a1 :: Ident
a1 a2 :: CStatement a
a2 a3 :: [CAttribute a]
a3 a4 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CCase a1 :: CExpression a
a1 a2 :: CStatement a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CCases a1 :: CExpression a
a1 a2 :: CExpression a
a2 a3 :: CStatement a
a3 a4 :: 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 (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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a3) (a -> b
_f a
a4)
fmap _f :: a -> b
_f (CDefault a1 :: CStatement a
a1 a2 :: a
a2) = CStatement b -> b -> CStatement b
forall a. CStatement a -> a -> CStatement a
CDefault ((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 _f :: a -> b
_f (CExpr a1 :: Maybe (CExpression a)
a1 a2 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CCompound a1 :: [Ident]
a1 a2 :: [CCompoundBlockItem a]
a2 a3 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CIf a1 :: CExpression a
a1 a2 :: CStatement a
a2 a3 :: Maybe (CStatement a)
a3 a4 :: 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 (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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CSwitch a1 :: CExpression a
a1 a2 :: CStatement a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CStatement a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CWhile a1 :: CExpression a
a1 a2 :: CStatement a
a2 a3 :: Bool
a3 a4 :: 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 (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 (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 _f :: a -> b
_f (CFor a1 :: Either (Maybe (CExpression a)) (CDeclaration a)
a1 a2 :: Maybe (CExpression a)
a2 a3 :: Maybe (CExpression a)
a3 a4 :: CStatement a
a4 a5 :: 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 a a b. (a -> a) -> (a -> b) -> Either a a -> Either a b
mapEither ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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 -> a) -> (a -> b) -> Either a a -> Either a b
mapEither f1 :: a -> a
f1 f2 :: a -> b
f2 = (a -> Either a b) -> (a -> Either a b) -> Either a a -> Either a b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (a -> Either a b
forall a b. a -> Either a b
Left (a -> Either a b) -> (a -> a) -> a -> Either a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
f1) (b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b) -> (a -> b) -> a -> Either a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f2)
fmap _f :: a -> b
_f (CGoto a1 :: Ident
a1 a2 :: a
a2) = Ident -> b -> CStatement b
forall a. Ident -> a -> CStatement a
CGoto Ident
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CGotoPtr a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CStatement b
forall a. CExpression a -> a -> CStatement a
CGotoPtr ((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 _f :: a -> b
_f (CCont a1 :: a
a1) = b -> CStatement b
forall a. a -> CStatement a
CCont (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CBreak a1 :: a
a1) = b -> CStatement b
forall a. a -> CStatement a
CBreak (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CReturn a1 :: Maybe (CExpression a)
a1 a2 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CAsm a1 :: CAssemblyStatement a
a1 a2 :: a
a2) = CAssemblyStatement b -> b -> CStatement b
forall a. CAssemblyStatement a -> a -> CStatement a
CAsm ((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
showList :: [CAssemblyStatement a] -> ShowS
$cshowList :: forall a. Show a => [CAssemblyStatement a] -> ShowS
show :: CAssemblyStatement a -> String
$cshow :: forall a. Show a => CAssemblyStatement a -> String
showsPrec :: Int -> CAssemblyStatement a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CAssemblyStatement a -> ShowS
Show, Typeable (CAssemblyStatement a)
DataType
Constr
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 -> DataType
CAssemblyStatement a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
(forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> c (CAssemblyStatement a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyStatement a)
forall a. Data a => Typeable (CAssemblyStatement a)
forall a. Data a => CAssemblyStatement a -> DataType
forall a. Data a => CAssemblyStatement a -> Constr
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))
$cCAsmStmt :: Constr
$tCAssemblyStatement :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAssemblyStatement a -> m (CAssemblyStatement a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CAssemblyStatement a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAssemblyStatement a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyStatement a -> r
gmapT :: (forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAssemblyStatement a -> CAssemblyStatement a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyStatement a))
dataTypeOf :: CAssemblyStatement a -> DataType
$cdataTypeOf :: forall a. Data a => CAssemblyStatement a -> DataType
toConstr :: CAssemblyStatement a -> Constr
$ctoConstr :: forall a. Data a => CAssemblyStatement a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyStatement a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CAssemblyStatement a) x -> CAssemblyStatement a
$cfrom :: forall a x. CAssemblyStatement a -> Rep (CAssemblyStatement a) x
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
$cto1 :: forall a. Rep1 CAssemblyStatement a -> CAssemblyStatement a
$cfrom1 :: forall a. CAssemblyStatement a -> Rep1 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
showList :: [CAssemblyOperand a] -> ShowS
$cshowList :: forall a. Show a => [CAssemblyOperand a] -> ShowS
show :: CAssemblyOperand a -> String
$cshow :: forall a. Show a => CAssemblyOperand a -> String
showsPrec :: Int -> CAssemblyOperand a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CAssemblyOperand a -> ShowS
Show, Typeable (CAssemblyOperand a)
DataType
Constr
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 -> DataType
CAssemblyOperand a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
(forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> c (CAssemblyOperand a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAssemblyOperand a)
forall a. Data a => Typeable (CAssemblyOperand a)
forall a. Data a => CAssemblyOperand a -> DataType
forall a. Data a => CAssemblyOperand a -> Constr
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))
$cCAsmOperand :: Constr
$tCAssemblyOperand :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAssemblyOperand a -> m (CAssemblyOperand a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CAssemblyOperand a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAssemblyOperand a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAssemblyOperand a -> r
gmapT :: (forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAssemblyOperand a -> CAssemblyOperand a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAssemblyOperand a))
dataTypeOf :: CAssemblyOperand a -> DataType
$cdataTypeOf :: forall a. Data a => CAssemblyOperand a -> DataType
toConstr :: CAssemblyOperand a -> Constr
$ctoConstr :: forall a. Data a => CAssemblyOperand a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAssemblyOperand a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CAssemblyOperand a) x -> CAssemblyOperand a
$cfrom :: forall a x. CAssemblyOperand a -> Rep (CAssemblyOperand a) x
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
$cto1 :: forall a. Rep1 CAssemblyOperand a -> CAssemblyOperand a
$cfrom1 :: forall a. CAssemblyOperand a -> Rep1 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
showList :: [CCompoundBlockItem a] -> ShowS
$cshowList :: forall a. Show a => [CCompoundBlockItem a] -> ShowS
show :: CCompoundBlockItem a -> String
$cshow :: forall a. Show a => CCompoundBlockItem a -> String
showsPrec :: Int -> CCompoundBlockItem a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CCompoundBlockItem a -> ShowS
Show, Typeable (CCompoundBlockItem a)
DataType
Constr
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 -> DataType
CCompoundBlockItem a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
(forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> c (CCompoundBlockItem a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CCompoundBlockItem a)
forall a. Data a => Typeable (CCompoundBlockItem a)
forall a. Data a => CCompoundBlockItem a -> DataType
forall a. Data a => CCompoundBlockItem a -> Constr
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))
$cCNestedFunDef :: Constr
$cCBlockDecl :: Constr
$cCBlockStmt :: Constr
$tCCompoundBlockItem :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CCompoundBlockItem a -> m (CCompoundBlockItem a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CCompoundBlockItem a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CCompoundBlockItem a -> r
gmapT :: (forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CCompoundBlockItem a -> CCompoundBlockItem a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CCompoundBlockItem a))
dataTypeOf :: CCompoundBlockItem a -> DataType
$cdataTypeOf :: forall a. Data a => CCompoundBlockItem a -> DataType
toConstr :: CCompoundBlockItem a -> Constr
$ctoConstr :: forall a. Data a => CCompoundBlockItem a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CCompoundBlockItem a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CCompoundBlockItem a) x -> CCompoundBlockItem a
$cfrom :: forall a x. CCompoundBlockItem a -> Rep (CCompoundBlockItem a) x
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
$cto1 :: forall a. Rep1 CCompoundBlockItem a -> CCompoundBlockItem a
$cfrom1 :: forall a. CCompoundBlockItem a -> Rep1 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
showList :: [CDeclarationSpecifier a] -> ShowS
$cshowList :: forall a. Show a => [CDeclarationSpecifier a] -> ShowS
show :: CDeclarationSpecifier a -> String
$cshow :: forall a. Show a => CDeclarationSpecifier a -> String
showsPrec :: Int -> CDeclarationSpecifier a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CDeclarationSpecifier a -> ShowS
Show, Typeable (CDeclarationSpecifier a)
DataType
Constr
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 -> DataType
CDeclarationSpecifier a -> Constr
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
(forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> c (CDeclarationSpecifier a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CDeclarationSpecifier a)
forall a. Data a => Typeable (CDeclarationSpecifier a)
forall a. Data a => CDeclarationSpecifier a -> DataType
forall a. Data a => CDeclarationSpecifier a -> Constr
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))
$cCAlignSpec :: Constr
$cCFunSpec :: Constr
$cCTypeQual :: Constr
$cCTypeSpec :: Constr
$cCStorageSpec :: Constr
$tCDeclarationSpecifier :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CDeclarationSpecifier a -> m (CDeclarationSpecifier a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CDeclarationSpecifier a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CDeclarationSpecifier a
-> r
gmapT :: (forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CDeclarationSpecifier a -> CDeclarationSpecifier a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (CDeclarationSpecifier a))
dataTypeOf :: CDeclarationSpecifier a -> DataType
$cdataTypeOf :: forall a. Data a => CDeclarationSpecifier a -> DataType
toConstr :: CDeclarationSpecifier a -> Constr
$ctoConstr :: forall a. Data a => CDeclarationSpecifier a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CDeclarationSpecifier a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x.
Rep (CDeclarationSpecifier a) x -> CDeclarationSpecifier a
$cfrom :: forall a x.
CDeclarationSpecifier a -> Rep (CDeclarationSpecifier a) x
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
$cto1 :: forall a. Rep1 CDeclarationSpecifier a -> CDeclarationSpecifier a
$cfrom1 :: forall a. CDeclarationSpecifier a -> Rep1 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 :: [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 (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 sp :: CStorageSpecifier a
sp) (sts :: [CStorageSpecifier a]
sts,ats :: [CAttribute a]
ats,tqs :: [CTypeQualifier a]
tqs,tss :: [CTypeSpecifier a]
tss,fss :: [CFunctionSpecifier a]
fss,ass :: [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 attr :: CAttribute a
attr)) (sts :: [CStorageSpecifier a]
sts,ats :: [CAttribute a]
ats,tqs :: [CTypeQualifier a]
tqs,tss :: [CTypeSpecifier a]
tss,fss :: [CFunctionSpecifier a]
fss,ass :: [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 tq :: CTypeQualifier a
tq) (sts :: [CStorageSpecifier a]
sts,ats :: [CAttribute a]
ats,tqs :: [CTypeQualifier a]
tqs,tss :: [CTypeSpecifier a]
tss,fss :: [CFunctionSpecifier a]
fss,ass :: [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 ts :: CTypeSpecifier a
ts) (sts :: [CStorageSpecifier a]
sts,ats :: [CAttribute a]
ats,tqs :: [CTypeQualifier a]
tqs,tss :: [CTypeSpecifier a]
tss,fss :: [CFunctionSpecifier a]
fss,ass :: [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 fs :: CFunctionSpecifier a
fs) (sts :: [CStorageSpecifier a]
sts,ats :: [CAttribute a]
ats,tqs :: [CTypeQualifier a]
tqs,tss :: [CTypeSpecifier a]
tss,fss :: [CFunctionSpecifier a]
fss,ass :: [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 as :: CAlignmentSpecifier a
as) (sts :: [CStorageSpecifier a]
sts,ats :: [CAttribute a]
ats,tqs :: [CTypeQualifier a]
tqs,tss :: [CTypeSpecifier a]
tss,fss :: [CFunctionSpecifier a]
fss,ass :: [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
showList :: [CStorageSpecifier a] -> ShowS
$cshowList :: forall a. Show a => [CStorageSpecifier a] -> ShowS
show :: CStorageSpecifier a -> String
$cshow :: forall a. Show a => CStorageSpecifier a -> String
showsPrec :: Int -> CStorageSpecifier a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> 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
/= :: CStorageSpecifier a -> CStorageSpecifier a -> Bool
$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
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
min :: CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
$cmin :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
max :: CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
$cmax :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> CStorageSpecifier a
>= :: 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
$c< :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Bool
compare :: CStorageSpecifier a -> CStorageSpecifier a -> Ordering
$ccompare :: forall a.
Ord a =>
CStorageSpecifier a -> CStorageSpecifier a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (CStorageSpecifier a)
Ord,Typeable (CStorageSpecifier a)
DataType
Constr
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 -> DataType
CStorageSpecifier a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
(forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> c (CStorageSpecifier a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStorageSpecifier a)
forall a. Data a => Typeable (CStorageSpecifier a)
forall a. Data a => CStorageSpecifier a -> DataType
forall a. Data a => CStorageSpecifier a -> Constr
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))
$cCClLocal :: Constr
$cCClGlobal :: Constr
$cCClKernel :: Constr
$cCThread :: Constr
$cCTypedef :: Constr
$cCExtern :: Constr
$cCStatic :: Constr
$cCRegister :: Constr
$cCAuto :: Constr
$tCStorageSpecifier :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStorageSpecifier a -> m (CStorageSpecifier a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CStorageSpecifier a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStorageSpecifier a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStorageSpecifier a -> r
gmapT :: (forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStorageSpecifier a -> CStorageSpecifier a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStorageSpecifier a))
dataTypeOf :: CStorageSpecifier a -> DataType
$cdataTypeOf :: forall a. Data a => CStorageSpecifier a -> DataType
toConstr :: CStorageSpecifier a -> Constr
$ctoConstr :: forall a. Data a => CStorageSpecifier a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStorageSpecifier a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CStorageSpecifier a) x -> CStorageSpecifier a
$cfrom :: forall a x. CStorageSpecifier a -> Rep (CStorageSpecifier a) x
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
$cto1 :: forall a. Rep1 CStorageSpecifier a -> CStorageSpecifier a
$cfrom1 :: forall a. CStorageSpecifier a -> Rep1 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
| 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
showList :: [CTypeSpecifier a] -> ShowS
$cshowList :: forall a. Show a => [CTypeSpecifier a] -> ShowS
show :: CTypeSpecifier a -> String
$cshow :: forall a. Show a => CTypeSpecifier a -> String
showsPrec :: Int -> CTypeSpecifier a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CTypeSpecifier a -> ShowS
Show, Typeable (CTypeSpecifier a)
DataType
Constr
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 -> DataType
CTypeSpecifier a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
(forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeSpecifier a -> c (CTypeSpecifier a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeSpecifier a)
forall a. Data a => Typeable (CTypeSpecifier a)
forall a. Data a => CTypeSpecifier a -> DataType
forall a. Data a => CTypeSpecifier a -> Constr
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))
$cCAtomicType :: Constr
$cCTypeOfType :: Constr
$cCTypeOfExpr :: Constr
$cCTypeDef :: Constr
$cCEnumType :: Constr
$cCSUType :: Constr
$cCFloatNType :: Constr
$cCInt128Type :: Constr
$cCComplexType :: Constr
$cCBoolType :: Constr
$cCUnsigType :: Constr
$cCSignedType :: Constr
$cCDoubleType :: Constr
$cCFloatType :: Constr
$cCLongType :: Constr
$cCIntType :: Constr
$cCShortType :: Constr
$cCCharType :: Constr
$cCVoidType :: Constr
$tCTypeSpecifier :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTypeSpecifier a -> m (CTypeSpecifier a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CTypeSpecifier a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTypeSpecifier a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeSpecifier a -> r
gmapT :: (forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTypeSpecifier a -> CTypeSpecifier a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeSpecifier a))
dataTypeOf :: CTypeSpecifier a -> DataType
$cdataTypeOf :: forall a. Data a => CTypeSpecifier a -> DataType
toConstr :: CTypeSpecifier a -> Constr
$ctoConstr :: forall a. Data a => CTypeSpecifier a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeSpecifier a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CTypeSpecifier a) x -> CTypeSpecifier a
$cfrom :: forall a x. CTypeSpecifier a -> Rep (CTypeSpecifier a) x
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
$cto1 :: forall a. Rep1 CTypeSpecifier a -> CTypeSpecifier a
$cfrom1 :: forall a. CTypeSpecifier a -> Rep1 CTypeSpecifier a
Generic1 )
instance NFData a => NFData (CTypeSpecifier a)
isSUEDef :: CTypeSpecifier a -> Bool
isSUEDef :: CTypeSpecifier a -> Bool
isSUEDef (CSUType (CStruct _ _ (Just _) _ _) _) = Bool
True
isSUEDef (CEnumType (CEnum _ (Just _) _ _) _) = Bool
True
isSUEDef _ = 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
showList :: [CTypeQualifier a] -> ShowS
$cshowList :: forall a. Show a => [CTypeQualifier a] -> ShowS
show :: CTypeQualifier a -> String
$cshow :: forall a. Show a => CTypeQualifier a -> String
showsPrec :: Int -> CTypeQualifier a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CTypeQualifier a -> ShowS
Show, Typeable (CTypeQualifier a)
DataType
Constr
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 -> DataType
CTypeQualifier a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
(forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeQualifier a -> c (CTypeQualifier a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CTypeQualifier a)
forall a. Data a => Typeable (CTypeQualifier a)
forall a. Data a => CTypeQualifier a -> DataType
forall a. Data a => CTypeQualifier a -> Constr
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))
$cCClWrOnlyQual :: Constr
$cCClRdOnlyQual :: Constr
$cCNonnullQual :: Constr
$cCNullableQual :: Constr
$cCAttrQual :: Constr
$cCAtomicQual :: Constr
$cCRestrQual :: Constr
$cCVolatQual :: Constr
$cCConstQual :: Constr
$tCTypeQualifier :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CTypeQualifier a -> m (CTypeQualifier a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CTypeQualifier a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CTypeQualifier a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CTypeQualifier a -> r
gmapT :: (forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CTypeQualifier a -> CTypeQualifier a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CTypeQualifier a))
dataTypeOf :: CTypeQualifier a -> DataType
$cdataTypeOf :: forall a. Data a => CTypeQualifier a -> DataType
toConstr :: CTypeQualifier a -> Constr
$ctoConstr :: forall a. Data a => CTypeQualifier a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CTypeQualifier a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CTypeQualifier a) x -> CTypeQualifier a
$cfrom :: forall a x. CTypeQualifier a -> Rep (CTypeQualifier a) x
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
$cto1 :: forall a. Rep1 CTypeQualifier a -> CTypeQualifier a
$cfrom1 :: forall a. CTypeQualifier a -> Rep1 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
showList :: [CFunctionSpecifier a] -> ShowS
$cshowList :: forall a. Show a => [CFunctionSpecifier a] -> ShowS
show :: CFunctionSpecifier a -> String
$cshow :: forall a. Show a => CFunctionSpecifier a -> String
showsPrec :: Int -> CFunctionSpecifier a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CFunctionSpecifier a -> ShowS
Show, Typeable (CFunctionSpecifier a)
DataType
Constr
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 -> DataType
CFunctionSpecifier a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
(forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> c (CFunctionSpecifier a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CFunctionSpecifier a)
forall a. Data a => Typeable (CFunctionSpecifier a)
forall a. Data a => CFunctionSpecifier a -> DataType
forall a. Data a => CFunctionSpecifier a -> Constr
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))
$cCNoreturnQual :: Constr
$cCInlineQual :: Constr
$tCFunctionSpecifier :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CFunctionSpecifier a -> m (CFunctionSpecifier a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CFunctionSpecifier a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CFunctionSpecifier a -> r
gmapT :: (forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CFunctionSpecifier a -> CFunctionSpecifier a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CFunctionSpecifier a))
dataTypeOf :: CFunctionSpecifier a -> DataType
$cdataTypeOf :: forall a. Data a => CFunctionSpecifier a -> DataType
toConstr :: CFunctionSpecifier a -> Constr
$ctoConstr :: forall a. Data a => CFunctionSpecifier a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CFunctionSpecifier a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CFunctionSpecifier a) x -> CFunctionSpecifier a
$cfrom :: forall a x. CFunctionSpecifier a -> Rep (CFunctionSpecifier a) x
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
$cto1 :: forall a. Rep1 CFunctionSpecifier a -> CFunctionSpecifier a
$cfrom1 :: forall a. CFunctionSpecifier a -> Rep1 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
showList :: [CAlignmentSpecifier a] -> ShowS
$cshowList :: forall a. Show a => [CAlignmentSpecifier a] -> ShowS
show :: CAlignmentSpecifier a -> String
$cshow :: forall a. Show a => CAlignmentSpecifier a -> String
showsPrec :: Int -> CAlignmentSpecifier a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CAlignmentSpecifier a -> ShowS
Show, Typeable (CAlignmentSpecifier a)
DataType
Constr
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 -> DataType
CAlignmentSpecifier a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
(forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> c (CAlignmentSpecifier a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAlignmentSpecifier a)
forall a. Data a => Typeable (CAlignmentSpecifier a)
forall a. Data a => CAlignmentSpecifier a -> DataType
forall a. Data a => CAlignmentSpecifier a -> Constr
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))
$cCAlignAsExpr :: Constr
$cCAlignAsType :: Constr
$tCAlignmentSpecifier :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CAlignmentSpecifier a -> m (CAlignmentSpecifier a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAlignmentSpecifier a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAlignmentSpecifier a -> r
gmapT :: (forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CAlignmentSpecifier a -> CAlignmentSpecifier a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAlignmentSpecifier a))
dataTypeOf :: CAlignmentSpecifier a -> DataType
$cdataTypeOf :: forall a. Data a => CAlignmentSpecifier a -> DataType
toConstr :: CAlignmentSpecifier a -> Constr
$ctoConstr :: forall a. Data a => CAlignmentSpecifier a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CAlignmentSpecifier a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CAlignmentSpecifier a) x -> CAlignmentSpecifier a
$cfrom :: forall a x. CAlignmentSpecifier a -> Rep (CAlignmentSpecifier a) x
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
$cto1 :: forall a. Rep1 CAlignmentSpecifier a -> CAlignmentSpecifier a
$cfrom1 :: forall a. CAlignmentSpecifier a -> Rep1 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
showList :: [CStructureUnion a] -> ShowS
$cshowList :: forall a. Show a => [CStructureUnion a] -> ShowS
show :: CStructureUnion a -> String
$cshow :: forall a. Show a => CStructureUnion a -> String
showsPrec :: Int -> CStructureUnion a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CStructureUnion a -> ShowS
Show, Typeable (CStructureUnion a)
DataType
Constr
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 -> DataType
CStructureUnion a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
(forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> c (CStructureUnion a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStructureUnion a)
forall a. Data a => Typeable (CStructureUnion a)
forall a. Data a => CStructureUnion a -> DataType
forall a. Data a => CStructureUnion a -> Constr
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))
$cCStruct :: Constr
$tCStructureUnion :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStructureUnion a -> m (CStructureUnion a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CStructureUnion a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStructureUnion a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructureUnion a -> r
gmapT :: (forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStructureUnion a -> CStructureUnion a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStructureUnion a))
dataTypeOf :: CStructureUnion a -> DataType
$cdataTypeOf :: forall a. Data a => CStructureUnion a -> DataType
toConstr :: CStructureUnion a -> Constr
$ctoConstr :: forall a. Data a => CStructureUnion a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CStructureUnion a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CStructureUnion a) x -> CStructureUnion a
$cfrom :: forall a x. CStructureUnion a -> Rep (CStructureUnion a) x
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
$cto1 :: forall a. Rep1 CStructureUnion a -> CStructureUnion a
$cfrom1 :: forall a. CStructureUnion a -> Rep1 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
showList :: [CStructTag] -> ShowS
$cshowList :: [CStructTag] -> ShowS
show :: CStructTag -> String
$cshow :: CStructTag -> String
showsPrec :: Int -> CStructTag -> ShowS
$cshowsPrec :: Int -> CStructTag -> ShowS
Show, CStructTag -> CStructTag -> Bool
(CStructTag -> CStructTag -> Bool)
-> (CStructTag -> CStructTag -> Bool) -> Eq CStructTag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CStructTag -> CStructTag -> Bool
$c/= :: CStructTag -> CStructTag -> Bool
== :: CStructTag -> CStructTag -> Bool
$c== :: CStructTag -> CStructTag -> Bool
Eq,Typeable CStructTag
DataType
Constr
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 -> DataType
CStructTag -> Constr
(forall b. Data b => b -> b) -> CStructTag -> CStructTag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cCUnionTag :: Constr
$cCStructTag :: Constr
$tCStructTag :: DataType
gmapMo :: (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
gmapMp :: (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
gmapM :: (forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CStructTag -> m CStructTag
gmapQi :: Int -> (forall d. Data d => d -> u) -> CStructTag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CStructTag -> u
gmapQ :: (forall d. Data d => d -> u) -> CStructTag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CStructTag -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStructTag -> r
gmapT :: (forall b. Data b => b -> b) -> CStructTag -> CStructTag
$cgmapT :: (forall b. Data b => b -> b) -> CStructTag -> CStructTag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CStructTag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CStructTag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c CStructTag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CStructTag)
dataTypeOf :: CStructTag -> DataType
$cdataTypeOf :: CStructTag -> DataType
toConstr :: CStructTag -> Constr
$ctoConstr :: CStructTag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CStructTag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CStructTag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStructTag -> c CStructTag
$cp1Data :: Typeable 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
$cto :: forall x. Rep CStructTag x -> CStructTag
$cfrom :: forall x. CStructTag -> Rep CStructTag x
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
showList :: [CEnumeration a] -> ShowS
$cshowList :: forall a. Show a => [CEnumeration a] -> ShowS
show :: CEnumeration a -> String
$cshow :: forall a. Show a => CEnumeration a -> String
showsPrec :: Int -> CEnumeration a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CEnumeration a -> ShowS
Show, Typeable (CEnumeration a)
DataType
Constr
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 -> DataType
CEnumeration a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
(forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> c (CEnumeration a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CEnumeration a)
forall a. Data a => Typeable (CEnumeration a)
forall a. Data a => CEnumeration a -> DataType
forall a. Data a => CEnumeration a -> Constr
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))
$cCEnum :: Constr
$tCEnumeration :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CEnumeration a -> m (CEnumeration a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CEnumeration a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CEnumeration a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CEnumeration a -> r
gmapT :: (forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CEnumeration a -> CEnumeration a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CEnumeration a))
dataTypeOf :: CEnumeration a -> DataType
$cdataTypeOf :: forall a. Data a => CEnumeration a -> DataType
toConstr :: CEnumeration a -> Constr
$ctoConstr :: forall a. Data a => CEnumeration a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CEnumeration a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CEnumeration a) x -> CEnumeration a
$cfrom :: forall a x. CEnumeration a -> Rep (CEnumeration a) x
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
$cto1 :: forall a. Rep1 CEnumeration a -> CEnumeration a
$cfrom1 :: forall a. CEnumeration a -> Rep1 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
showList :: [CInitializer a] -> ShowS
$cshowList :: forall a. Show a => [CInitializer a] -> ShowS
show :: CInitializer a -> String
$cshow :: forall a. Show a => CInitializer a -> String
showsPrec :: Int -> CInitializer a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CInitializer a -> ShowS
Show, Typeable (CInitializer a)
DataType
Constr
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 -> DataType
CInitializer a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
(forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> c (CInitializer a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CInitializer a)
forall a. Data a => Typeable (CInitializer a)
forall a. Data a => CInitializer a -> DataType
forall a. Data a => CInitializer a -> Constr
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))
$cCInitList :: Constr
$cCInitExpr :: Constr
$tCInitializer :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CInitializer a -> m (CInitializer a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CInitializer a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CInitializer a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CInitializer a -> r
gmapT :: (forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CInitializer a -> CInitializer a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CInitializer a))
dataTypeOf :: CInitializer a -> DataType
$cdataTypeOf :: forall a. Data a => CInitializer a -> DataType
toConstr :: CInitializer a -> Constr
$ctoConstr :: forall a. Data a => CInitializer a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CInitializer a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CInitializer a) x -> CInitializer a
$cfrom :: forall a x. CInitializer a -> Rep (CInitializer a) x
Generic )
instance NFData a => NFData (CInitializer a)
instance Functor CInitializer where
fmap :: (a -> b) -> CInitializer a -> CInitializer b
fmap _f :: a -> b
_f (CInitExpr a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CInitializer b
forall a. CExpression a -> a -> CInitializer a
CInitExpr ((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 _f :: a -> b
_f (CInitList a1 :: CInitializerList a
a1 a2 :: 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 :: (a -> b) -> CInitializerList a -> CInitializerList b
fmapInitList _f :: a -> b
_f = (([CPartDesignator a], CInitializer a)
-> ([CPartDesignator b], CInitializer b))
-> CInitializerList a -> CInitializerList b
forall a b. (a -> b) -> [a] -> [b]
map (\(desigs :: [CPartDesignator a]
desigs, initializer :: CInitializer a
initializer) -> ((CPartDesignator a -> CPartDesignator b)
-> [CPartDesignator a] -> [CPartDesignator b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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
showList :: [CPartDesignator a] -> ShowS
$cshowList :: forall a. Show a => [CPartDesignator a] -> ShowS
show :: CPartDesignator a -> String
$cshow :: forall a. Show a => CPartDesignator a -> String
showsPrec :: Int -> CPartDesignator a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CPartDesignator a -> ShowS
Show, Typeable (CPartDesignator a)
DataType
Constr
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 -> DataType
CPartDesignator a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
(forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> c (CPartDesignator a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CPartDesignator a)
forall a. Data a => Typeable (CPartDesignator a)
forall a. Data a => CPartDesignator a -> DataType
forall a. Data a => CPartDesignator a -> Constr
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))
$cCRangeDesig :: Constr
$cCMemberDesig :: Constr
$cCArrDesig :: Constr
$tCPartDesignator :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CPartDesignator a -> m (CPartDesignator a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CPartDesignator a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CPartDesignator a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CPartDesignator a -> r
gmapT :: (forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CPartDesignator a -> CPartDesignator a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CPartDesignator a))
dataTypeOf :: CPartDesignator a -> DataType
$cdataTypeOf :: forall a. Data a => CPartDesignator a -> DataType
toConstr :: CPartDesignator a -> Constr
$ctoConstr :: forall a. Data a => CPartDesignator a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CPartDesignator a
-> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CPartDesignator a) x -> CPartDesignator a
$cfrom :: forall a x. CPartDesignator a -> Rep (CPartDesignator a) x
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
showList :: [CAttribute a] -> ShowS
$cshowList :: forall a. Show a => [CAttribute a] -> ShowS
show :: CAttribute a -> String
$cshow :: forall a. Show a => CAttribute a -> String
showsPrec :: Int -> CAttribute a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CAttribute a -> ShowS
Show, Typeable (CAttribute a)
DataType
Constr
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 -> DataType
CAttribute a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
(forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> c (CAttribute a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CAttribute a)
forall a. Data a => Typeable (CAttribute a)
forall a. Data a => CAttribute a -> DataType
forall a. Data a => CAttribute a -> Constr
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))
$cCAttr :: Constr
$tCAttribute :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CAttribute a -> m (CAttribute a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CAttribute a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CAttribute a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CAttribute a -> r
gmapT :: (forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CAttribute a -> CAttribute a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CAttribute a))
dataTypeOf :: CAttribute a -> DataType
$cdataTypeOf :: forall a. Data a => CAttribute a -> DataType
toConstr :: CAttribute a -> Constr
$ctoConstr :: forall a. Data a => CAttribute a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CAttribute a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CAttribute a) x -> CAttribute a
$cfrom :: forall a x. CAttribute a -> Rep (CAttribute a) x
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
$cto1 :: forall a. Rep1 CAttribute a -> CAttribute a
$cfrom1 :: forall a. CAttribute a -> Rep1 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)
DataType
Constr
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 -> DataType
CExpression a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
(forall b. Data b => b -> b) -> CExpression a -> CExpression a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> c (CExpression a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CExpression a)
forall a. Data a => Typeable (CExpression a)
forall a. Data a => CExpression a -> DataType
forall a. Data a => CExpression a -> Constr
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))
$cCBuiltinExpr :: Constr
$cCLabAddrExpr :: Constr
$cCStatExpr :: Constr
$cCGenericSelection :: Constr
$cCCompoundLit :: Constr
$cCConst :: Constr
$cCVar :: Constr
$cCMember :: Constr
$cCCall :: Constr
$cCIndex :: Constr
$cCComplexImag :: Constr
$cCComplexReal :: Constr
$cCAlignofType :: Constr
$cCAlignofExpr :: Constr
$cCSizeofType :: Constr
$cCSizeofExpr :: Constr
$cCUnary :: Constr
$cCCast :: Constr
$cCBinary :: Constr
$cCCond :: Constr
$cCAssign :: Constr
$cCComma :: Constr
$tCExpression :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CExpression a -> m (CExpression a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CExpression a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CExpression a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CExpression a -> r
gmapT :: (forall b. Data b => b -> b) -> CExpression a -> CExpression a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CExpression a -> CExpression a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CExpression a))
dataTypeOf :: CExpression a -> DataType
$cdataTypeOf :: forall a. Data a => CExpression a -> DataType
toConstr :: CExpression a -> Constr
$ctoConstr :: forall a. Data a => CExpression a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CExpression a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
showList :: [CExpression a] -> ShowS
$cshowList :: forall a. Show a => [CExpression a] -> ShowS
show :: CExpression a -> String
$cshow :: forall a. Show a => CExpression a -> String
showsPrec :: Int -> CExpression a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> 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
$cto :: forall a x. Rep (CExpression a) x -> CExpression a
$cfrom :: forall a x. CExpression a -> Rep (CExpression a) x
Generic )
instance NFData a => NFData (CExpression a)
instance Functor CExpression where
fmap :: (a -> b) -> CExpression a -> CExpression b
fmap _f :: a -> b
_f (CComma a1 :: [CExpression a]
a1 a2 :: a
a2) = [CExpression b] -> b -> CExpression b
forall a. [CExpression a] -> a -> CExpression a
CComma ((CExpression a -> CExpression b)
-> [CExpression a] -> [CExpression b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CAssign a1 :: CAssignOp
a1 a2 :: CExpression a
a2 a3 :: CExpression a
a3 a4 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
fmap _f :: a -> b
_f (CCond a1 :: CExpression a
a1 a2 :: Maybe (CExpression a)
a2 a3 :: CExpression a
a3 a4 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
fmap _f :: a -> b
_f (CBinary a1 :: CBinaryOp
a1 a2 :: CExpression a
a2 a3 :: CExpression a
a3 a4 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a3) (a -> b
_f a
a4)
fmap _f :: a -> b
_f (CCast a1 :: CDeclaration a
a1 a2 :: CExpression a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CUnary a1 :: CUnaryOp
a1 a2 :: CExpression a
a2 a3 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CSizeofExpr a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CSizeofExpr ((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 _f :: a -> b
_f (CSizeofType a1 :: CDeclaration a
a1 a2 :: a
a2) = CDeclaration b -> b -> CExpression b
forall a. CDeclaration a -> a -> CExpression a
CSizeofType ((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 _f :: a -> b
_f (CAlignofExpr a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CAlignofExpr ((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 _f :: a -> b
_f (CAlignofType a1 :: CDeclaration a
a1 a2 :: a
a2) = CDeclaration b -> b -> CExpression b
forall a. CDeclaration a -> a -> CExpression a
CAlignofType ((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 _f :: a -> b
_f (CComplexReal a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CComplexReal ((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 _f :: a -> b
_f (CComplexImag a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CExpression b
forall a. CExpression a -> a -> CExpression a
CComplexImag ((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 _f :: a -> b
_f (CIndex a1 :: CExpression a
a1 a2 :: CExpression a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CExpression a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CCall a1 :: CExpression a
a1 a2 :: [CExpression a]
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CMember a1 :: CExpression a
a1 a2 :: Ident
a2 a3 :: Bool
a3 a4 :: 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 (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 _f :: a -> b
_f (CVar a1 :: Ident
a1 a2 :: a
a2) = Ident -> b -> CExpression b
forall a. Ident -> a -> CExpression a
CVar Ident
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CConst a1 :: CConstant a
a1) = CConstant b -> CExpression b
forall a. CConstant a -> CExpression a
CConst ((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 _f :: a -> b
_f (CCompoundLit a1 :: CDeclaration a
a1 a2 :: CInitializerList a
a2 a3 :: 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 (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 _f :: a -> b
_f (CStatExpr a1 :: CStatement a
a1 a2 :: a
a2) = CStatement b -> b -> CExpression b
forall a. CStatement a -> a -> CExpression a
CStatExpr ((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 _f :: a -> b
_f (CLabAddrExpr a1 :: Ident
a1 a2 :: a
a2) = Ident -> b -> CExpression b
forall a. Ident -> a -> CExpression a
CLabAddrExpr Ident
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CBuiltinExpr a1 :: CBuiltinThing a
a1) = CBuiltinThing b -> CExpression b
forall a. CBuiltinThing a -> CExpression a
CBuiltinExpr ((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 _f :: a -> b
_f (CGenericSelection expr :: CExpression a
expr list :: [(Maybe (CDeclaration a), CExpression a)]
list annot :: 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 (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 (ma1 :: f (f a)
ma1, a2 :: f a
a2) = ((f a -> f b) -> f (f a) -> f (f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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
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
showList :: [CBuiltinThing a] -> ShowS
$cshowList :: forall a. Show a => [CBuiltinThing a] -> ShowS
show :: CBuiltinThing a -> String
$cshow :: forall a. Show a => CBuiltinThing a -> String
showsPrec :: Int -> CBuiltinThing a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CBuiltinThing a -> ShowS
Show, Typeable (CBuiltinThing a)
DataType
Constr
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 -> DataType
CBuiltinThing a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
(forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> c (CBuiltinThing a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CBuiltinThing a)
forall a. Data a => Typeable (CBuiltinThing a)
forall a. Data a => CBuiltinThing a -> DataType
forall a. Data a => CBuiltinThing a -> Constr
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))
$cCBuiltinConvertVector :: Constr
$cCBuiltinTypesCompatible :: Constr
$cCBuiltinOffsetOf :: Constr
$cCBuiltinVaArg :: Constr
$tCBuiltinThing :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CBuiltinThing a -> m (CBuiltinThing a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CBuiltinThing a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CBuiltinThing a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CBuiltinThing a -> r
gmapT :: (forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CBuiltinThing a -> CBuiltinThing a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CBuiltinThing a))
dataTypeOf :: CBuiltinThing a -> DataType
$cdataTypeOf :: forall a. Data a => CBuiltinThing a -> DataType
toConstr :: CBuiltinThing a -> Constr
$ctoConstr :: forall a. Data a => CBuiltinThing a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CBuiltinThing a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CBuiltinThing a) x -> CBuiltinThing a
$cfrom :: forall a x. CBuiltinThing a -> Rep (CBuiltinThing a) x
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
showList :: [CConstant a] -> ShowS
$cshowList :: forall a. Show a => [CConstant a] -> ShowS
show :: CConstant a -> String
$cshow :: forall a. Show a => CConstant a -> String
showsPrec :: Int -> CConstant a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CConstant a -> ShowS
Show, Typeable (CConstant a)
DataType
Constr
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 -> DataType
CConstant a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
(forall b. Data b => b -> b) -> CConstant a -> CConstant a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> c (CConstant a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CConstant a)
forall a. Data a => Typeable (CConstant a)
forall a. Data a => CConstant a -> DataType
forall a. Data a => CConstant a -> Constr
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))
$cCStrConst :: Constr
$cCFloatConst :: Constr
$cCCharConst :: Constr
$cCIntConst :: Constr
$tCConstant :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> CConstant a -> m (CConstant a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CConstant a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CConstant a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CConstant a -> r
gmapT :: (forall b. Data b => b -> b) -> CConstant a -> CConstant a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> CConstant a -> CConstant a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CConstant a))
dataTypeOf :: CConstant a -> DataType
$cdataTypeOf :: forall a. Data a => CConstant a -> DataType
toConstr :: CConstant a -> Constr
$ctoConstr :: forall a. Data a => CConstant a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CConstant a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CConstant a) x -> CConstant a
$cfrom :: forall a x. CConstant a -> Rep (CConstant a) x
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
$cto1 :: forall a. Rep1 CConstant a -> CConstant a
$cfrom1 :: forall a. CConstant a -> Rep1 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
showList :: [CStringLiteral a] -> ShowS
$cshowList :: forall a. Show a => [CStringLiteral a] -> ShowS
show :: CStringLiteral a -> String
$cshow :: forall a. Show a => CStringLiteral a -> String
showsPrec :: Int -> CStringLiteral a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CStringLiteral a -> ShowS
Show, Typeable (CStringLiteral a)
DataType
Constr
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 -> DataType
CStringLiteral a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
(forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStringLiteral a -> c (CStringLiteral a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CStringLiteral a)
forall a. Data a => Typeable (CStringLiteral a)
forall a. Data a => CStringLiteral a -> DataType
forall a. Data a => CStringLiteral a -> Constr
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))
$cCStrLit :: Constr
$tCStringLiteral :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CStringLiteral a -> m (CStringLiteral a)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> CStringLiteral a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> CStringLiteral a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CStringLiteral a -> r
gmapT :: (forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> CStringLiteral a -> CStringLiteral a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CStringLiteral a))
dataTypeOf :: CStringLiteral a -> DataType
$cdataTypeOf :: forall a. Data a => CStringLiteral a -> DataType
toConstr :: CStringLiteral a -> Constr
$ctoConstr :: forall a. Data a => CStringLiteral a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CStringLiteral a -> 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)
$cp1Data :: forall a. Data a => Typeable (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
$cto :: forall a x. Rep (CStringLiteral a) x -> CStringLiteral a
$cfrom :: forall a x. CStringLiteral a -> Rep (CStringLiteral a) x
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
$cto1 :: forall a. Rep1 CStringLiteral a -> CStringLiteral a
$cfrom1 :: forall a. CStringLiteral a -> Rep1 CStringLiteral a
Generic1 )
instance NFData a => NFData (CStringLiteral a)
cstringOfLit :: CStringLiteral a -> CString
cstringOfLit :: CStringLiteral a -> CString
cstringOfLit (CStrLit cstr :: CString
cstr _) = CString
cstr
liftStrLit :: CStringLiteral a -> CConstant a
liftStrLit :: CStringLiteral a -> CConstant a
liftStrLit (CStrLit str :: CString
str at :: 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 _ n :: 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 x :: 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 :: (a -> b) -> CTranslationUnit a -> CTranslationUnit b
fmap _f :: a -> b
_f (CTranslUnit a1 :: [CExternalDeclaration a]
a1 a2 :: a
a2)
= [CExternalDeclaration b] -> b -> CTranslationUnit b
forall a. [CExternalDeclaration a] -> a -> CTranslationUnit a
CTranslUnit ((CExternalDeclaration a -> CExternalDeclaration b)
-> [CExternalDeclaration a] -> [CExternalDeclaration b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 :: CTranslationUnit a -> a
annotation (CTranslUnit _ n :: a
n) = a
n
amap :: (a -> a) -> CTranslationUnit a -> CTranslationUnit a
amap f :: a -> a
f (CTranslUnit a_1 :: [CExternalDeclaration a]
a_1 a_2 :: 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 d :: CDeclaration t1
d) = CDeclaration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclaration t1
d
nodeInfo (CFDefExt d :: CFunctionDef t1
d) = CFunctionDef t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionDef t1
d
nodeInfo (CAsmExt _ n :: 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 x :: 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 :: (a -> b) -> CExternalDeclaration a -> CExternalDeclaration b
fmap _f :: a -> b
_f (CDeclExt a1 :: CDeclaration a
a1) = CDeclaration b -> CExternalDeclaration b
forall a. CDeclaration a -> CExternalDeclaration a
CDeclExt ((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 _f :: a -> b
_f (CFDefExt a1 :: CFunctionDef a
a1) = CFunctionDef b -> CExternalDeclaration b
forall a. CFunctionDef a -> CExternalDeclaration a
CFDefExt ((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 _f :: a -> b
_f (CAsmExt a1 :: CStringLiteral a
a1 a2 :: a
a2) = CStringLiteral b -> b -> CExternalDeclaration b
forall a. CStringLiteral a -> a -> CExternalDeclaration a
CAsmExt ((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 :: CExternalDeclaration a -> a
annotation (CDeclExt n :: CDeclaration a
n) = CDeclaration a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CDeclaration a
n
annotation (CFDefExt n :: CFunctionDef a
n) = CFunctionDef a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CFunctionDef a
n
annotation (CAsmExt _ n :: a
n) = a
n
amap :: (a -> a) -> CExternalDeclaration a -> CExternalDeclaration a
amap f :: a -> a
f (CDeclExt n :: CDeclaration a
n) = CDeclaration a -> CExternalDeclaration a
forall a. CDeclaration a -> CExternalDeclaration a
CDeclExt ((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 f :: a -> a
f (CFDefExt n :: CFunctionDef a
n) = CFunctionDef a -> CExternalDeclaration a
forall a. CFunctionDef a -> CExternalDeclaration a
CFDefExt ((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 f :: a -> a
f (CAsmExt a_1 :: CStringLiteral a
a_1 a_2 :: 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 _ _ _ _ n :: 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 x :: 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 :: (a -> b) -> CFunctionDef a -> CFunctionDef b
fmap _f :: a -> b
_f (CFunDef a1 :: [CDeclarationSpecifier a]
a1 a2 :: CDeclarator a
a2 a3 :: [CDeclaration a]
a3 a4 :: CStatement a
a4 a5 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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 :: CFunctionDef a -> a
annotation (CFunDef _ _ _ _ n :: a
n) = a
n
amap :: (a -> a) -> CFunctionDef a -> CFunctionDef a
amap f :: a -> a
f (CFunDef a_1 :: [CDeclarationSpecifier a]
a_1 a_2 :: CDeclarator a
a_2 a_3 :: [CDeclaration a]
a_3 a_4 :: CStatement a
a_4 a_5 :: 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 _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CStaticAssert _ _ n :: 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 x :: 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 :: CDeclaration a -> a
annotation (CDecl _ _ n :: a
n) = a
n
annotation (CStaticAssert _ _ n :: a
n) = a
n
amap :: (a -> a) -> CDeclaration a -> CDeclaration a
amap f :: a -> a
f (CDecl a_1 :: [CDeclarationSpecifier a]
a_1 a_2 :: [(Maybe (CDeclarator a), Maybe (CInitializer a),
Maybe (CExpression a))]
a_2 a_3 :: 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 f :: a -> a
f (CStaticAssert a_1 :: CExpression a
a_1 a_2 :: CStringLiteral a
a_2 a_3 :: 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 _ _ _ _ n :: 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 x :: 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 :: (a -> b) -> CDeclarator a -> CDeclarator b
fmap _f :: a -> b
_f (CDeclr a1 :: Maybe Ident
a1 a2 :: [CDerivedDeclarator a]
a2 a3 :: Maybe (CStringLiteral a)
a3 a4 :: [CAttribute a]
a4 a5 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 :: CDeclarator a -> a
annotation (CDeclr _ _ _ _ n :: a
n) = a
n
amap :: (a -> a) -> CDeclarator a -> CDeclarator a
amap f :: a -> a
f (CDeclr a_1 :: Maybe Ident
a_1 a_2 :: [CDerivedDeclarator a]
a_2 a_3 :: Maybe (CStringLiteral a)
a_3 a_4 :: [CAttribute a]
a_4 a_5 :: 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 _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CArrDeclr _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CFunDeclr _ _ n :: 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 x :: 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 :: CDerivedDeclarator a -> a
annotation (CPtrDeclr _ n :: a
n) = a
n
annotation (CArrDeclr _ _ n :: a
n) = a
n
annotation (CFunDeclr _ _ n :: a
n) = a
n
amap :: (a -> a) -> CDerivedDeclarator a -> CDerivedDeclarator a
amap f :: a -> a
f (CPtrDeclr a_1 :: [CTypeQualifier a]
a_1 a_2 :: 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 f :: a -> a
f (CArrDeclr a_1 :: [CTypeQualifier a]
a_1 a_2 :: CArraySize a
a_2 a_3 :: 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 f :: a -> a
f (CFunDeclr a_1 :: Either [Ident] ([CDeclaration a], Bool)
a_1 a_2 :: [CAttribute a]
a_2 a_3 :: 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 :: (a -> b) -> CArraySize a -> CArraySize b
fmap _ (CNoArrSize a1 :: Bool
a1) = Bool -> CArraySize b
forall a. Bool -> CArraySize a
CNoArrSize Bool
a1
fmap _f :: a -> b
_f (CArrSize a1 :: Bool
a1 a2 :: 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 (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 _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCase _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCases _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CDefault _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CExpr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCompound _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CIf _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CSwitch _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CWhile _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CFor _ _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CGoto _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CGotoPtr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCont d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CBreak d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CReturn _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAsm _ n :: 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 x :: 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 :: CStatement a -> a
annotation (CLabel _ _ _ n :: a
n) = a
n
annotation (CCase _ _ n :: a
n) = a
n
annotation (CCases _ _ _ n :: a
n) = a
n
annotation (CDefault _ n :: a
n) = a
n
annotation (CExpr _ n :: a
n) = a
n
annotation (CCompound _ _ n :: a
n) = a
n
annotation (CIf _ _ _ n :: a
n) = a
n
annotation (CSwitch _ _ n :: a
n) = a
n
annotation (CWhile _ _ _ n :: a
n) = a
n
annotation (CFor _ _ _ _ n :: a
n) = a
n
annotation (CGoto _ n :: a
n) = a
n
annotation (CGotoPtr _ n :: a
n) = a
n
annotation (CCont n :: a
n) = a
n
annotation (CBreak n :: a
n) = a
n
annotation (CReturn _ n :: a
n) = a
n
annotation (CAsm _ n :: a
n) = a
n
amap :: (a -> a) -> CStatement a -> CStatement a
amap f :: a -> a
f (CLabel a_1 :: Ident
a_1 a_2 :: CStatement a
a_2 a_3 :: [CAttribute a]
a_3 a_4 :: 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 f :: a -> a
f (CCase a_1 :: CExpression a
a_1 a_2 :: CStatement a
a_2 a_3 :: 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 f :: a -> a
f (CCases a_1 :: CExpression a
a_1 a_2 :: CExpression a
a_2 a_3 :: CStatement a
a_3 a_4 :: 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 f :: a -> a
f (CDefault a_1 :: CStatement a
a_1 a_2 :: 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 f :: a -> a
f (CExpr a_1 :: Maybe (CExpression a)
a_1 a_2 :: 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 f :: a -> a
f (CCompound a_1 :: [Ident]
a_1 a_2 :: [CCompoundBlockItem a]
a_2 a_3 :: 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 f :: a -> a
f (CIf a_1 :: CExpression a
a_1 a_2 :: CStatement a
a_2 a_3 :: Maybe (CStatement a)
a_3 a_4 :: 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 f :: a -> a
f (CSwitch a_1 :: CExpression a
a_1 a_2 :: CStatement a
a_2 a_3 :: 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 f :: a -> a
f (CWhile a_1 :: CExpression a
a_1 a_2 :: CStatement a
a_2 a_3 :: Bool
a_3 a_4 :: 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 f :: a -> a
f (CFor a_1 :: Either (Maybe (CExpression a)) (CDeclaration a)
a_1 a_2 :: Maybe (CExpression a)
a_2 a_3 :: Maybe (CExpression a)
a_3 a_4 :: CStatement a
a_4 a_5 :: 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 f :: a -> a
f (CGoto a_1 :: Ident
a_1 a_2 :: a
a_2) = Ident -> a -> CStatement a
forall a. Ident -> a -> CStatement a
CGoto Ident
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CGotoPtr a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CCont a_1 :: a
a_1) = a -> CStatement a
forall a. a -> CStatement a
CCont (a -> a
f a
a_1)
amap f :: a -> a
f (CBreak a_1 :: a
a_1) = a -> CStatement a
forall a. a -> CStatement a
CBreak (a -> a
f a
a_1)
amap f :: a -> a
f (CReturn a_1 :: Maybe (CExpression a)
a_1 a_2 :: 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 f :: a -> a
f (CAsm a_1 :: CAssemblyStatement a
a_1 a_2 :: 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 _ _ _ _ _ n :: 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 x :: 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 :: (a -> b) -> CAssemblyStatement a -> CAssemblyStatement b
fmap _f :: a -> b
_f (CAsmStmt a1 :: Maybe (CTypeQualifier a)
a1 a2 :: CStringLiteral a
a2 a3 :: [CAssemblyOperand a]
a3 a4 :: [CAssemblyOperand a]
a4 a5 :: [CStringLiteral a]
a5 a6 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 :: CAssemblyStatement a -> a
annotation (CAsmStmt _ _ _ _ _ n :: a
n) = a
n
amap :: (a -> a) -> CAssemblyStatement a -> CAssemblyStatement a
amap f :: a -> a
f (CAsmStmt a_1 :: Maybe (CTypeQualifier a)
a_1 a_2 :: CStringLiteral a
a_2 a_3 :: [CAssemblyOperand a]
a_3 a_4 :: [CAssemblyOperand a]
a_4 a_5 :: [CStringLiteral a]
a_5 a_6 :: 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 _ _ _ n :: 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 x :: 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 :: (a -> b) -> CAssemblyOperand a -> CAssemblyOperand b
fmap _f :: a -> b
_f (CAsmOperand a1 :: Maybe Ident
a1 a2 :: CStringLiteral a
a2 a3 :: CExpression a
a3 a4 :: 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 (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 (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 :: CAssemblyOperand a -> a
annotation (CAsmOperand _ _ _ n :: a
n) = a
n
amap :: (a -> a) -> CAssemblyOperand a -> CAssemblyOperand a
amap f :: a -> a
f (CAsmOperand a_1 :: Maybe Ident
a_1 a_2 :: CStringLiteral a
a_2 a_3 :: CExpression a
a_3 a_4 :: 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 d :: CStatement t1
d) = CStatement t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStatement t1
d
nodeInfo (CBlockDecl d :: CDeclaration t1
d) = CDeclaration t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CDeclaration t1
d
nodeInfo (CNestedFunDef d :: 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 x :: 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 :: (a -> b) -> CCompoundBlockItem a -> CCompoundBlockItem b
fmap _f :: a -> b
_f (CBlockStmt a1 :: CStatement a
a1) = CStatement b -> CCompoundBlockItem b
forall a. CStatement a -> CCompoundBlockItem a
CBlockStmt ((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 _f :: a -> b
_f (CBlockDecl a1 :: CDeclaration a
a1) = CDeclaration b -> CCompoundBlockItem b
forall a. CDeclaration a -> CCompoundBlockItem a
CBlockDecl ((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 _f :: a -> b
_f (CNestedFunDef a1 :: CFunctionDef a
a1) = CFunctionDef b -> CCompoundBlockItem b
forall a. CFunctionDef a -> CCompoundBlockItem a
CNestedFunDef ((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 :: CCompoundBlockItem a -> a
annotation (CBlockStmt n :: CStatement a
n) = CStatement a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CStatement a
n
annotation (CBlockDecl n :: CDeclaration a
n) = CDeclaration a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CDeclaration a
n
annotation (CNestedFunDef n :: CFunctionDef a
n) = CFunctionDef a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CFunctionDef a
n
amap :: (a -> a) -> CCompoundBlockItem a -> CCompoundBlockItem a
amap f :: a -> a
f (CBlockStmt n :: CStatement a
n) = CStatement a -> CCompoundBlockItem a
forall a. CStatement a -> CCompoundBlockItem a
CBlockStmt ((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 f :: a -> a
f (CBlockDecl n :: CDeclaration a
n) = CDeclaration a -> CCompoundBlockItem a
forall a. CDeclaration a -> CCompoundBlockItem a
CBlockDecl ((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 f :: a -> a
f (CNestedFunDef n :: CFunctionDef a
n) = CFunctionDef a -> CCompoundBlockItem a
forall a. CFunctionDef a -> CCompoundBlockItem a
CNestedFunDef ((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 d :: CStorageSpecifier t1
d) = CStorageSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CStorageSpecifier t1
d
nodeInfo (CTypeSpec d :: CTypeSpecifier t1
d) = CTypeSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTypeSpecifier t1
d
nodeInfo (CTypeQual d :: CTypeQualifier t1
d) = CTypeQualifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CTypeQualifier t1
d
nodeInfo (CFunSpec d :: CFunctionSpecifier t1
d) = CFunctionSpecifier t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CFunctionSpecifier t1
d
nodeInfo (CAlignSpec d :: 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 x :: 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 :: (a -> b) -> CDeclarationSpecifier a -> CDeclarationSpecifier b
fmap _f :: a -> b
_f (CStorageSpec a1 :: CStorageSpecifier a
a1) = CStorageSpecifier b -> CDeclarationSpecifier b
forall a. CStorageSpecifier a -> CDeclarationSpecifier a
CStorageSpec ((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 _f :: a -> b
_f (CTypeSpec a1 :: CTypeSpecifier a
a1) = CTypeSpecifier b -> CDeclarationSpecifier b
forall a. CTypeSpecifier a -> CDeclarationSpecifier a
CTypeSpec ((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 _f :: a -> b
_f (CTypeQual a1 :: CTypeQualifier a
a1) = CTypeQualifier b -> CDeclarationSpecifier b
forall a. CTypeQualifier a -> CDeclarationSpecifier a
CTypeQual ((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 _f :: a -> b
_f (CFunSpec a1 :: CFunctionSpecifier a
a1) = CFunctionSpecifier b -> CDeclarationSpecifier b
forall a. CFunctionSpecifier a -> CDeclarationSpecifier a
CFunSpec ((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 _f :: a -> b
_f (CAlignSpec a1 :: CAlignmentSpecifier a
a1) = CAlignmentSpecifier b -> CDeclarationSpecifier b
forall a. CAlignmentSpecifier a -> CDeclarationSpecifier a
CAlignSpec ((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 :: CDeclarationSpecifier a -> a
annotation (CStorageSpec n :: CStorageSpecifier a
n) = CStorageSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CStorageSpecifier a
n
annotation (CTypeSpec n :: CTypeSpecifier a
n) = CTypeSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CTypeSpecifier a
n
annotation (CTypeQual n :: CTypeQualifier a
n) = CTypeQualifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CTypeQualifier a
n
annotation (CFunSpec n :: CFunctionSpecifier a
n) = CFunctionSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CFunctionSpecifier a
n
annotation (CAlignSpec n :: CAlignmentSpecifier a
n) = CAlignmentSpecifier a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CAlignmentSpecifier a
n
amap :: (a -> a) -> CDeclarationSpecifier a -> CDeclarationSpecifier a
amap f :: a -> a
f (CStorageSpec n :: CStorageSpecifier a
n) = CStorageSpecifier a -> CDeclarationSpecifier a
forall a. CStorageSpecifier a -> CDeclarationSpecifier a
CStorageSpec ((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 f :: a -> a
f (CTypeSpec n :: CTypeSpecifier a
n) = CTypeSpecifier a -> CDeclarationSpecifier a
forall a. CTypeSpecifier a -> CDeclarationSpecifier a
CTypeSpec ((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 f :: a -> a
f (CTypeQual n :: CTypeQualifier a
n) = CTypeQualifier a -> CDeclarationSpecifier a
forall a. CTypeQualifier a -> CDeclarationSpecifier a
CTypeQual ((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 f :: a -> a
f (CFunSpec n :: CFunctionSpecifier a
n) = CFunctionSpecifier a -> CDeclarationSpecifier a
forall a. CFunctionSpecifier a -> CDeclarationSpecifier a
CFunSpec ((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 f :: a -> a
f (CAlignSpec n :: CAlignmentSpecifier a
n) = CAlignmentSpecifier a -> CDeclarationSpecifier a
forall a. CAlignmentSpecifier a -> CDeclarationSpecifier a
CAlignSpec ((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 d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CRegister d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CStatic d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CExtern d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CTypedef d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CThread d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClKernel d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClGlobal d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClLocal d :: 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 x :: 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 :: (a -> b) -> CStorageSpecifier a -> CStorageSpecifier b
fmap _f :: a -> b
_f (CAuto a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CAuto (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CRegister a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CRegister (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CStatic a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CStatic (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CExtern a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CExtern (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CTypedef a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CTypedef (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CThread a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CThread (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CClKernel a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CClKernel (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CClGlobal a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CClGlobal (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CClLocal a1 :: a
a1) = b -> CStorageSpecifier b
forall a. a -> CStorageSpecifier a
CClLocal (a -> b
_f a
a1)
instance Annotated CStorageSpecifier where
annotation :: CStorageSpecifier a -> a
annotation (CAuto n :: a
n) = a
n
annotation (CRegister n :: a
n) = a
n
annotation (CStatic n :: a
n) = a
n
annotation (CExtern n :: a
n) = a
n
annotation (CTypedef n :: a
n) = a
n
annotation (CThread n :: a
n) = a
n
annotation (CClKernel n :: a
n) = a
n
annotation (CClGlobal n :: a
n) = a
n
annotation (CClLocal n :: a
n) = a
n
amap :: (a -> a) -> CStorageSpecifier a -> CStorageSpecifier a
amap f :: a -> a
f (CAuto a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CAuto (a -> a
f a
a_1)
amap f :: a -> a
f (CRegister a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CRegister (a -> a
f a
a_1)
amap f :: a -> a
f (CStatic a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CStatic (a -> a
f a
a_1)
amap f :: a -> a
f (CExtern a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CExtern (a -> a
f a
a_1)
amap f :: a -> a
f (CTypedef a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CTypedef (a -> a
f a
a_1)
amap f :: a -> a
f (CThread a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CThread (a -> a
f a
a_1)
amap f :: a -> a
f (CClKernel a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CClKernel (a -> a
f a
a_1)
amap f :: a -> a
f (CClGlobal a_1 :: a
a_1) = a -> CStorageSpecifier a
forall a. a -> CStorageSpecifier a
CClGlobal (a -> a
f a
a_1)
amap f :: a -> a
f (CClLocal a_1 :: 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 d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CCharType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CShortType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CIntType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CLongType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CFloatType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CFloatNType _ _ d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CDoubleType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CSignedType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CUnsigType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CBoolType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CComplexType d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CInt128Type d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CSUType _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CEnumType _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CTypeDef _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CTypeOfExpr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CTypeOfType _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAtomicType _ n :: 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 x :: 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 :: (a -> b) -> CTypeSpecifier a -> CTypeSpecifier b
fmap _f :: a -> b
_f (CVoidType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CVoidType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CCharType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CCharType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CShortType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CShortType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CIntType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CIntType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CLongType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CLongType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CFloatType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CFloatType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CFloatNType n :: Int
n x :: Bool
x a1 :: 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 _f :: a -> b
_f (CDoubleType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CDoubleType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CSignedType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CSignedType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CUnsigType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CUnsigType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CBoolType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CBoolType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CComplexType a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CComplexType (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CInt128Type a1 :: a
a1) = b -> CTypeSpecifier b
forall a. a -> CTypeSpecifier a
CInt128Type (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CSUType a1 :: CStructureUnion a
a1 a2 :: a
a2) = CStructureUnion b -> b -> CTypeSpecifier b
forall a. CStructureUnion a -> a -> CTypeSpecifier a
CSUType ((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 _f :: a -> b
_f (CEnumType a1 :: CEnumeration a
a1 a2 :: a
a2) = CEnumeration b -> b -> CTypeSpecifier b
forall a. CEnumeration a -> a -> CTypeSpecifier a
CEnumType ((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 _f :: a -> b
_f (CTypeDef a1 :: Ident
a1 a2 :: a
a2) = Ident -> b -> CTypeSpecifier b
forall a. Ident -> a -> CTypeSpecifier a
CTypeDef Ident
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CTypeOfExpr a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CTypeSpecifier b
forall a. CExpression a -> a -> CTypeSpecifier a
CTypeOfExpr ((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 _f :: a -> b
_f (CTypeOfType a1 :: CDeclaration a
a1 a2 :: a
a2) = CDeclaration b -> b -> CTypeSpecifier b
forall a. CDeclaration a -> a -> CTypeSpecifier a
CTypeOfType ((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 _f :: a -> b
_f (CAtomicType a1 :: CDeclaration a
a1 a2 :: a
a2) = CDeclaration b -> b -> CTypeSpecifier b
forall a. CDeclaration a -> a -> CTypeSpecifier a
CAtomicType ((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 :: CTypeSpecifier a -> a
annotation (CVoidType n :: a
n) = a
n
annotation (CCharType n :: a
n) = a
n
annotation (CShortType n :: a
n) = a
n
annotation (CIntType n :: a
n) = a
n
annotation (CLongType n :: a
n) = a
n
annotation (CFloatType n :: a
n) = a
n
annotation (CFloatNType _ _ n :: a
n) = a
n
annotation (CDoubleType n :: a
n) = a
n
annotation (CSignedType n :: a
n) = a
n
annotation (CUnsigType n :: a
n) = a
n
annotation (CBoolType n :: a
n) = a
n
annotation (CComplexType n :: a
n) = a
n
annotation (CInt128Type n :: a
n) = a
n
annotation (CSUType _ n :: a
n) = a
n
annotation (CEnumType _ n :: a
n) = a
n
annotation (CTypeDef _ n :: a
n) = a
n
annotation (CTypeOfExpr _ n :: a
n) = a
n
annotation (CTypeOfType _ n :: a
n) = a
n
annotation (CAtomicType _ n :: a
n) = a
n
amap :: (a -> a) -> CTypeSpecifier a -> CTypeSpecifier a
amap f :: a -> a
f (CVoidType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CVoidType (a -> a
f a
a_1)
amap f :: a -> a
f (CCharType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CCharType (a -> a
f a
a_1)
amap f :: a -> a
f (CShortType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CShortType (a -> a
f a
a_1)
amap f :: a -> a
f (CIntType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CIntType (a -> a
f a
a_1)
amap f :: a -> a
f (CLongType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CLongType (a -> a
f a
a_1)
amap f :: a -> a
f (CFloatType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CFloatType (a -> a
f a
a_1)
amap f :: a -> a
f (CFloatNType n :: Int
n x :: Bool
x a_1 :: 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 f :: a -> a
f (CDoubleType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CDoubleType (a -> a
f a
a_1)
amap f :: a -> a
f (CSignedType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CSignedType (a -> a
f a
a_1)
amap f :: a -> a
f (CUnsigType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CUnsigType (a -> a
f a
a_1)
amap f :: a -> a
f (CBoolType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CBoolType (a -> a
f a
a_1)
amap f :: a -> a
f (CComplexType a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CComplexType (a -> a
f a
a_1)
amap f :: a -> a
f (CInt128Type a_1 :: a
a_1) = a -> CTypeSpecifier a
forall a. a -> CTypeSpecifier a
CInt128Type (a -> a
f a
a_1)
amap f :: a -> a
f (CSUType a_1 :: CStructureUnion a
a_1 a_2 :: 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 f :: a -> a
f (CEnumType a_1 :: CEnumeration a
a_1 a_2 :: 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 f :: a -> a
f (CTypeDef a_1 :: Ident
a_1 a_2 :: a
a_2) = Ident -> a -> CTypeSpecifier a
forall a. Ident -> a -> CTypeSpecifier a
CTypeDef Ident
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CTypeOfExpr a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CTypeOfType a_1 :: CDeclaration a
a_1 a_2 :: 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 f :: a -> a
f (CAtomicType a_1 :: CDeclaration a
a_1 a_2 :: 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 d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CVolatQual d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CRestrQual d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CAtomicQual d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CAttrQual d :: CAttribute t1
d) = CAttribute t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CAttribute t1
d
nodeInfo (CNullableQual d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CNonnullQual d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClRdOnlyQual d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CClWrOnlyQual d :: 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 x :: 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 :: (a -> b) -> CTypeQualifier a -> CTypeQualifier b
fmap _f :: a -> b
_f (CConstQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CConstQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CVolatQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CVolatQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CRestrQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CRestrQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CAtomicQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CAtomicQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CAttrQual a1 :: CAttribute a
a1) = CAttribute b -> CTypeQualifier b
forall a. CAttribute a -> CTypeQualifier a
CAttrQual ((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 _f :: a -> b
_f (CNullableQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CNullableQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CNonnullQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CNonnullQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CClRdOnlyQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CClRdOnlyQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CClWrOnlyQual a1 :: a
a1) = b -> CTypeQualifier b
forall a. a -> CTypeQualifier a
CClWrOnlyQual (a -> b
_f a
a1)
instance Annotated CTypeQualifier where
annotation :: CTypeQualifier a -> a
annotation (CConstQual n :: a
n) = a
n
annotation (CVolatQual n :: a
n) = a
n
annotation (CRestrQual n :: a
n) = a
n
annotation (CAtomicQual n :: a
n) = a
n
annotation (CAttrQual n :: CAttribute a
n) = CAttribute a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CAttribute a
n
annotation (CNullableQual n :: a
n) = a
n
annotation (CNonnullQual n :: a
n) = a
n
annotation (CClRdOnlyQual n :: a
n) = a
n
annotation (CClWrOnlyQual n :: a
n) = a
n
amap :: (a -> a) -> CTypeQualifier a -> CTypeQualifier a
amap f :: a -> a
f (CConstQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CConstQual (a -> a
f a
a_1)
amap f :: a -> a
f (CVolatQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CVolatQual (a -> a
f a
a_1)
amap f :: a -> a
f (CRestrQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CRestrQual (a -> a
f a
a_1)
amap f :: a -> a
f (CAtomicQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CAtomicQual (a -> a
f a
a_1)
amap f :: a -> a
f (CAttrQual n :: CAttribute a
n) = CAttribute a -> CTypeQualifier a
forall a. CAttribute a -> CTypeQualifier a
CAttrQual ((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 f :: a -> a
f (CNullableQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CNullableQual (a -> a
f a
a_1)
amap f :: a -> a
f (CNonnullQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CNonnullQual (a -> a
f a
a_1)
amap f :: a -> a
f (CClRdOnlyQual a_1 :: a
a_1) = a -> CTypeQualifier a
forall a. a -> CTypeQualifier a
CClRdOnlyQual (a -> a
f a
a_1)
amap f :: a -> a
f (CClWrOnlyQual a_1 :: 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 d :: t1
d) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
d
nodeInfo (CNoreturnQual d :: 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 x :: 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 :: (a -> b) -> CFunctionSpecifier a -> CFunctionSpecifier b
fmap _f :: a -> b
_f (CInlineQual a1 :: a
a1) = b -> CFunctionSpecifier b
forall a. a -> CFunctionSpecifier a
CInlineQual (a -> b
_f a
a1)
fmap _f :: a -> b
_f (CNoreturnQual a1 :: a
a1) = b -> CFunctionSpecifier b
forall a. a -> CFunctionSpecifier a
CNoreturnQual (a -> b
_f a
a1)
instance Annotated CFunctionSpecifier where
annotation :: CFunctionSpecifier a -> a
annotation (CInlineQual n :: a
n) = a
n
annotation (CNoreturnQual n :: a
n) = a
n
amap :: (a -> a) -> CFunctionSpecifier a -> CFunctionSpecifier a
amap f :: a -> a
f (CInlineQual a_1 :: a
a_1) = a -> CFunctionSpecifier a
forall a. a -> CFunctionSpecifier a
CInlineQual (a -> a
f a
a_1)
amap f :: a -> a
f (CNoreturnQual a_1 :: 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 _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAlignAsExpr _ n :: 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 x :: 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 :: (a -> b) -> CAlignmentSpecifier a -> CAlignmentSpecifier b
fmap _f :: a -> b
_f (CAlignAsType a1 :: CDeclaration a
a1 a2 :: a
a2) = CDeclaration b -> b -> CAlignmentSpecifier b
forall a. CDeclaration a -> a -> CAlignmentSpecifier a
CAlignAsType ((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 _f :: a -> b
_f (CAlignAsExpr a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CAlignmentSpecifier b
forall a. CExpression a -> a -> CAlignmentSpecifier a
CAlignAsExpr ((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 :: CAlignmentSpecifier a -> a
annotation (CAlignAsType _ n :: a
n) = a
n
annotation (CAlignAsExpr _ n :: a
n) = a
n
amap :: (a -> a) -> CAlignmentSpecifier a -> CAlignmentSpecifier a
amap f :: a -> a
f (CAlignAsType a_1 :: CDeclaration a
a_1 a_2 :: 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 f :: a -> a
f (CAlignAsExpr a_1 :: CExpression a
a_1 a_2 :: 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 _ _ _ _ n :: 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 x :: 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 :: (a -> b) -> CStructureUnion a -> CStructureUnion b
fmap _f :: a -> b
_f (CStruct a1 :: CStructTag
a1 a2 :: Maybe Ident
a2 a3 :: Maybe [CDeclaration a]
a3 a4 :: [CAttribute a]
a4 a5 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CDeclaration a -> CDeclaration b)
-> [CDeclaration a] -> [CDeclaration b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 :: CStructureUnion a -> a
annotation (CStruct _ _ _ _ n :: a
n) = a
n
amap :: (a -> a) -> CStructureUnion a -> CStructureUnion a
amap f :: a -> a
f (CStruct a_1 :: CStructTag
a_1 a_2 :: Maybe Ident
a_2 a_3 :: Maybe [CDeclaration a]
a_3 a_4 :: [CAttribute a]
a_4 a_5 :: 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 _ _ _ n :: 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 x :: 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 :: (a -> b) -> CEnumeration a -> CEnumeration b
fmap _f :: a -> b
_f (CEnum a1 :: Maybe Ident
a1 a2 :: Maybe [(Ident, Maybe (CExpression a))]
a2 a3 :: [CAttribute a]
a3 a4 :: 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 (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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CExpression a -> CExpression b)
-> Maybe (CExpression a) -> Maybe (CExpression b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 :: CEnumeration a -> a
annotation (CEnum _ _ _ n :: a
n) = a
n
amap :: (a -> a) -> CEnumeration a -> CEnumeration a
amap f :: a -> a
f (CEnum a_1 :: Maybe Ident
a_1 a_2 :: Maybe [(Ident, Maybe (CExpression a))]
a_2 a_3 :: [CAttribute a]
a_3 a_4 :: 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 _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CInitList _ n :: 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 x :: 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 :: CInitializer a -> a
annotation (CInitExpr _ n :: a
n) = a
n
annotation (CInitList _ n :: a
n) = a
n
amap :: (a -> a) -> CInitializer a -> CInitializer a
amap f :: a -> a
f (CInitExpr a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CInitList a_1 :: CInitializerList a
a_1 a_2 :: 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 _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CMemberDesig _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CRangeDesig _ _ n :: 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 x :: 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 :: (a -> b) -> CPartDesignator a -> CPartDesignator b
fmap _f :: a -> b
_f (CArrDesig a1 :: CExpression a
a1 a2 :: a
a2) = CExpression b -> b -> CPartDesignator b
forall a. CExpression a -> a -> CPartDesignator a
CArrDesig ((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 _f :: a -> b
_f (CMemberDesig a1 :: Ident
a1 a2 :: a
a2) = Ident -> b -> CPartDesignator b
forall a. Ident -> a -> CPartDesignator a
CMemberDesig Ident
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CRangeDesig a1 :: CExpression a
a1 a2 :: CExpression a
a2 a3 :: 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 (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 (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 :: CPartDesignator a -> a
annotation (CArrDesig _ n :: a
n) = a
n
annotation (CMemberDesig _ n :: a
n) = a
n
annotation (CRangeDesig _ _ n :: a
n) = a
n
amap :: (a -> a) -> CPartDesignator a -> CPartDesignator a
amap f :: a -> a
f (CArrDesig a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CMemberDesig a_1 :: Ident
a_1 a_2 :: a
a_2) = Ident -> a -> CPartDesignator a
forall a. Ident -> a -> CPartDesignator a
CMemberDesig Ident
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CRangeDesig a_1 :: CExpression a
a_1 a_2 :: CExpression a
a_2 a_3 :: 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 _ _ n :: 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 x :: 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 :: (a -> b) -> CAttribute a -> CAttribute b
fmap _f :: a -> b
_f (CAttr a1 :: Ident
a1 a2 :: [CExpression a]
a2 a3 :: 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 :: CAttribute a -> a
annotation (CAttr _ _ n :: a
n) = a
n
amap :: (a -> a) -> CAttribute a -> CAttribute a
amap f :: a -> a
f (CAttr a_1 :: Ident
a_1 a_2 :: [CExpression a]
a_2 a_3 :: 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 _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAssign _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCond _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBinary _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCast _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CUnary _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CSizeofExpr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CSizeofType _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAlignofExpr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CAlignofType _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CComplexReal _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CComplexImag _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CIndex _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCall _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CMember _ _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CVar _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CConst d :: CConstant t1
d) = CConstant t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo CConstant t1
d
nodeInfo (CCompoundLit _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CGenericSelection _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CStatExpr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CLabAddrExpr _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinExpr d :: 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 x :: 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 :: CExpression a -> a
annotation (CComma _ n :: a
n) = a
n
annotation (CAssign _ _ _ n :: a
n) = a
n
annotation (CCond _ _ _ n :: a
n) = a
n
annotation (CBinary _ _ _ n :: a
n) = a
n
annotation (CCast _ _ n :: a
n) = a
n
annotation (CUnary _ _ n :: a
n) = a
n
annotation (CSizeofExpr _ n :: a
n) = a
n
annotation (CSizeofType _ n :: a
n) = a
n
annotation (CAlignofExpr _ n :: a
n) = a
n
annotation (CAlignofType _ n :: a
n) = a
n
annotation (CComplexReal _ n :: a
n) = a
n
annotation (CComplexImag _ n :: a
n) = a
n
annotation (CIndex _ _ n :: a
n) = a
n
annotation (CCall _ _ n :: a
n) = a
n
annotation (CMember _ _ _ n :: a
n) = a
n
annotation (CVar _ n :: a
n) = a
n
annotation (CConst n :: CConstant a
n) = CConstant a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CConstant a
n
annotation (CCompoundLit _ _ n :: a
n) = a
n
annotation (CGenericSelection _ _ n :: a
n) = a
n
annotation (CStatExpr _ n :: a
n) = a
n
annotation (CLabAddrExpr _ n :: a
n) = a
n
annotation (CBuiltinExpr n :: CBuiltinThing a
n) = CBuiltinThing a -> a
forall (ast :: * -> *) a. Annotated ast => ast a -> a
annotation CBuiltinThing a
n
amap :: (a -> a) -> CExpression a -> CExpression a
amap f :: a -> a
f (CComma a_1 :: [CExpression a]
a_1 a_2 :: 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 f :: a -> a
f (CAssign a_1 :: CAssignOp
a_1 a_2 :: CExpression a
a_2 a_3 :: CExpression a
a_3 a_4 :: 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 f :: a -> a
f (CCond a_1 :: CExpression a
a_1 a_2 :: Maybe (CExpression a)
a_2 a_3 :: CExpression a
a_3 a_4 :: 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 f :: a -> a
f (CBinary a_1 :: CBinaryOp
a_1 a_2 :: CExpression a
a_2 a_3 :: CExpression a
a_3 a_4 :: 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 f :: a -> a
f (CCast a_1 :: CDeclaration a
a_1 a_2 :: CExpression a
a_2 a_3 :: 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 f :: a -> a
f (CUnary a_1 :: CUnaryOp
a_1 a_2 :: CExpression a
a_2 a_3 :: 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 f :: a -> a
f (CSizeofExpr a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CSizeofType a_1 :: CDeclaration a
a_1 a_2 :: 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 f :: a -> a
f (CAlignofExpr a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CAlignofType a_1 :: CDeclaration a
a_1 a_2 :: 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 f :: a -> a
f (CComplexReal a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CComplexImag a_1 :: CExpression a
a_1 a_2 :: 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 f :: a -> a
f (CIndex a_1 :: CExpression a
a_1 a_2 :: CExpression a
a_2 a_3 :: 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 f :: a -> a
f (CCall a_1 :: CExpression a
a_1 a_2 :: [CExpression a]
a_2 a_3 :: 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 f :: a -> a
f (CMember a_1 :: CExpression a
a_1 a_2 :: Ident
a_2 a_3 :: Bool
a_3 a_4 :: 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 f :: a -> a
f (CVar a_1 :: Ident
a_1 a_2 :: a
a_2) = Ident -> a -> CExpression a
forall a. Ident -> a -> CExpression a
CVar Ident
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CConst n :: CConstant a
n) = CConstant a -> CExpression a
forall a. CConstant a -> CExpression a
CConst ((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 f :: a -> a
f (CCompoundLit a_1 :: CDeclaration a
a_1 a_2 :: CInitializerList a
a_2 a_3 :: 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 f :: a -> a
f (CGenericSelection a_1 :: CExpression a
a_1 a_2 :: [(Maybe (CDeclaration a), CExpression a)]
a_2 a_3 :: 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 f :: a -> a
f (CStatExpr a_1 :: CStatement a
a_1 a_2 :: 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 f :: a -> a
f (CLabAddrExpr a_1 :: Ident
a_1 a_2 :: a
a_2) = Ident -> a -> CExpression a
forall a. Ident -> a -> CExpression a
CLabAddrExpr Ident
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CBuiltinExpr n :: CBuiltinThing a
n) = CBuiltinThing a -> CExpression a
forall a. CBuiltinThing a -> CExpression a
CBuiltinExpr ((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 _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinOffsetOf _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinTypesCompatible _ _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CBuiltinConvertVector _ _ n :: 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 x :: 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 :: (a -> b) -> CBuiltinThing a -> CBuiltinThing b
fmap _f :: a -> b
_f (CBuiltinVaArg a1 :: CExpression a
a1 a2 :: CDeclaration a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CBuiltinOffsetOf a1 :: CDeclaration a
a1 a2 :: [CPartDesignator a]
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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 _f :: a -> b
_f (CBuiltinTypesCompatible a1 :: CDeclaration a
a1 a2 :: CDeclaration a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a2) (a -> b
_f a
a3)
fmap _f :: a -> b
_f (CBuiltinConvertVector a1 :: CExpression a
a1 a2 :: CDeclaration a
a2 a3 :: 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
_f CDeclaration a
a2) (a -> b
_f a
a3)
instance Annotated CBuiltinThing where
annotation :: CBuiltinThing a -> a
annotation (CBuiltinVaArg _ _ n :: a
n) = a
n
annotation (CBuiltinOffsetOf _ _ n :: a
n) = a
n
annotation (CBuiltinTypesCompatible _ _ n :: a
n) = a
n
annotation (CBuiltinConvertVector _ _ n :: a
n) = a
n
amap :: (a -> a) -> CBuiltinThing a -> CBuiltinThing a
amap f :: a -> a
f (CBuiltinVaArg a_1 :: CExpression a
a_1 a_2 :: CDeclaration a
a_2 a_3 :: 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 f :: a -> a
f (CBuiltinOffsetOf a_1 :: CDeclaration a
a_1 a_2 :: [CPartDesignator a]
a_2 a_3 :: 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 f :: a -> a
f (CBuiltinTypesCompatible a_1 :: CDeclaration a
a_1 a_2 :: CDeclaration a
a_2 a_3 :: 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 f :: a -> a
f (CBuiltinConvertVector a_1 :: CExpression a
a_1 a_2 :: CDeclaration a
a_2 a_3 :: 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)
instance CNode t1 => CNode (CConstant t1) where
nodeInfo :: CConstant t1 -> NodeInfo
nodeInfo (CIntConst _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CCharConst _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CFloatConst _ n :: t1
n) = t1 -> NodeInfo
forall a. CNode a => a -> NodeInfo
nodeInfo t1
n
nodeInfo (CStrConst _ n :: 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 x :: 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 :: (a -> b) -> CConstant a -> CConstant b
fmap _f :: a -> b
_f (CIntConst a1 :: CInteger
a1 a2 :: a
a2) = CInteger -> b -> CConstant b
forall a. CInteger -> a -> CConstant a
CIntConst CInteger
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CCharConst a1 :: CChar
a1 a2 :: a
a2) = CChar -> b -> CConstant b
forall a. CChar -> a -> CConstant a
CCharConst CChar
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CFloatConst a1 :: CFloat
a1 a2 :: a
a2) = CFloat -> b -> CConstant b
forall a. CFloat -> a -> CConstant a
CFloatConst CFloat
a1 (a -> b
_f a
a2)
fmap _f :: a -> b
_f (CStrConst a1 :: CString
a1 a2 :: 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 :: CConstant a -> a
annotation (CIntConst _ n :: a
n) = a
n
annotation (CCharConst _ n :: a
n) = a
n
annotation (CFloatConst _ n :: a
n) = a
n
annotation (CStrConst _ n :: a
n) = a
n
amap :: (a -> a) -> CConstant a -> CConstant a
amap f :: a -> a
f (CIntConst a_1 :: CInteger
a_1 a_2 :: a
a_2) = CInteger -> a -> CConstant a
forall a. CInteger -> a -> CConstant a
CIntConst CInteger
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CCharConst a_1 :: CChar
a_1 a_2 :: a
a_2) = CChar -> a -> CConstant a
forall a. CChar -> a -> CConstant a
CCharConst CChar
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CFloatConst a_1 :: CFloat
a_1 a_2 :: a
a_2) = CFloat -> a -> CConstant a
forall a. CFloat -> a -> CConstant a
CFloatConst CFloat
a_1 (a -> a
f a
a_2)
amap f :: a -> a
f (CStrConst a_1 :: CString
a_1 a_2 :: 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 _ n :: 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 x :: 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 :: (a -> b) -> CStringLiteral a -> CStringLiteral b
fmap _f :: a -> b
_f (CStrLit a1 :: CString
a1 a2 :: 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 :: CStringLiteral a -> a
annotation (CStrLit _ n :: a
n) = a
n
amap :: (a -> a) -> CStringLiteral a -> CStringLiteral a
amap f :: a -> a
f (CStrLit a_1 :: CString
a_1 a_2 :: a
a_2) = CString -> a -> CStringLiteral a
forall a. CString -> a -> CStringLiteral a
CStrLit CString
a_1 (a -> a
f a
a_2)