Giter Site home page Giter Site logo

bodigrim / quote-quot Goto Github PK

View Code? Open in Web Editor NEW
15.0 3.0 1.0 22 KB

Divide without division

Home Page: http://hackage.haskell.org/package/quote-quot

License: BSD 3-Clause "New" or "Revised" License

Haskell 100.00%
code-generation hackers-delight integer-division long-multiplication strength-reduction template-haskell

quote-quot's Introduction

quote-quot Hackage Stackage LTS Stackage Nightly

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.

{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices -ddump-simpl -dsuppress-all #-}
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):

{-# LANGUAGE TemplateHaskell #-}
import Data.List
import Numeric.QuoteQuot
import System.CPUTime

measure :: String -> (Word -> Word) -> IO ()
measure name f = do
  t0 <- getCPUTime
  print $ foldl' (+) 0 $ map f [0..100000000]
  t1 <- getCPUTime
  putStrLn $ name ++ " " ++ show ((t1 - t0) `quot` 1000000000) ++ " ms"
{-# INLINE measure #-}

main :: IO ()
main = do
  measure "     (`quot` 10)"      (`quot` 10)
  measure "$$(quoteQuot 10)" $$(quoteQuot 10)
499999960000000
     (`quot` 10) 316 ms
499999960000000
$$(quoteQuot 10)  89 ms

Conventional wisdom is that such microoptimizations are negligible in practice, but this is not always the case. For instance, quite surprisingly, this trick alone made Unicode normalization of Hangul characters twice faster in unicode-transforms.

quote-quot's People

Contributors

bodigrim avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar

Forkers

1jajen1

quote-quot's Issues

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.