{-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} module Language.C.Analysis.MachineDescs where import Language.C.Analysis.ConstEval import Language.C.Analysis.SemRep x86_64 :: MachineDesc x86_64 :: MachineDesc x86_64 = let iSize :: IntType -> Integer iSize = \case IntType TyBool -> Integer 1 IntType TyChar -> Integer 1 IntType TySChar -> Integer 1 IntType TyUChar -> Integer 1 IntType TyShort -> Integer 2 IntType TyUShort -> Integer 2 IntType TyInt -> Integer 4 IntType TyUInt -> Integer 4 IntType TyLong -> Integer 8 IntType TyULong -> Integer 8 IntType TyLLong -> Integer 8 IntType TyULLong -> Integer 8 IntType TyInt128 -> Integer 16 IntType TyUInt128 -> Integer 16 fSize :: FloatType -> Integer fSize = \case FloatType TyFloat -> Integer 4 FloatType TyDouble -> Integer 8 FloatType TyLDouble -> Integer 16 TyFloatN{} -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyFloatN" builtinSize :: BuiltinType -> Integer builtinSize = \case BuiltinType TyVaList -> Integer 24 BuiltinType TyAny -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyAny" ptrSize :: Integer ptrSize = Integer 8 voidSize :: Integer voidSize = Integer 1 iAlign :: IntType -> Integer iAlign = \case IntType TyBool -> Integer 1 IntType TyChar -> Integer 1 IntType TySChar -> Integer 1 IntType TyUChar -> Integer 1 IntType TyShort -> Integer 2 IntType TyUShort -> Integer 2 IntType TyInt -> Integer 4 IntType TyUInt -> Integer 4 IntType TyLong -> Integer 8 IntType TyULong -> Integer 8 IntType TyLLong -> Integer 8 IntType TyULLong -> Integer 8 IntType TyInt128 -> Integer 16 IntType TyUInt128 -> Integer 16 fAlign :: FloatType -> Integer fAlign = \case FloatType TyFloat -> Integer 4 FloatType TyDouble -> Integer 8 FloatType TyLDouble -> Integer 16 TyFloatN{} -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyFloatN" builtinAlign :: BuiltinType -> Integer builtinAlign = \case BuiltinType TyVaList -> Integer 8 BuiltinType TyAny -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyAny" ptrAlign :: Integer ptrAlign = Integer 8 voidAlign :: Integer voidAlign = Integer 1 in MachineDesc { Integer FloatType -> Integer IntType -> Integer BuiltinType -> Integer iSize :: IntType -> Integer fSize :: FloatType -> Integer builtinSize :: BuiltinType -> Integer ptrSize :: Integer voidSize :: Integer iAlign :: IntType -> Integer fAlign :: FloatType -> Integer builtinAlign :: BuiltinType -> Integer ptrAlign :: Integer voidAlign :: Integer iSize :: IntType -> Integer fSize :: FloatType -> Integer builtinSize :: BuiltinType -> Integer ptrSize :: Integer voidSize :: Integer iAlign :: IntType -> Integer fAlign :: FloatType -> Integer builtinAlign :: BuiltinType -> Integer ptrAlign :: Integer voidAlign :: Integer .. } armv7l :: MachineDesc armv7l :: MachineDesc armv7l = let iSize :: IntType -> Integer iSize = \case IntType TyBool -> Integer 1 IntType TyChar -> Integer 1 IntType TySChar -> Integer 1 IntType TyUChar -> Integer 1 IntType TyShort -> Integer 2 IntType TyUShort -> Integer 2 IntType TyInt -> Integer 4 IntType TyUInt -> Integer 4 IntType TyLong -> Integer 4 IntType TyULong -> Integer 4 IntType TyLLong -> Integer 8 IntType TyULLong -> Integer 8 IntType TyInt128 -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyInt128 on armv7l" IntType TyUInt128 -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyUInt128 on armv7l" fSize :: FloatType -> Integer fSize = \case FloatType TyFloat -> Integer 4 FloatType TyDouble -> Integer 8 FloatType TyLDouble -> Integer 8 TyFloatN{} -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyFloatN" builtinSize :: BuiltinType -> Integer builtinSize = \case BuiltinType TyVaList -> Integer 4 BuiltinType TyAny -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyAny" ptrSize :: Integer ptrSize = Integer 4 voidSize :: Integer voidSize = Integer 1 iAlign :: IntType -> Integer iAlign = \case IntType TyBool -> Integer 1 IntType TyChar -> Integer 1 IntType TySChar -> Integer 1 IntType TyUChar -> Integer 1 IntType TyShort -> Integer 2 IntType TyUShort -> Integer 2 IntType TyInt -> Integer 4 IntType TyUInt -> Integer 4 IntType TyLong -> Integer 4 IntType TyULong -> Integer 4 IntType TyLLong -> Integer 8 IntType TyULLong -> Integer 8 IntType TyInt128 -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyInt128 on armv7l" IntType TyUInt128 -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyUInt128 on armv7l" fAlign :: FloatType -> Integer fAlign = \case FloatType TyFloat -> Integer 4 FloatType TyDouble -> Integer 8 FloatType TyLDouble -> Integer 8 TyFloatN{} -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyFloatN" builtinAlign :: BuiltinType -> Integer builtinAlign = \case BuiltinType TyVaList -> Integer 4 BuiltinType TyAny -> [Char] -> Integer forall a. HasCallStack => [Char] -> a error [Char] "TyAny" ptrAlign :: Integer ptrAlign = Integer 4 voidAlign :: Integer voidAlign = Integer 1 in MachineDesc { Integer FloatType -> Integer IntType -> Integer BuiltinType -> Integer iSize :: IntType -> Integer fSize :: FloatType -> Integer builtinSize :: BuiltinType -> Integer ptrSize :: Integer voidSize :: Integer iAlign :: IntType -> Integer fAlign :: FloatType -> Integer builtinAlign :: BuiltinType -> Integer ptrAlign :: Integer voidAlign :: Integer iSize :: IntType -> Integer fSize :: FloatType -> Integer builtinSize :: BuiltinType -> Integer ptrSize :: Integer voidSize :: Integer iAlign :: IntType -> Integer fAlign :: FloatType -> Integer builtinAlign :: BuiltinType -> Integer ptrAlign :: Integer voidAlign :: Integer .. }