module Language.C.Analysis.Builtins (builtins) where
import Language.C.Analysis.DefTable
import Language.C.Analysis.SemRep
import Language.C.Analysis.TypeUtils
import Language.C.Data.Ident
import Language.C.Data.Node
builtins :: DefTable
builtins :: DefTable
builtins = (IdentDecl -> DefTable -> DefTable)
-> DefTable -> [IdentDecl] -> DefTable
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr IdentDecl -> DefTable -> DefTable
doIdent ((TypeDef -> DefTable -> DefTable)
-> DefTable -> [TypeDef] -> DefTable
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr TypeDef -> DefTable -> DefTable
doTypeDef DefTable
emptyDefTable [TypeDef]
typedefs) [IdentDecl]
idents
where doTypeDef :: TypeDef -> DefTable -> DefTable
doTypeDef TypeDef
d = (DeclarationStatus IdentEntry, DefTable) -> DefTable
forall a b. (a, b) -> b
snd ((DeclarationStatus IdentEntry, DefTable) -> DefTable)
-> (DefTable -> (DeclarationStatus IdentEntry, DefTable))
-> DefTable
-> DefTable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ident
-> TypeDef -> DefTable -> (DeclarationStatus IdentEntry, DefTable)
defineTypeDef (TypeDef -> Ident
identOfTypeDef TypeDef
d) TypeDef
d
doIdent :: IdentDecl -> DefTable -> DefTable
doIdent IdentDecl
d = (DeclarationStatus IdentEntry, DefTable) -> DefTable
forall a b. (a, b) -> b
snd ((DeclarationStatus IdentEntry, DefTable) -> DefTable)
-> (DefTable -> (DeclarationStatus IdentEntry, DefTable))
-> DefTable
-> DefTable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ident
-> IdentDecl
-> DefTable
-> (DeclarationStatus IdentEntry, DefTable)
defineGlobalIdent (IdentDecl -> Ident
forall n. Declaration n => n -> Ident
declIdent IdentDecl
d) IdentDecl
d
dName :: String -> VarName
dName String
s = Ident -> Maybe AsmName -> VarName
VarName (String -> Ident
builtinIdent String
s) Maybe AsmName
forall a. Maybe a
Nothing
param :: Type -> ParamDecl
param Type
ty = VarDecl -> NodeInfo -> ParamDecl
ParamDecl (VarName -> DeclAttrs -> Type -> VarDecl
VarDecl
VarName
NoName
(FunctionAttrs -> Storage -> Attributes -> DeclAttrs
DeclAttrs FunctionAttrs
noFunctionAttrs (Register -> Storage
Auto Register
False) [])
Type
ty) NodeInfo
undefNode
fnAttrs :: DeclAttrs
fnAttrs = FunctionAttrs -> Storage -> Attributes -> DeclAttrs
DeclAttrs FunctionAttrs
noFunctionAttrs (Linkage -> Storage
FunLinkage Linkage
ExternalLinkage) []
varAttrs :: DeclAttrs
varAttrs = FunctionAttrs -> Storage -> Attributes -> DeclAttrs
DeclAttrs FunctionAttrs
noFunctionAttrs (Linkage -> Register -> Storage
Static Linkage
InternalLinkage Register
False) []
fnType :: Type -> [Type] -> Type
fnType Type
r [Type]
as = FunType -> Attributes -> Type
FunctionType (Type -> [ParamDecl] -> Register -> FunType
FunType Type
r ((Type -> ParamDecl) -> [Type] -> [ParamDecl]
forall a b. (a -> b) -> [a] -> [b]
map Type -> ParamDecl
param [Type]
as) Register
False) Attributes
noAttributes
fnType' :: Type -> [Type] -> Type
fnType' Type
r [Type]
as = FunType -> Attributes -> Type
FunctionType (Type -> [ParamDecl] -> Register -> FunType
FunType Type
r ((Type -> ParamDecl) -> [Type] -> [ParamDecl]
forall a b. (a -> b) -> [a] -> [b]
map Type -> ParamDecl
param [Type]
as) Register
True) Attributes
noAttributes
func :: String -> Type -> [Type] -> IdentDecl
func String
n Type
r [Type]
as = Decl -> IdentDecl
Declaration
(VarDecl -> NodeInfo -> Decl
Decl
(VarName -> DeclAttrs -> Type -> VarDecl
VarDecl (String -> VarName
dName String
n) DeclAttrs
fnAttrs (Type -> [Type] -> Type
fnType Type
r [Type]
as))
NodeInfo
undefNode)
func' :: String -> Type -> [Type] -> IdentDecl
func' String
n Type
r [Type]
as = Decl -> IdentDecl
Declaration
(VarDecl -> NodeInfo -> Decl
Decl
(VarName -> DeclAttrs -> Type -> VarDecl
VarDecl (String -> VarName
dName String
n) DeclAttrs
fnAttrs (Type -> [Type] -> Type
fnType' Type
r [Type]
as))
NodeInfo
undefNode)
var :: String -> Type -> IdentDecl
var String
n Type
t = Decl -> IdentDecl
Declaration
(VarDecl -> NodeInfo -> Decl
Decl (VarName -> DeclAttrs -> Type -> VarDecl
VarDecl (String -> VarName
dName String
n) DeclAttrs
varAttrs Type
t) NodeInfo
undefNode)
typedef :: String -> Type -> TypeDef
typedef String
n Type
t = Ident -> Type -> Attributes -> NodeInfo -> TypeDef
TypeDef (String -> Ident
builtinIdent String
n) Type
t [] NodeInfo
undefNode
typedefs :: [TypeDef]
typedefs = [ String -> Type -> TypeDef
typedef String
"__builtin_va_list"
Type
valistType
]
idents :: [IdentDecl]
idents = [ String -> Type -> [Type] -> IdentDecl
func String
"__builtin_expect"
(IntType -> Type
integral IntType
TyLong)
[IntType -> Type
integral IntType
TyLong, IntType -> Type
integral IntType
TyLong]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_bswap16"
Type
uint16_tType
[Type
uint16_tType]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_bswap32"
Type
uint32_tType
[Type
uint32_tType]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_bswap64"
Type
uint64_tType
[Type
uint64_tType]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_fabs"
(FloatType -> Type
floating FloatType
TyDouble)
[FloatType -> Type
floating FloatType
TyDouble]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_fabsf"
(FloatType -> Type
floating FloatType
TyFloat)
[FloatType -> Type
floating FloatType
TyFloat]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_fabsl"
(FloatType -> Type
floating FloatType
TyLDouble)
[FloatType -> Type
floating FloatType
TyLDouble]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_inf" (FloatType -> Type
floating FloatType
TyDouble) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_inff" (FloatType -> Type
floating FloatType
TyFloat) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_infl" (FloatType -> Type
floating FloatType
TyLDouble) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_huge_val" (FloatType -> Type
floating FloatType
TyDouble) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_huge_valf" (FloatType -> Type
floating FloatType
TyFloat) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_huge_vall" (FloatType -> Type
floating FloatType
TyLDouble) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_copysign"
(FloatType -> Type
floating FloatType
TyDouble)
[ FloatType -> Type
floating FloatType
TyDouble, FloatType -> Type
floating FloatType
TyDouble ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_va_start"
Type
voidType
[ Type
valistType , Type
voidPtr ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_va_end"
Type
voidType
[Type
valistType]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_va_copy"
Type
voidType
[ Type
valistType, Type
valistType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_va_arg_pack" (IntType -> Type
integral IntType
TyInt) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_va_arg_pack_len" (IntType -> Type
integral IntType
TyInt) []
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_alloca"
Type
voidPtr
[ Type
size_tType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_memcpy"
Type
voidPtr
[ Type
voidPtr
, Type
constVoidPtr
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strspn"
Type
size_tType
[ Type
constCharPtr, Type
constCharPtr ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strcspn"
Type
size_tType
[ Type
constCharPtr, Type
constCharPtr ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strchr"
Type
charPtr
[ Type
constCharPtr, IntType -> Type
integral IntType
TyInt]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strncpy"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strncat"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strcmp"
(IntType -> Type
integral IntType
TyInt)
[ Type
constCharPtr, Type
constCharPtr ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_strpbrk"
Type
charPtr
[ Type
constCharPtr, Type
constCharPtr ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_bzero"
Type
voidType
[ Type
voidPtr, Type
size_tType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_clz"
(IntType -> Type
integral IntType
TyInt)
[ IntType -> Type
integral IntType
TyUInt ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_constant_p"
(IntType -> Type
integral IntType
TyInt)
[TypeName -> TypeQuals -> Attributes -> Type
DirectType (BuiltinType -> TypeName
TyBuiltin BuiltinType
TyAny) TypeQuals
noTypeQuals Attributes
noAttributes]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_extract_return_addr"
Type
voidPtr
[ Type
voidPtr ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_return_address"
Type
voidPtr
[ IntType -> Type
integral IntType
TyUInt ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_frame_address"
Type
voidPtr
[ IntType -> Type
integral IntType
TyUInt ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_expect"
(IntType -> Type
integral IntType
TyLong)
[ IntType -> Type
integral IntType
TyLong, IntType -> Type
integral IntType
TyLong ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_prefetch"
Type
voidType
[ Type
constVoidPtr ]
, String -> Type -> IdentDecl
var String
"__func__"
Type
stringType
, String -> Type -> IdentDecl
var String
"__PRETTY_FUNCTION__"
Type
stringType
, String -> Type -> IdentDecl
var String
"__FUNCTION__"
Type
stringType
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin_object_size"
Type
size_tType
[ Type
voidPtr, IntType -> Type
integral IntType
TyInt ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___memcpy_chk"
Type
voidPtr
[ Type
voidPtr, Type
constVoidPtr, Type
size_tType, Type
size_tType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___mempcpy_chk"
Type
voidPtr
[ Type
voidPtr, Type
constVoidPtr, Type
size_tType, Type
size_tType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___memmove_chk"
Type
voidPtr
[ Type
voidPtr, Type
constVoidPtr, Type
size_tType, Type
size_tType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___memset_chk"
Type
voidPtr
[ Type
voidPtr, IntType -> Type
integral IntType
TyInt, Type
size_tType, Type
size_tType ]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___strcpy_chk"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___stpcpy_chk"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___strncpy_chk"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___strcat_chk"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___strncat_chk"
Type
charPtr
[ Type
constCharPtr
, Type
constCharPtr
, Type
size_tType
, Type
size_tType
]
, String -> Type -> [Type] -> IdentDecl
func' String
"__builtin___sprintf_chk"
(IntType -> Type
integral IntType
TyInt)
[ Type
charPtr
, IntType -> Type
integral IntType
TyInt
, Type
size_tType
, Type
constCharPtr
]
, String -> Type -> [Type] -> IdentDecl
func' String
"__builtin___snprintf_chk"
(IntType -> Type
integral IntType
TyInt)
[ Type
charPtr
, Type
size_tType
, IntType -> Type
integral IntType
TyInt
, Type
size_tType
, Type
constCharPtr
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___vsprintf_chk"
(IntType -> Type
integral IntType
TyInt)
[ Type
charPtr
, IntType -> Type
integral IntType
TyInt
, Type
size_tType
, Type
constCharPtr
, Type
valistType
]
, String -> Type -> [Type] -> IdentDecl
func String
"__builtin___vsnprintf_chk"
(IntType -> Type
integral IntType
TyInt)
[ Type
charPtr
, Type
size_tType
, IntType -> Type
integral IntType
TyInt
, Type
size_tType
, Type
constCharPtr
, Type
valistType
]
]