|
|
# Implementing new primitive comparisons to allow branchless algorithms
|
|
|
|
|
|
|
|
|
This page gathers the notes about implementing new primitive logical operations and thus resolving ticket [\#6135](https://gitlab.haskell.org//ghc/ghc/issues/6135). See [ this page](http://ghc.haskell.org/trac/ghc/wiki/NewPrimopsInGHC7.8) for a instructions how to adjust your already existing code to work with new primops.
|
|
|
This page presents motivation and technical details behind implementing new primitive comparison operators (this was originaly reported as Trac ticket [\#6135](https://gitlab.haskell.org//ghc/ghc/issues/6135)). See [ this page](http://ghc.haskell.org/trac/ghc/wiki/NewPrimopsInGHC7.8) for instructions how to adjust your already existing code to work with new primops.
|
|
|
|
|
|
## The problem
|
|
|
|
... | ... | @@ -24,7 +24,7 @@ False || x = x |
|
|
```
|
|
|
|
|
|
|
|
|
in GHC.Classes (ghc-prim library) which is equivalent of:
|
|
|
in GHC.Classes (ghc-prim library). This definition is equivalent of:
|
|
|
|
|
|
```wiki
|
|
|
(||) x y = case x of
|
... | ... | @@ -33,7 +33,7 @@ in GHC.Classes (ghc-prim library) which is equivalent of: |
|
|
```
|
|
|
|
|
|
|
|
|
During the compilation process (assuming the optimizations are turned on) the definition of `(||)` gets inlined and then case-of-case transform is performed successively. This results in following Core (cleaned up for clarity):
|
|
|
During compilation definition of `(||)` gets inlined (assuming the optimizations are turned on) and then case-of-case transform is performed successively. This results in following Core (cleaned up for clarity):
|
|
|
|
|
|
```wiki
|
|
|
case <# x 0 of _ {
|
... | ... | @@ -55,7 +55,7 @@ case <# x 0 of _ { |
|
|
```
|
|
|
|
|
|
|
|
|
and in following assembler code:
|
|
|
and in following assembly code:
|
|
|
|
|
|
```wiki
|
|
|
.Lc1rf:
|
... | ... | @@ -92,72 +92,7 @@ Note: this example was produced with GHC 7.6.3. At the moment of merging new pri |
|
|
## Solution
|
|
|
|
|
|
|
|
|
This problem was solved by modifying comparison primops to return unboxed unlifted `Int#` instead of `Bool` (which is lifted and thus is returned as a thunk that needs to be evaluated). Having `Int#` returned as a result of logical comparison will allow to use branchless bitwise logical operators instead of branching logical operators defined by Haskell.
|
|
|
|
|
|
## Implementation details
|
|
|
|
|
|
|
|
|
Below is a summary of implementation details and decisions:
|
|
|
|
|
|
- The new comparison primops return a value of type `Int#`: `1#` represents `True` and `0#` represents `False`. The `Int#` type was chosen because on Haskell it is more common to use signed Int type insetad of unsigned Word. By using `Int#` the users can easily convert unboxed result into a boxed value, without need to use `word2Int#` and `int2word#` primops.
|
|
|
|
|
|
- Unlike C, `2#` or `-3#` don't represent a Boolean value. More concretely, you can use `tagToEnum#` to convert one of these `Int#` values to a `Bool`, but `tagToEnum#` does no error checking, so it would be Very Very Bad to call it on `2#`.
|
|
|
|
|
|
- As a small side-task, four new logical bitwise primops have been implemented: `andI#`, `orI#`, `xorI#` and `negI#` ([\#7689](https://gitlab.haskell.org//ghc/ghc/issues/7689)). These operate on values of type `Int#`. Earlier we had only bitwise logical primops operating on values of type `Word#`.
|
|
|
|
|
|
- Names of the existing comparison primops were changed. Operators had `$` added before `#`, others had `I` added before the `#` (this is a mnemonic denoting that this primop returns and `Int#`). Examples:
|
|
|
|
|
|
```wiki
|
|
|
>=$# :: Int# -> Int# -> Int#
|
|
|
/=$## :: Double# -> Double# -> Int#
|
|
|
gtCharI# :: Char# -> Char# -> Int#
|
|
|
eqWordI# :: Word# -> Word# -> Int#
|
|
|
ltFloatI# :: Float# -> Float# -> Int#
|
|
|
leAddrI# :: Addr# -> Addr# -> Int#
|
|
|
```
|
|
|
|
|
|
- A new module `GHC.PrimWrappers` was added to ghc-prim library. This module contains wrappers for comparison primops. These wrappers have names identical to removed primops and return a `Bool`. Examples:
|
|
|
|
|
|
```wiki
|
|
|
gtChar# :: Char# -> Char# -> Bool
|
|
|
gtChar# a b = tagToEnum# (a `gtCharI#` b)
|
|
|
|
|
|
(>=#) :: Int# -> Int# -> Bool
|
|
|
(>=#) a b = tagToEnum# (a >=$# b)
|
|
|
|
|
|
eqWord# :: Word# -> Word# -> Bool
|
|
|
eqWord# a b = tagToEnum# (a `eqWordI#` b)
|
|
|
|
|
|
(/=##) :: Double# -> Double# -> Bool
|
|
|
(/=##) a b = tagToEnum# (a /=$## b)
|
|
|
|
|
|
ltFloat# :: Float# -> Float# -> Bool
|
|
|
ltFloat# a b = tagToEnum# (a `ltFloatI#` b)
|
|
|
|
|
|
leAddr# :: Addr# -> Addr# -> Bool
|
|
|
leAddr# a b = tagToEnum# (a `leAddrI#` b)
|
|
|
```
|
|
|
|
|
|
|
|
|
Thanks to these wrappers the change is almost backwards compatible. **The only thing primop users need to change in their existing code to make it work again is adding import of GHC.PrimWrappers module.**
|
|
|
|
|
|
- Functions for comparing `Integer` type, implemented in integer-gmp and integer-simple libraries, received a similar treatment. Technically they are not primops, because they are implemented in Haskell (in case of integer-gmp also with FFI), but they pretend to be ones. There are six primops for comparing `Integer` values:
|
|
|
|
|
|
```wiki
|
|
|
eqInteger# :: Integer -> Integer -> Int#
|
|
|
neqInteger# :: Integer -> Integer -> Int#
|
|
|
leInteger# :: Integer -> Integer -> Int#
|
|
|
ltInteger# :: Integer -> Integer -> Int#
|
|
|
gtInteger# :: Integer -> Integer -> Int#
|
|
|
geInteger# :: Integer -> Integer -> Int#
|
|
|
```
|
|
|
|
|
|
|
|
|
Each of these functions has a wrapper that calls `tagToEnum#` and returns a `Bool`. These wrappers are: `eqInteger`, `neqInteger`, `leInteger`, `ltInteger`, `gtInteger` and `geInteger`.
|
|
|
|
|
|
- Six primops are an exception to the rules above: `sameMutableArray#`, `sameMutableByteArray#`, `sameMutableArrayArray#`, `sameMutVar#`, `sameMVar#` and `sameTVar#`. Their names have remained the same as before and new wrappers created for them lack `#` at the end of their name. We made that decission because this naming feels more consistent and these primops are rarely used so we expect that they won't break a lot of existing code.
|
|
|
|
|
|
- Other libraries that were modified to work with the new primops are: base, ghc-prim and primitive. The only required modifications were imports of the GHC.PrimWrappers module in modules that use the primops.
|
|
|
This problem was solved by modifying comparison primops to return unboxed unlifted `Int#` instead of `Bool`, which is lifted and thus must be inspected with a `case` expression. Having `Int#` returned as a result of logical comparison allows to use branchless bitwise logical operators instead of branching logical operators defined by Haskell.
|
|
|
|
|
|
## Eliminating branches using new primops
|
|
|
|
... | ... | @@ -302,6 +237,71 @@ Let's analyze line by line the part responsible for evaluating the scrutinee: |
|
|
|
|
|
The assembly does not contain comparisons and branches in the scrutinee of the case expression, but still uses jumps to select an appropriate branch of the case expression.
|
|
|
|
|
|
## Implementation details
|
|
|
|
|
|
|
|
|
Below is a summary of implementation details and decisions:
|
|
|
|
|
|
- The new comparison primops return a value of type `Int#`: `1#` represents `True` and `0#` represents `False`. The `Int#` type was chosen because on Haskell it is more common to use signed Int type insetad of unsigned Word. By using `Int#` the users can easily convert unboxed result into a boxed value, without need to use `word2Int#` and `int2word#` primops.
|
|
|
|
|
|
- Unlike C, `2#` or `-3#` don't represent a Boolean value. More concretely, you can use `tagToEnum#` to convert one of these `Int#` values to a `Bool`, but `tagToEnum#` does no error checking, so it would be Very Very Bad to call it on `2#`.
|
|
|
|
|
|
- As a small side-task, four new logical bitwise primops have been implemented: `andI#`, `orI#`, `xorI#` and `negI#` ([\#7689](https://gitlab.haskell.org//ghc/ghc/issues/7689)). These operate on values of type `Int#`. Earlier we had only bitwise logical primops operating on values of type `Word#`.
|
|
|
|
|
|
- Names of the existing comparison primops were changed. Operators had `$` added before `#`, others had `I` added before the `#` (this is a mnemonic denoting that this primop returns and `Int#`). Examples:
|
|
|
|
|
|
```wiki
|
|
|
>=$# :: Int# -> Int# -> Int#
|
|
|
/=$## :: Double# -> Double# -> Int#
|
|
|
gtCharI# :: Char# -> Char# -> Int#
|
|
|
eqWordI# :: Word# -> Word# -> Int#
|
|
|
ltFloatI# :: Float# -> Float# -> Int#
|
|
|
leAddrI# :: Addr# -> Addr# -> Int#
|
|
|
```
|
|
|
|
|
|
- A new module `GHC.PrimWrappers` was added to ghc-prim library. This module contains wrappers for comparison primops. These wrappers have names identical to removed primops and return a `Bool`. Examples:
|
|
|
|
|
|
```wiki
|
|
|
gtChar# :: Char# -> Char# -> Bool
|
|
|
gtChar# a b = tagToEnum# (a `gtCharI#` b)
|
|
|
|
|
|
(>=#) :: Int# -> Int# -> Bool
|
|
|
(>=#) a b = tagToEnum# (a >=$# b)
|
|
|
|
|
|
eqWord# :: Word# -> Word# -> Bool
|
|
|
eqWord# a b = tagToEnum# (a `eqWordI#` b)
|
|
|
|
|
|
(/=##) :: Double# -> Double# -> Bool
|
|
|
(/=##) a b = tagToEnum# (a /=$## b)
|
|
|
|
|
|
ltFloat# :: Float# -> Float# -> Bool
|
|
|
ltFloat# a b = tagToEnum# (a `ltFloatI#` b)
|
|
|
|
|
|
leAddr# :: Addr# -> Addr# -> Bool
|
|
|
leAddr# a b = tagToEnum# (a `leAddrI#` b)
|
|
|
```
|
|
|
|
|
|
|
|
|
Thanks to these wrappers the change is almost backwards compatible. **The only thing primop users need to change in their existing code to make it work again is adding import of GHC.PrimWrappers module.**
|
|
|
|
|
|
- Functions for comparing `Integer` type, implemented in integer-gmp and integer-simple libraries, received a similar treatment. Technically they are not primops, because they are implemented in Haskell (in case of integer-gmp also with FFI), but they pretend to be ones. There are six primops for comparing `Integer` values:
|
|
|
|
|
|
```wiki
|
|
|
eqInteger# :: Integer -> Integer -> Int#
|
|
|
neqInteger# :: Integer -> Integer -> Int#
|
|
|
leInteger# :: Integer -> Integer -> Int#
|
|
|
ltInteger# :: Integer -> Integer -> Int#
|
|
|
gtInteger# :: Integer -> Integer -> Int#
|
|
|
geInteger# :: Integer -> Integer -> Int#
|
|
|
```
|
|
|
|
|
|
|
|
|
Each of these functions has a wrapper that calls `tagToEnum#` and returns a `Bool`. These wrappers are: `eqInteger`, `neqInteger`, `leInteger`, `ltInteger`, `gtInteger` and `geInteger`.
|
|
|
|
|
|
- Six primops are an exception to the rules above: `sameMutableArray#`, `sameMutableByteArray#`, `sameMutableArrayArray#`, `sameMutVar#`, `sameMVar#` and `sameTVar#`. Their names have remained the same as before and new wrappers created for them lack `#` at the end of their name. We made that decission because this naming feels more consistent and these primops are rarely used so we expect that they won't break a lot of existing code.
|
|
|
|
|
|
- Other libraries that were modified to work with the new primops are: base, ghc-prim and primitive. The only required modifications were imports of the GHC.PrimWrappers module in modules that use the primops.
|
|
|
|
|
|
### Benchmarks
|
|
|
|
|
|
|
... | ... | |