Skip to content
Snippets Groups Projects
Commit 1d788f7f authored by chrg's avatar chrg
Browse files

Add support of gcc __vector_size__

parent 5c35709f
No related branches found
No related tags found
No related merge requests found
Showing
with 13225 additions and 133 deletions
......@@ -26,21 +26,52 @@ module ReduceC (
prettyIdent,
) where
import Control.Applicative
import Control.Monad
import Control.Applicative (Alternative (empty, (<|>)))
import Control.Monad (
MonadPlus (mzero),
foldM,
forM,
forM_,
guard,
join,
mapAndUnzipM,
unless,
void,
when,
)
import qualified Control.Monad.IRTree as IRTree
import Control.Monad.Reduce
import Control.Monad.State
import Control.Monad.Trans.Maybe
import Data.Function
import Data.Functor
import Control.Monad.Reduce (
MonadReduce (split),
collect,
exceptIf,
liftMaybe,
)
import Control.Monad.State (
MonadState (get, state),
MonadTrans (lift),
State,
StateT (runStateT),
evalState,
evalStateT,
gets,
modify',
runState,
)
import Control.Monad.Trans.Maybe (MaybeT (runMaybeT))
import Data.Function ((&))
import Data.Functor (($>), (<&>))
import qualified Data.List as List
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map.Strict as Map
import Data.Maybe
import Data.Maybe (
catMaybes,
fromMaybe,
isJust,
isNothing,
mapMaybe,
)
import qualified Data.Set as Set
import Data.Vector.Internal.Check (HasCallStack)
import Debug.Pretty.Simple
import qualified Language.C as C
import qualified Language.C.Data.Ident as C
import qualified Language.C.Data.Node as C
......@@ -53,11 +84,11 @@ defaultReduceC :: (MonadReduce (String, C.Position) m) => C.CTranslUnit -> m C.C
defaultReduceC a = reduceCTranslUnit a defaultContext
{-# SPECIALIZE defaultReduceC :: C.CTranslUnit -> IRTree.IRTree (String, C.Position) C.CTranslUnit #-}
reduceCTranslUnit
:: (MonadReduce Lab m)
=> C.CTranslationUnit C.NodeInfo
-> Context
-> m (C.CTranslationUnit C.NodeInfo)
reduceCTranslUnit ::
(MonadReduce Lab m) =>
C.CTranslationUnit C.NodeInfo ->
Context ->
m (C.CTranslationUnit C.NodeInfo)
reduceCTranslUnit (C.CTranslUnit es ni) ctx = do
let _functions = foldMap (findFunctions (: [])) es
......@@ -111,6 +142,7 @@ reduceCTranslUnit (C.CTranslUnit es ni) ctx = do
let builtins =
[ ("fabsf", FunType (NonVoid TNum) (Params [Just TNum] False))
, ("fabs", FunType (NonVoid TNum) (Params [Just TNum] False))
, ("__builtin_abort", FunType Void (Params [] False))
]
let functions''' =
......@@ -153,24 +185,24 @@ keepAll = SpecifierFilter{sfKeepStatic = True}
{- | Update the CDeclarationSpecifier's to match the context. Specifically, update
the typedefs and the structs. Alos return a base type.
-}
updateCDeclarationSpecifiers
:: ( MonadState Context m
, MonadPlus m
)
=> SpecifierFilter
-> [C.CDeclarationSpecifier C.NodeInfo]
-> m (Voidable, [C.CDeclarationSpecifier C.NodeInfo])
updateCDeclarationSpecifiers ::
( MonadState Context m
, MonadPlus m
) =>
SpecifierFilter ->
[C.CDeclarationSpecifier C.NodeInfo] ->
m (Voidable, [C.CDeclarationSpecifier C.NodeInfo])
updateCDeclarationSpecifiers sf spec = do
ctx <- get
spec' <- concat <$> mapM (updateSpec ctx) spec
bt <- baseType ctx spec'
pure (bt, spec')
where
baseType
:: (MonadPlus m)
=> Context
-> [C.CDeclarationSpecifier C.NodeInfo]
-> m Voidable
baseType ::
(MonadPlus m) =>
Context ->
[C.CDeclarationSpecifier C.NodeInfo] ->
m Voidable
baseType ctx =
liftMaybe
. exactlyOne
......@@ -305,23 +337,23 @@ updateCDeclarationSpecifiers sf spec = do
a' -> notSupportedYet' a'
pure $ catMaybes declrs'
updateCDerivedDeclarators
:: forall m
. ( MonadState Context m
, MonadPlus m
)
=> Voidable
-> [Bool]
-> [C.CDerivedDeclarator C.NodeInfo]
-> m (Voidable, [C.CDerivedDeclarator C.NodeInfo])
updateCDerivedDeclarators ::
forall m.
( MonadState Context m
, MonadPlus m
) =>
Voidable ->
[Bool] ->
[C.CDerivedDeclarator C.NodeInfo] ->
m (Voidable, [C.CDerivedDeclarator C.NodeInfo])
updateCDerivedDeclarators bt ff dd = do
foldM applyDD (bt, []) (reverse dd)
where
applyDD
:: (r ~ (Voidable, [C.CDerivedDeclarator C.NodeInfo]))
=> r
-> C.CDerivedDeclarator C.NodeInfo
-> m r
applyDD ::
(r ~ (Voidable, [C.CDerivedDeclarator C.NodeInfo])) =>
r ->
C.CDerivedDeclarator C.NodeInfo ->
m r
applyDD (t, dd') d = case d of
C.CPtrDeclr _ _ -> do
pure (NonVoid . TPointer $ t, d : dd')
......@@ -335,10 +367,10 @@ updateCDerivedDeclarators bt ff dd = do
pure (t', C.CFunDeclr (C.CFunParamsNew params'' varadic) arr ni : dd')
b -> notSupportedYet b ni
findParams
:: Bool
-> [C.CDeclaration C.NodeInfo]
-> State Context (Params, [C.CDeclaration C.NodeInfo])
findParams ::
Bool ->
[C.CDeclaration C.NodeInfo] ->
State Context (Params, [C.CDeclaration C.NodeInfo])
findParams varadic decls = case decls of
[C.CDecl [C.CTypeSpec (C.CVoidType _)] [] _] ->
pure (VoidParams, decls)
......@@ -374,10 +406,10 @@ updateCDerivedDeclarators bt ff dd = do
Nothing -> (Nothing, [])
pure (Params ts varadic, concat decls')
reduceCExternalDeclaration
:: (HasCallStack, MonadReduce Lab m)
=> C.CExternalDeclaration C.NodeInfo
-> StateT Context m (Maybe (C.CExternalDeclaration C.NodeInfo))
reduceCExternalDeclaration ::
(HasCallStack, MonadReduce Lab m) =>
C.CExternalDeclaration C.NodeInfo ->
StateT Context m (Maybe (C.CExternalDeclaration C.NodeInfo))
reduceCExternalDeclaration r = case r of
C.CFDefExt (C.CFunDef spec declr [] stmt ni) -> runMaybeT do
ctx <- get
......@@ -419,9 +451,21 @@ reduceCExternalDeclaration r = case r of
-- Type definitions
C.CDeclExt (C.CDecl (C.CStorageSpec (C.CTypedef nif) : rst) [item] ni) -> runMaybeT do
(ix, dd) <- case item of
C.CDeclarationItem (C.CDeclr (Just ix) dd Nothing _ _) Nothing Nothing ->
pure (ix, dd)
(ix, dd, wrap) <- case item of
C.CDeclarationItem (C.CDeclr (Just ix) dd Nothing extras _) Nothing Nothing ->
case extras of
[] -> pure (ix, dd, id)
[C.CAttr (C.Ident "__vector_size__" _ _) [a] _] -> do
case a of
C.CBinary C.CMulOp (C.CConst (C.CIntConst (C.CInteger n _ _) _)) (C.CSizeofType _ _) _ ->
-- todo assuming this is a checked size
pure
( ix
, dd
, NonVoid . TVector (fromInteger n)
)
_ -> notSupportedYet a ni
a -> notSupportedYet (map void a) ni
i -> notSupportedYet (void i) ni
modify' (addTypeDef ix ITDelete)
......@@ -432,10 +476,10 @@ reduceCExternalDeclaration r = case r of
(t, _) <- updateCDerivedDeclarators bt (repeat True) dd
unless keep do
modify' (addTypeDef ix (ITInline t rst'))
modify' (addTypeDef ix (ITInline (wrap t) rst'))
exceptIf ("inline typedef " <> C.identToString ix, C.posOf ni)
modify' (addTypeDef ix (ITKeep t))
modify' (addTypeDef ix (ITKeep (wrap t)))
pure $ C.CDeclExt $ C.CDecl (C.CStorageSpec (C.CTypedef nif) : rst') [item] ni
-- The rest.
......@@ -499,13 +543,13 @@ isStaticFromSpecs = any \case
{- | This checks the current declaration and reduces any new struct found here.
Returns true if the specifier is requried.
-}
reduceStructDeclaration
:: ( MonadReduce Lab m
, MonadState Context m
, MonadPlus m
)
=> [C.CDeclarationSpecifier C.NodeInfo]
-> m Bool
reduceStructDeclaration ::
( MonadReduce Lab m
, MonadState Context m
, MonadPlus m
) =>
[C.CDeclarationSpecifier C.NodeInfo] ->
m Bool
reduceStructDeclaration =
fmap or . mapM \case
C.CTypeSpec (C.CEnumType (C.CEnum mid mf _ _) ni) -> do
......@@ -583,14 +627,14 @@ reduceStructDeclaration =
)
a@(C.CStaticAssert{}) -> notSupportedYet' a
reduceCDeclarationItem
:: ( MonadReduce Lab m
, MonadState Context m
, MonadPlus m
)
=> Voidable
-> C.CDeclarationItem C.NodeInfo
-> m (C.CDeclarationItem C.NodeInfo)
reduceCDeclarationItem ::
( MonadReduce Lab m
, MonadState Context m
, MonadPlus m
) =>
Voidable ->
C.CDeclarationItem C.NodeInfo ->
m (C.CDeclarationItem C.NodeInfo)
reduceCDeclarationItem bt = \case
di@(C.CDeclarationItem (C.CDeclr mid dd Nothing [] ni) einit Nothing) -> do
ctx <- get
......@@ -622,22 +666,37 @@ reduceCDeclarationItem bt = \case
pure di
a -> notSupportedYet a C.undefNode
reduceCInitializer
:: (MonadReduce Lab m)
=> Type
-> C.CInitializer C.NodeInfo
-> Context
-> m (C.CInitializer C.NodeInfo, Maybe C.CExpr)
reduceCInitializer ::
(MonadReduce Lab m) =>
Type ->
C.CInitializer C.NodeInfo ->
Context ->
m (C.CInitializer C.NodeInfo, Maybe C.CExpr)
reduceCInitializer t einit ctx = case einit of
C.CInitExpr e ni2 -> do
e' <- fromMaybe (pure zeroExpr) $ reduceCExpr e (exactly t) ctx
pure
( C.CInitExpr e' ni2
, case e' of
C.CConst _ -> Just e'
C.CVar _ _ -> Just e'
_ow -> Nothing
)
let me = reduceCExpr e (exactly t) ctx
case (me, t) of
(Just es, _) -> do
e' <- es
pure
( C.CInitExpr e' ni2
, case e' of
C.CConst _ -> Just e'
C.CVar _ _ -> Just e'
_ow -> Nothing
)
(Nothing, TVector n _) -> do
let items' = [([], C.CInitExpr zeroExpr ni2) | _ <- replicate n ()]
pure (C.CInitList (C.CInitializerList items') ni2, Nothing)
(Nothing, _) -> do
let e' = zeroExpr
pure
( C.CInitExpr e' ni2
, case e' of
C.CConst _ -> Just e'
C.CVar _ _ -> Just e'
_ow -> Nothing
)
C.CInitList (C.CInitializerList items) ni2 -> do
items' <- case t of
TStruct stct -> do
......@@ -655,11 +714,11 @@ reduceCInitializer t einit ctx = case einit of
pure items
pure (C.CInitList (C.CInitializerList items') ni2, Nothing)
reduceCCompoundBlockItem
:: (MonadReduce Lab m, HasCallStack)
=> StmtContext
-> C.CCompoundBlockItem C.NodeInfo
-> StateT Context m [C.CCompoundBlockItem C.NodeInfo]
reduceCCompoundBlockItem ::
(MonadReduce Lab m, HasCallStack) =>
StmtContext ->
C.CCompoundBlockItem C.NodeInfo ->
StateT Context m [C.CCompoundBlockItem C.NodeInfo]
reduceCCompoundBlockItem lab r = do
case r of
C.CBlockStmt smt -> do
......@@ -701,24 +760,24 @@ markDeleted = mapM_ \case
modify' (addInlineExpr ix IEDelete)
_a -> pure ()
reduceCStatementOrEmptyBlock
:: (MonadReduce Lab m, HasCallStack)
=> C.CStatement C.NodeInfo
-> StmtContext
-> Context
-> m (C.CStatement C.NodeInfo)
reduceCStatementOrEmptyBlock ::
(MonadReduce Lab m, HasCallStack) =>
C.CStatement C.NodeInfo ->
StmtContext ->
Context ->
m (C.CStatement C.NodeInfo)
reduceCStatementOrEmptyBlock stmt ids ctx = do
fromMaybe emptyBlock
<$> runMaybeT
( wrapCCompound <$> reduceCStatement stmt ids ctx
)
reduceCStatementOrEmptyExpr
:: (MonadReduce Lab m, HasCallStack)
=> C.CStatement C.NodeInfo
-> StmtContext
-> Context
-> m (C.CStatement C.NodeInfo)
reduceCStatementOrEmptyExpr ::
(MonadReduce Lab m, HasCallStack) =>
C.CStatement C.NodeInfo ->
StmtContext ->
Context ->
m (C.CStatement C.NodeInfo)
reduceCStatementOrEmptyExpr stmt ids ctx = do
fromMaybe (C.CExpr Nothing C.undefNode)
<$> runMaybeT (reduceCStatement stmt ids ctx)
......@@ -742,13 +801,13 @@ exactly :: Type -> EType
exactly c = EType (ETExactly c) False
-- | Reduce given a list of required labels reduce a c statement, possibly into nothingness.
reduceCStatement
:: forall m
. (MonadReduce Lab m, HasCallStack)
=> C.CStatement C.NodeInfo
-> StmtContext
-> Context
-> MaybeT m (C.CStatement C.NodeInfo)
reduceCStatement ::
forall m.
(MonadReduce Lab m, HasCallStack) =>
C.CStatement C.NodeInfo ->
StmtContext ->
Context ->
MaybeT m (C.CStatement C.NodeInfo)
reduceCStatement smt labs ctx = case smt of
C.CCompound is cbi ni -> do
cbi' <- lift $ evalStateT (mapM (reduceCCompoundBlockItem labs) cbi) ctx
......@@ -920,6 +979,7 @@ data ETSet
= ETExactly !Type
| ETStructWithField !C.Ident !ETSet
| ETPointer !ETSet
| ETIndexable !ETSet
| ETAny
deriving (Show, Eq)
......@@ -954,12 +1014,19 @@ isExpectedType ctx = \c et ->
TPointer Void -> True
TPointer (NonVoid c') -> go c' t'
_ow -> False
ETIndexable t' ->
case c of
TPointer Void -> True
TPointer (NonVoid c') -> go c' t'
TVector _ (NonVoid c') -> go c' t'
TVector _ Void -> True
_ow -> False
fieldsOfStruct :: (HasCallStack) => Context -> Either C.Ident StructType -> [(C.Ident, Maybe Type)]
fieldsOfStruct ctx (Left ix) =
case lookupStruct ctx ix of
ISKeep a -> structTypeFields a
_ow -> error ("Something bad happend")
_ow -> error "Something bad happend"
fieldsOfStruct _ (Right a) = structTypeFields a
etUnPointer :: EType -> Maybe EType
......@@ -1009,7 +1076,8 @@ inferType ctx = \case
t2 <- inferType ctx x
case (t1, t2) of
(NonVoid (TPointer x'), NonVoid TNum) -> pure x'
_ow -> error (show ("index", t1, t2))
(NonVoid (TVector _ x'), NonVoid TNum) -> pure x'
_ow -> error (show ("index", a, t1, t2))
C.CMember a l t _ -> do
t1 <- inferType ctx a
s' <- case (t1, t) of
......@@ -1046,13 +1114,13 @@ inferType ctx = \case
inferType ctx (List.last items)
a -> notSupportedYet' a
reduceCExpr
:: forall m
. (MonadReduce Lab m, HasCallStack)
=> C.CExpr
-> EType
-> Context
-> Maybe (m C.CExpr)
reduceCExpr ::
forall m.
(MonadReduce Lab m, HasCallStack) =>
C.CExpr ->
EType ->
Context ->
Maybe (m C.CExpr)
reduceCExpr expr t ctx = case expr of
C.CBinary o elhs erhs ni -> do
msplit ("reduce to left", C.posOf elhs) (reduceCExpr elhs t ctx) do
......@@ -1121,13 +1189,16 @@ reduceCExpr expr t ctx = case expr of
msplit ("reduce to operant", C.posOf eopr) (reduceCExpr eopr t ctx) do
case o of
C.CIndOp -> do
ropr <- reduceCExpr eopr (t{etSet = ETPointer (etSet t), etAssignable = True}) ctx
ropr <-
if etSet t == ETAny
then do
reduceCExpr eopr t ctx
else reduceCExpr eopr (t{etSet = ETPointer (etSet t), etAssignable = True}) ctx
Just do
eopr' <- ropr
pure $ C.CUnary o eopr' ni
C.CAdrOp -> do
t' <- etUnPointer t
-- pTraceShowM (t', void eopr)
ropr <- reduceCExpr eopr (t'{etAssignable = True}) ctx
Just do
eopr' <- ropr
......@@ -1204,12 +1275,10 @@ reduceCExpr expr t ctx = case expr of
C.CIndex e1 e2 ni -> do
msplit ("reduce to indexee", C.posOf e1) (reduceCExpr e1 t ctx) do
msplit ("reduce to index", C.posOf e2) (reduceCExpr e2 t ctx) do
re1 <- reduceCExpr e1 t{etSet = ETPointer (etSet t), etAssignable = True} ctx
re1 <- reduceCExpr e1 t{etSet = ETIndexable (etSet t), etAssignable = True} ctx
Just do
e1' <- re1
e2' <-
fromMaybe (pure zeroExpr) $
reduceCExpr e2 etNum ctx
e2' <- fromMaybe (pure zeroExpr) $ reduceCExpr e2 etNum ctx
pure $ C.CIndex e1' e2' ni
C.CComma items ni -> do
(x, rst) <- List.uncons (reverse items)
......@@ -1365,11 +1434,11 @@ data Function = Function
}
deriving (Show, Eq)
findFunctions
:: (Monoid m)
=> (Function -> m)
-> C.CExternalDeclaration C.NodeInfo
-> m
findFunctions ::
(Monoid m) =>
(Function -> m) ->
C.CExternalDeclaration C.NodeInfo ->
m
findFunctions inject = \case
C.CFDefExt (C.CFunDef spec declr [] _ ni) ->
findFunctionsInDeclarator ni spec declr
......@@ -1436,6 +1505,7 @@ data Type
= TNum
| TStruct !(Either C.Ident StructType)
| TPointer !Voidable
| TVector !Int !Voidable
| TFun !FunType
deriving (Show, Eq)
......
typedef long long llong;
typedef char vchar64 __attribute__((__vector_size__(64 * sizeof(char))));
__attribute__((noinline, noclone)) vchar64 test1char64(char c) {
vchar64 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vchar64 test2char64(char *p) {
char c = *p;
vchar64 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3char64(void) {
char c = 17;
int i;
vchar64 a = test1char64(c);
for (i = 0; i < 64; i++)
if (a[i] != 17)
__builtin_abort();
vchar64 b = test2char64(&c);
for (i = 0; i < 64; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef char vchar32 __attribute__((__vector_size__(32 * sizeof(char))));
__attribute__((noinline, noclone)) vchar32 test1char32(char c) {
vchar32 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vchar32 test2char32(char *p) {
char c = *p;
vchar32 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3char32(void) {
char c = 17;
int i;
vchar32 a = test1char32(c);
for (i = 0; i < 32; i++)
if (a[i] != 17)
__builtin_abort();
vchar32 b = test2char32(&c);
for (i = 0; i < 32; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef char vchar16 __attribute__((__vector_size__(16 * sizeof(char))));
__attribute__((noinline, noclone)) vchar16 test1char16(char c) {
vchar16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vchar16 test2char16(char *p) {
char c = *p;
vchar16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3char16(void) {
char c = 17;
int i;
vchar16 a = test1char16(c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
vchar16 b = test2char16(&c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef char vchar8 __attribute__((__vector_size__(8 * sizeof(char))));
__attribute__((noinline, noclone)) vchar8 test1char8(char c) {
vchar8 v = {c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vchar8 test2char8(char *p) {
char c = *p;
vchar8 v = {c, c, c, c, c, c, c, c};
return v;
}
void test3char8(void) {
char c = 17;
int i;
vchar8 a = test1char8(c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
vchar8 b = test2char8(&c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef char vchar4 __attribute__((__vector_size__(4 * sizeof(char))));
__attribute__((noinline, noclone)) vchar4 test1char4(char c) {
vchar4 v = {c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vchar4 test2char4(char *p) {
char c = *p;
vchar4 v = {c, c, c, c};
return v;
}
void test3char4(void) {
char c = 17;
int i;
vchar4 a = test1char4(c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
vchar4 b = test2char4(&c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef char vchar2 __attribute__((__vector_size__(2 * sizeof(char))));
__attribute__((noinline, noclone)) vchar2 test1char2(char c) {
vchar2 v = {c, c};
return v;
}
__attribute__((noinline, noclone)) vchar2 test2char2(char *p) {
char c = *p;
vchar2 v = {c, c};
return v;
}
void test3char2(void) {
char c = 17;
int i;
vchar2 a = test1char2(c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
vchar2 b = test2char2(&c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef char vchar1 __attribute__((__vector_size__(1 * sizeof(char))));
__attribute__((noinline, noclone)) vchar1 test1char1(char c) {
vchar1 v = {c};
return v;
}
__attribute__((noinline, noclone)) vchar1 test2char1(char *p) {
char c = *p;
vchar1 v = {c};
return v;
}
void test3char1(void) {
char c = 17;
int i;
vchar1 a = test1char1(c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
vchar1 b = test2char1(&c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef short vshort32 __attribute__((__vector_size__(32 * sizeof(short))));
__attribute__((noinline, noclone)) vshort32 test1short32(short c) {
vshort32 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vshort32 test2short32(short *p) {
short c = *p;
vshort32 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c,
c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3short32(void) {
short c = 17;
int i;
vshort32 a = test1short32(c);
for (i = 0; i < 32; i++)
if (a[i] != 17)
__builtin_abort();
vshort32 b = test2short32(&c);
for (i = 0; i < 32; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef short vshort16 __attribute__((__vector_size__(16 * sizeof(short))));
__attribute__((noinline, noclone)) vshort16 test1short16(short c) {
vshort16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vshort16 test2short16(short *p) {
short c = *p;
vshort16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3short16(void) {
short c = 17;
int i;
vshort16 a = test1short16(c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
vshort16 b = test2short16(&c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef short vshort8 __attribute__((__vector_size__(8 * sizeof(short))));
__attribute__((noinline, noclone)) vshort8 test1short8(short c) {
vshort8 v = {c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vshort8 test2short8(short *p) {
short c = *p;
vshort8 v = {c, c, c, c, c, c, c, c};
return v;
}
void test3short8(void) {
short c = 17;
int i;
vshort8 a = test1short8(c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
vshort8 b = test2short8(&c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef short vshort4 __attribute__((__vector_size__(4 * sizeof(short))));
__attribute__((noinline, noclone)) vshort4 test1short4(short c) {
vshort4 v = {c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vshort4 test2short4(short *p) {
short c = *p;
vshort4 v = {c, c, c, c};
return v;
}
void test3short4(void) {
short c = 17;
int i;
vshort4 a = test1short4(c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
vshort4 b = test2short4(&c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef short vshort2 __attribute__((__vector_size__(2 * sizeof(short))));
__attribute__((noinline, noclone)) vshort2 test1short2(short c) {
vshort2 v = {c, c};
return v;
}
__attribute__((noinline, noclone)) vshort2 test2short2(short *p) {
short c = *p;
vshort2 v = {c, c};
return v;
}
void test3short2(void) {
short c = 17;
int i;
vshort2 a = test1short2(c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
vshort2 b = test2short2(&c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef short vshort1 __attribute__((__vector_size__(1 * sizeof(short))));
__attribute__((noinline, noclone)) vshort1 test1short1(short c) {
vshort1 v = {c};
return v;
}
__attribute__((noinline, noclone)) vshort1 test2short1(short *p) {
short c = *p;
vshort1 v = {c};
return v;
}
void test3short1(void) {
short c = 17;
int i;
vshort1 a = test1short1(c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
vshort1 b = test2short1(&c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef int vint16 __attribute__((__vector_size__(16 * sizeof(int))));
__attribute__((noinline, noclone)) vint16 test1int16(int c) {
vint16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vint16 test2int16(int *p) {
int c = *p;
vint16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3int16(void) {
int c = 17;
int i;
vint16 a = test1int16(c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
vint16 b = test2int16(&c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef int vint8 __attribute__((__vector_size__(8 * sizeof(int))));
__attribute__((noinline, noclone)) vint8 test1int8(int c) {
vint8 v = {c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vint8 test2int8(int *p) {
int c = *p;
vint8 v = {c, c, c, c, c, c, c, c};
return v;
}
void test3int8(void) {
int c = 17;
int i;
vint8 a = test1int8(c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
vint8 b = test2int8(&c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef int vint4 __attribute__((__vector_size__(4 * sizeof(int))));
__attribute__((noinline, noclone)) vint4 test1int4(int c) {
vint4 v = {c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vint4 test2int4(int *p) {
int c = *p;
vint4 v = {c, c, c, c};
return v;
}
void test3int4(void) {
int c = 17;
int i;
vint4 a = test1int4(c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
vint4 b = test2int4(&c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef int vint2 __attribute__((__vector_size__(2 * sizeof(int))));
__attribute__((noinline, noclone)) vint2 test1int2(int c) {
vint2 v = {c, c};
return v;
}
__attribute__((noinline, noclone)) vint2 test2int2(int *p) {
int c = *p;
vint2 v = {c, c};
return v;
}
void test3int2(void) {
int c = 17;
int i;
vint2 a = test1int2(c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
vint2 b = test2int2(&c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef int vint1 __attribute__((__vector_size__(1 * sizeof(int))));
__attribute__((noinline, noclone)) vint1 test1int1(int c) {
vint1 v = {c};
return v;
}
__attribute__((noinline, noclone)) vint1 test2int1(int *p) {
int c = *p;
vint1 v = {c};
return v;
}
void test3int1(void) {
int c = 17;
int i;
vint1 a = test1int1(c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
vint1 b = test2int1(&c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef float vfloat16 __attribute__((__vector_size__(16 * sizeof(float))));
__attribute__((noinline, noclone)) vfloat16 test1float16(float c) {
vfloat16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vfloat16 test2float16(float *p) {
float c = *p;
vfloat16 v = {c, c, c, c, c, c, c, c, c, c, c, c, c, c, c, c};
return v;
}
void test3float16(void) {
float c = 17;
int i;
vfloat16 a = test1float16(c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
vfloat16 b = test2float16(&c);
for (i = 0; i < 16; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef float vfloat8 __attribute__((__vector_size__(8 * sizeof(float))));
__attribute__((noinline, noclone)) vfloat8 test1float8(float c) {
vfloat8 v = {c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vfloat8 test2float8(float *p) {
float c = *p;
vfloat8 v = {c, c, c, c, c, c, c, c};
return v;
}
void test3float8(void) {
float c = 17;
int i;
vfloat8 a = test1float8(c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
vfloat8 b = test2float8(&c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef float vfloat4 __attribute__((__vector_size__(4 * sizeof(float))));
__attribute__((noinline, noclone)) vfloat4 test1float4(float c) {
vfloat4 v = {c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vfloat4 test2float4(float *p) {
float c = *p;
vfloat4 v = {c, c, c, c};
return v;
}
void test3float4(void) {
float c = 17;
int i;
vfloat4 a = test1float4(c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
vfloat4 b = test2float4(&c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef float vfloat2 __attribute__((__vector_size__(2 * sizeof(float))));
__attribute__((noinline, noclone)) vfloat2 test1float2(float c) {
vfloat2 v = {c, c};
return v;
}
__attribute__((noinline, noclone)) vfloat2 test2float2(float *p) {
float c = *p;
vfloat2 v = {c, c};
return v;
}
void test3float2(void) {
float c = 17;
int i;
vfloat2 a = test1float2(c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
vfloat2 b = test2float2(&c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef float vfloat1 __attribute__((__vector_size__(1 * sizeof(float))));
__attribute__((noinline, noclone)) vfloat1 test1float1(float c) {
vfloat1 v = {c};
return v;
}
__attribute__((noinline, noclone)) vfloat1 test2float1(float *p) {
float c = *p;
vfloat1 v = {c};
return v;
}
void test3float1(void) {
float c = 17;
int i;
vfloat1 a = test1float1(c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
vfloat1 b = test2float1(&c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef llong vllong8 __attribute__((__vector_size__(8 * sizeof(llong))));
__attribute__((noinline, noclone)) vllong8 test1llong8(llong c) {
vllong8 v = {c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vllong8 test2llong8(llong *p) {
llong c = *p;
vllong8 v = {c, c, c, c, c, c, c, c};
return v;
}
void test3llong8(void) {
llong c = 17;
int i;
vllong8 a = test1llong8(c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
vllong8 b = test2llong8(&c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef llong vllong4 __attribute__((__vector_size__(4 * sizeof(llong))));
__attribute__((noinline, noclone)) vllong4 test1llong4(llong c) {
vllong4 v = {c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vllong4 test2llong4(llong *p) {
llong c = *p;
vllong4 v = {c, c, c, c};
return v;
}
void test3llong4(void) {
llong c = 17;
int i;
vllong4 a = test1llong4(c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
vllong4 b = test2llong4(&c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef llong vllong2 __attribute__((__vector_size__(2 * sizeof(llong))));
__attribute__((noinline, noclone)) vllong2 test1llong2(llong c) {
vllong2 v = {c, c};
return v;
}
__attribute__((noinline, noclone)) vllong2 test2llong2(llong *p) {
llong c = *p;
vllong2 v = {c, c};
return v;
}
void test3llong2(void) {
llong c = 17;
int i;
vllong2 a = test1llong2(c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
vllong2 b = test2llong2(&c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef llong vllong1 __attribute__((__vector_size__(1 * sizeof(llong))));
__attribute__((noinline, noclone)) vllong1 test1llong1(llong c) {
vllong1 v = {c};
return v;
}
__attribute__((noinline, noclone)) vllong1 test2llong1(llong *p) {
llong c = (llong) *test1char8;
vllong1 v = {c};
return v;
}
void test3llong1(void) {
llong c = 17;
int i;
vllong1 a = test1llong1(c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
vllong1 b = test2llong1(&c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef double vdouble8 __attribute__((__vector_size__(8 * sizeof(double))));
__attribute__((noinline, noclone)) vdouble8 test1double8(double c) {
vdouble8 v = {c, c, c, c, c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vdouble8 test2double8(double *p) {
double c = *p;
vdouble8 v = {c, c, c, c, c, c, c, c};
return v;
}
void test3double8(void) {
double c = 17;
int i;
vdouble8 a = test1double8(c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
vdouble8 b = test2double8(&c);
for (i = 0; i < 8; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef double vdouble4 __attribute__((__vector_size__(4 * sizeof(double))));
__attribute__((noinline, noclone)) vdouble4 test1double4(double c) {
vdouble4 v = {c, c, c, c};
return v;
}
__attribute__((noinline, noclone)) vdouble4 test2double4(double *p) {
double c = *p;
vdouble4 v = {c, c, c, c};
return v;
}
void test3double4(void) {
double c = 17;
int i;
vdouble4 a = test1double4(c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
vdouble4 b = test2double4(&c);
for (i = 0; i < 4; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef double vdouble2 __attribute__((__vector_size__(2 * sizeof(double))));
__attribute__((noinline, noclone)) vdouble2 test1double2(double c) {
vdouble2 v = {c, c};
return v;
}
__attribute__((noinline, noclone)) vdouble2 test2double2(double *p) {
double c = *p;
vdouble2 v = {c, c};
return v;
}
void test3double2(void) {
double c = 17;
int i;
vdouble2 a = test1double2(c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
vdouble2 b = test2double2(&c);
for (i = 0; i < 2; i++)
if (a[i] != 17)
__builtin_abort();
}
typedef double vdouble1 __attribute__((__vector_size__(1 * sizeof(double))));
__attribute__((noinline, noclone)) vdouble1 test1double1(double c) {
vdouble1 v = {c};
return v;
}
__attribute__((noinline, noclone)) vdouble1 test2double1(double *p) {
double c = *p;
vdouble1 v = {c};
return v;
}
void test3double1(void) {
double c = 17;
int i;
vdouble1 a = test1double1(c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
vdouble1 b = test2double1(&c);
for (i = 0; i < 1; i++)
if (a[i] != 17)
__builtin_abort();
}
int main() {
test3char64();
test3char32();
test3char16();
test3char8();
test3char4();
test3char2();
test3char1();
test3short32();
test3short16();
test3short8();
test3short4();
test3short2();
test3short1();
test3int16();
test3int8();
test3int4();
test3int2();
test3int1();
test3float16();
test3float8();
test3float4();
test3float2();
test3float1();
test3llong8();
test3llong4();
test3llong2();
test3llong1();
test3double8();
test3double4();
test3double2();
test3double1();
return 0;
}
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
int main()
{
}
This diff is collapsed.
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment