[Git][ghc/ghc][wip/ncg-simd] further adjustments to genprimopcode

sheaf (@sheaf) gitlab at gitlab.haskell.org
Wed Jun 26 12:17:41 UTC 2024



sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC


Commits:
1604d9dc by sheaf at 2024-06-26T14:17:30+02:00
further adjustments to genprimopcode

- - - - -


2 changed files:

- compiler/GHC/Builtin/primops.txt.pp
- utils/genprimopcode/Main.hs


Changes:

=====================================
compiler/GHC/Builtin/primops.txt.pp
=====================================
@@ -4022,86 +4022,73 @@ section "SIMD Vectors"
   ,<Word8,Word8#,64>,<Word16,Word16#,32>,<Word32,Word32#,16>,<Word64,Word64#,8>]
 
 primtype VECTOR
-   with simd = True
-        vector = ALL_VECTOR_TYPES
+   with vector = ALL_VECTOR_TYPES
 
 primop VecBroadcastOp "broadcast#" GenPrimOp
    SCALAR -> VECTOR
    { Broadcast a scalar to all elements of a vector. }
-   with simd = True
-        vector = ALL_VECTOR_TYPES
+   with vector = ALL_VECTOR_TYPES
 
 primop VecPackOp "pack#" GenPrimOp
    VECTUPLE -> VECTOR
    { Pack the elements of an unboxed tuple into a vector. }
-   with simd = True
-        vector = ALL_VECTOR_TYPES
+   with vector = ALL_VECTOR_TYPES
 
 primop VecUnpackOp "unpack#" GenPrimOp
    VECTOR -> VECTUPLE
    { Unpack the elements of a vector into an unboxed tuple. #}
-   with simd = True
-        vector = ALL_VECTOR_TYPES
+   with vector = ALL_VECTOR_TYPES
 
 primop VecInsertOp "insert#" GenPrimOp
    VECTOR -> SCALAR -> Int# -> VECTOR
    { Insert a scalar at the given position in a vector. }
    with effect = CanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecAddOp "plus#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR
    { Add two vectors element-wise. }
    with commutable = True
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecSubOp "minus#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR
    { Subtract two vectors element-wise. }
-   with simd = True
-        vector = ALL_VECTOR_TYPES
+   with vector = ALL_VECTOR_TYPES
 
 primop VecMulOp "times#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR
    { Multiply two vectors element-wise. }
    with commutable = True
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecDivOp "divide#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR
    { Divide two vectors element-wise. }
    with effect = CanFail
-        simd = True
         vector = FLOAT_VECTOR_TYPES
 
 primop VecQuotOp "quot#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR
    { Rounds towards zero element-wise. }
    with effect = CanFail
-        simd = True
         vector = INT_VECTOR_TYPES
 
 primop VecRemOp "rem#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR
    { Satisfies @('quot#' x y) 'times#' y 'plus#' ('rem#' x y) == x at . }
    with effect = CanFail
-        simd = True
         vector = INT_VECTOR_TYPES
 
 primop VecNegOp "negate#" GenPrimOp
    VECTOR -> VECTOR
    { Negate element-wise. }
-   with simd = True
-        vector = SIGNED_VECTOR_TYPES
+   with vector = SIGNED_VECTOR_TYPES
 
 primop VecIndexByteArrayOp "indexArray#" GenPrimOp
    ByteArray# -> Int# -> VECTOR
    { Read a vector from specified index of immutable array. }
    with effect = CanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecReadByteArrayOp "readArray#" GenPrimOp
@@ -4109,7 +4096,6 @@ primop VecReadByteArrayOp "readArray#" GenPrimOp
    { Read a vector from specified index of mutable array. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecWriteByteArrayOp "writeArray#" GenPrimOp
@@ -4117,14 +4103,12 @@ primop VecWriteByteArrayOp "writeArray#" GenPrimOp
    { Write a vector to specified index of mutable array. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecIndexOffAddrOp "indexOffAddr#" GenPrimOp
    Addr# -> Int# -> VECTOR
    { Reads vector; offset in bytes. }
    with effect = CanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecReadOffAddrOp "readOffAddr#" GenPrimOp
@@ -4132,7 +4116,6 @@ primop VecReadOffAddrOp "readOffAddr#" GenPrimOp
    { Reads vector; offset in bytes. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecWriteOffAddrOp "writeOffAddr#" GenPrimOp
@@ -4140,7 +4123,6 @@ primop VecWriteOffAddrOp "writeOffAddr#" GenPrimOp
    { Write vector; offset in bytes. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 
@@ -4148,7 +4130,6 @@ primop VecIndexScalarByteArrayOp "indexArrayAs#" GenPrimOp
    ByteArray# -> Int# -> VECTOR
    { Read a vector from specified index of immutable array of scalars; offset is in scalar elements. }
    with effect = CanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecReadScalarByteArrayOp "readArrayAs#" GenPrimOp
@@ -4156,7 +4137,6 @@ primop VecReadScalarByteArrayOp "readArrayAs#" GenPrimOp
    { Read a vector from specified index of mutable array of scalars; offset is in scalar elements. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecWriteScalarByteArrayOp "writeArrayAs#" GenPrimOp
@@ -4164,14 +4144,12 @@ primop VecWriteScalarByteArrayOp "writeArrayAs#" GenPrimOp
    { Write a vector to specified index of mutable array of scalars; offset is in scalar elements. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecIndexScalarOffAddrOp "indexOffAddrAs#" GenPrimOp
    Addr# -> Int# -> VECTOR
    { Reads vector; offset in scalar elements. }
    with effect = CanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecReadScalarOffAddrOp "readOffAddrAs#" GenPrimOp
@@ -4179,7 +4157,6 @@ primop VecReadScalarOffAddrOp "readOffAddrAs#" GenPrimOp
    { Reads vector; offset in scalar elements. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop VecWriteScalarOffAddrOp "writeOffAddrAs#" GenPrimOp
@@ -4187,40 +4164,34 @@ primop VecWriteScalarOffAddrOp "writeOffAddrAs#" GenPrimOp
    { Write vector; offset in scalar elements. }
    with effect = ReadWriteEffect
         can_fail_warning = YesWarnCanFail
-        simd = True
         vector = ALL_VECTOR_TYPES
 
 primop   VecFMAdd   "fmadd#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR -> VECTOR
    {Fused multiply-add operation @x*y+z at . See "GHC.Prim#fma".}
    with
-      simd = True
       vector = FLOAT_VECTOR_TYPES
 primop   VecFMSub   "fmsub#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR -> VECTOR
    {Fused multiply-subtract operation @x*y-z at . See "GHC.Prim#fma".}
    with
-      simd = True
       vector = FLOAT_VECTOR_TYPES
 primop   VecFNMAdd   "fnmadd#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR -> VECTOR
    {Fused negate-multiply-add operation @-x*y+z at . See "GHC.Prim#fma".}
    with
-      simd = True
       vector = FLOAT_VECTOR_TYPES
 primop   VecFNMSub   "fnmsub#" GenPrimOp
    VECTOR -> VECTOR -> VECTOR -> VECTOR
    {Fused negate-multiply-subtract operation @-x*y-z at . See "GHC.Prim#fma".}
    with
-      simd = True
       vector = FLOAT_VECTOR_TYPES
 
 primop VecShuffleOp "shuffle#" GenPrimOp
   VECTOR -> VECTOR -> INTVECTUPLE -> VECTOR
   {Shuffle elements of the concatenation of the input two vectors
   into the result vector.}
-   with simd = True
-        vector = ALL_VECTOR_TYPES
+   with vector = ALL_VECTOR_TYPES
 
 ------------------------------------------------------------------------
 


=====================================
utils/genprimopcode/Main.hs
=====================================
@@ -468,53 +468,46 @@ gen_wrappers (Info _ entries)
      ++ "import qualified GHC.Prim\n"
      ++ "import GHC.Tuple ()\n"
      ++ "import GHC.Prim (" ++ types ++ ")\n"
-     ++ unlines (concatMap mkWrapper wrappers)
+     ++ unlines (concatMap mk_wrapper wrappers)
      where
-        wrappers = filter wantWrapper entries
+        wrappers = filter want_wrapper entries
         tycons = foldr union [] $ map (tyconsIn . ty) wrappers
         tycons' = filter (`notElem` [TyCon "()", TyCon "Bool"]) tycons
         types = concat $ intersperse ", " $ map show tycons'
-        mkWrapper spec =
+        mk_wrapper spec =
           let args = map (\n -> "a" ++ show n) [1 .. arity (ty spec)]
               src_name = wrap (name spec)
               lhs = src_name ++ " " ++ unwords args
-              rhs = wrapQual (name spec) ++ " " ++ unwords args
+              rhs = wrap_qual (name spec) ++ " " ++ unwords args
           in ["{-# NOINLINE " ++ src_name ++ " #-}",
               src_name ++ " :: " ++ pprTy (ty spec),
               lhs ++ " = " ++ rhs]
         wrap nm | isLower (head nm) = nm
                 | otherwise = "(" ++ nm ++ ")"
-        wrapQual nm | isLower (head nm) = "GHC.Prim." ++ nm
-                    | otherwise         = "(GHC.Prim." ++ nm ++ ")"
+        wrap_qual nm | isLower (head nm) = "GHC.Prim." ++ nm
+                     | otherwise         = "(GHC.Prim." ++ nm ++ ")"
 
-        wantWrapper :: Entry -> Bool
-        wantWrapper entry =
+        want_wrapper :: Entry -> Bool
+        want_wrapper entry =
           and
-            [ not $ name entry `elem` magicalPrimops
-            , is_primop entry
-                -- NB: is_primop rules out vector primops; not sure why this is necessary.
-            , not $ is_simd entry
-                -- Don't produce wrappers for SIMD primops.
+            [ is_primop entry
+            , not $ name entry `elem` magical_primops
+            , not $ is_vector entry
+                -- We currently don't generate wrappers for vector primops.
                 --
                 -- SIMD NCG TODO: this was the logic in place when SIMD primops
                 -- were LLVM only; but now that this is no longer the case I
                 -- suppose this choice can be revisited?
             ]
 
-        magicalPrimops :: [String]
-        magicalPrimops =
+        magical_primops :: [String]
+        magical_primops =
           [ "tagToEnum#"
               -- tagToEnum# is really magical, and can't have
               -- a wrapper since its implementation depends on
               -- the type of its result
           ]
 
-        is_simd :: Entry -> Bool
-        is_simd entry =
-            case lookup_attrib "simd" (opts entry) of
-              Just (OptionTrue _) -> True
-              _                   -> False
-
 gen_primop_list :: Info -> String
 gen_primop_list (Info _ entries)
    = unlines (



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1604d9dcfeffe44b50ee3250f59e7215f5bc7548

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1604d9dcfeffe44b50ee3250f59e7215f5bc7548
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240626/0a620a3d/attachment-0001.html>


More information about the ghc-commits mailing list