quote-quot-0.2.1.0: Divide without division
Copyright(c) 2020-2022 Andrew Lelechenko
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Numeric.QuoteQuot

Description

Generate routines for integer division, employing arithmetic and bitwise operations only, which are 2.5x-3.5x faster than quot. Divisors must be known in compile-time and be positive.

Synopsis

Quasiquoters

quoteQuot :: (MulHi a, Lift a) => a -> Q (TExp (a -> a)) Source #

Quote integer division (quot) by a compile-time known divisor, which generates source code, employing arithmetic and bitwise operations only. This is usually 2.5x-3.5x faster than using normal quot.

{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices -ddump-simpl -dsuppress-all #-}
module Example where
import Numeric.QuoteQuot

-- Equivalent to (`quot` 10).
quot10 :: Word -> Word
quot10 = $$(quoteQuot 10)
>>> quot10 123
12

Here -ddump-splices demonstrates the chosen implementation for division by 10:

Splicing expression quoteQuot 10 ======>
((`shiftR` 3) . ((\ (W# w_a9N4) ->
  let !(# hi_a9N5, _ #) = (timesWord2# w_a9N4) 14757395258967641293##
  in W# hi_a9N5) . id))

And -ddump-simpl demonstrates generated Core:

quot10 = \ x_a5t2 ->
  case x_a5t2 of { W# w_acHY ->
  case timesWord2# w_acHY 14757395258967641293## of
  { (# hi_acIg, ds_dcIs #) ->
  W# (uncheckedShiftRL# hi_acIg 3#)
  }
  }

Benchmarks show that this implementation is 3.5x faster than (`quot` 10).

quoteRem :: (MulHi a, Lift a) => a -> Q (TExp (a -> a)) Source #

Similar to quoteQuot, but for rem.

quoteQuotRem :: (MulHi a, Lift a) => a -> Q (TExp (a -> (a, a))) Source #

Similar to quoteQuot, but for quotRem.

AST

astQuot :: (Integral a, FiniteBits a) => a -> AST a Source #

astQuot d constructs an AST representing a function, equivalent to quot a for positive a, but avoiding division instructions.

>>> astQuot (10 :: Data.Word.Word8)
Shr (MulHi Arg 205) 3

And indeed to divide Word8 by 10 one can multiply it by 205, take the high byte and shift it right by 3. Somewhat counterintuitively, this sequence of operations is faster than a single division on most modern achitectures.

astQuot function is polymorphic and supports both signed and unsigned operands of arbitrary finite bitness. Implementation is based on Ch. 10 of Hacker's Delight by Henry S. Warren, 2012.

data AST a Source #

An abstract syntax tree to represent a function of one argument.

Constructors

Arg

Argument of the function

MulHi (AST a) a

Multiply wide and return the high word of result

MulLo (AST a) a

Multiply

Add (AST a) (AST a)

Add

Sub (AST a) (AST a)

Subtract

Shl (AST a) Int

Shift left

Shr (AST a) Int

Shift right with sign extension

CmpGE (AST a) a

1 if greater than or equal, 0 otherwise

CmpLT (AST a) a

1 if less than, 0 otherwise

Instances

Instances details
Show a => Show (AST a) Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

showsPrec :: Int -> AST a -> ShowS #

show :: AST a -> String #

showList :: [AST a] -> ShowS #

interpretAST :: (Integral a, FiniteBits a) => AST a -> a -> a Source #

Reference (but slow) interpreter of AST. It is not meant to be used in production and is provided primarily for testing purposes.

>>> interpretAST (astQuot (10 :: Data.Word.Word8)) 123
12

quoteAST :: (MulHi a, Lift a) => AST a -> Q (TExp (a -> a)) Source #

Embed AST into Haskell expression.

assumeNonNegArg :: (Ord a, Num a) => AST a -> AST a Source #

Optimize AST, assuming that Arg is non-negative.

class (Integral a, FiniteBits a) => MulHi a where Source #

Types allowing to multiply wide and return the high word of result.

Methods

mulHi :: a -> a -> a Source #

Instances

Instances details
MulHi Int8 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Int8 -> Int8 -> Int8 Source #

MulHi Int16 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Int16 -> Int16 -> Int16 Source #

MulHi Int32 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Int32 -> Int32 -> Int32 Source #

MulHi Word Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Word -> Word -> Word Source #

MulHi Word8 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Word8 -> Word8 -> Word8 Source #

MulHi Word16 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Word16 -> Word16 -> Word16 Source #

MulHi Word32 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Word32 -> Word32 -> Word32 Source #

MulHi Word64 Source # 
Instance details

Defined in Numeric.QuoteQuot

Methods

mulHi :: Word64 -> Word64 -> Word64 Source #