From daff1e30219d136977c71f42e82ccc58c9013cfb Mon Sep 17 00:00:00 2001 From: Jannis <overesch.jannis@gmail.com> Date: Wed, 20 Mar 2024 20:39:38 +0100 Subject: [PATCH] Division by constants optimization --- compiler/GHC/Cmm/Config.hs | 2 + compiler/GHC/Cmm/MachOp.hs | 15 + compiler/GHC/Cmm/Opt.hs | 610 +- compiler/GHC/Cmm/Pipeline.hs | 7 +- compiler/GHC/Cmm/Sink.hs | 135 +- compiler/GHC/Driver/Config/Cmm.hs | 12 + compiler/GHC/StgToCmm/Prim.hs | 33 +- testsuite/tests/numeric/should_run/all.T | 1 + testsuite/tests/numeric/should_run/div01.hs | 109 + .../tests/numeric/should_run/div01.stdout | 12030 ++++++++++++++++ .../numeric/should_run/div01.stdout-ws-32 | 12030 ++++++++++++++++ testsuite/tests/numeric/should_run/mul2.hs | 21 +- .../tests/numeric/should_run/mul2.stdout | 18 + .../numeric/should_run/mul2.stdout-ws-32 | 18 + 14 files changed, 24909 insertions(+), 132 deletions(-) create mode 100644 testsuite/tests/numeric/should_run/div01.hs create mode 100644 testsuite/tests/numeric/should_run/div01.stdout create mode 100644 testsuite/tests/numeric/should_run/div01.stdout-ws-32 diff --git a/compiler/GHC/Cmm/Config.hs b/compiler/GHC/Cmm/Config.hs index 4c8f8f2280c7..218aa70de571 100644 --- a/compiler/GHC/Cmm/Config.hs +++ b/compiler/GHC/Cmm/Config.hs @@ -24,6 +24,8 @@ data CmmConfig = CmmConfig , cmmExternalDynamicRefs :: !Bool -- ^ Generate code to link against dynamic libraries , cmmDoCmmSwitchPlans :: !Bool -- ^ Should the Cmm pass replace Stg switch statements , cmmSplitProcPoints :: !Bool -- ^ Should Cmm split proc points or not + , cmmAllowMul2 :: !Bool -- ^ Does this platform support mul2 + , cmmOptConstDivision :: !Bool -- ^ Should we optimize constant divisors } -- | retrieve the target Cmm platform diff --git a/compiler/GHC/Cmm/MachOp.hs b/compiler/GHC/Cmm/MachOp.hs index 81abe1a5d7b3..508359e40ab7 100644 --- a/compiler/GHC/Cmm/MachOp.hs +++ b/compiler/GHC/Cmm/MachOp.hs @@ -7,6 +7,7 @@ module GHC.Cmm.MachOp , pprMachOp, isCommutableMachOp, isAssociativeMachOp , isComparisonMachOp, maybeIntComparison, machOpResultType , machOpArgReps, maybeInvertComparison, isFloatComparison + , isCommutableCallishMachOp -- MachOp builders , mo_wordAdd, mo_wordSub, mo_wordEq, mo_wordNe,mo_wordMul, mo_wordSQuot @@ -790,3 +791,17 @@ machOpMemcpyishAlign op = case op of MO_Memmove align -> Just align MO_Memcmp align -> Just align _ -> Nothing + +isCommutableCallishMachOp :: CallishMachOp -> Bool +isCommutableCallishMachOp op = + case op of + MO_x64_Add -> True + MO_x64_Mul -> True + MO_x64_Eq -> True + MO_x64_Ne -> True + MO_x64_And -> True + MO_x64_Or -> True + MO_x64_Xor -> True + MO_S_Mul2 _ -> True + MO_U_Mul2 _ -> True + _ -> False diff --git a/compiler/GHC/Cmm/Opt.hs b/compiler/GHC/Cmm/Opt.hs index a7a03b2526ad..2d0b54232d71 100644 --- a/compiler/GHC/Cmm/Opt.hs +++ b/compiler/GHC/Cmm/Opt.hs @@ -5,28 +5,52 @@ -- (c) The University of Glasgow 2006 -- ----------------------------------------------------------------------------- - +{-# LANGUAGE TupleSections #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE PatternSynonyms #-} module GHC.Cmm.Opt ( constantFoldNode, constantFoldExpr, cmmMachOpFold, - cmmMachOpFoldM + cmmMachOpFoldM, + Opt, runOpt ) where import GHC.Prelude +import GHC.Cmm.Dataflow.Block import GHC.Cmm.Utils import GHC.Cmm -import GHC.Utils.Misc +import GHC.Cmm.Config + +import GHC.Types.Unique.Supply +import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Platform import Data.Maybe - - -constantFoldNode :: Platform -> CmmNode e x -> CmmNode e x -constantFoldNode platform = mapExp (constantFoldExpr platform) +import Data.Word +import GHC.Exts (oneShot) +import Control.Monad + +constantFoldNode :: CmmNode e x -> Opt (CmmNode e x) +constantFoldNode (CmmUnsafeForeignCall (PrimTarget op) res args) + = traverse constantFoldExprOpt args >>= cmmCallishMachOpFold op res +constantFoldNode node + = mapExpOpt constantFoldExprOpt node + +constantFoldExprOpt :: CmmExpr -> Opt CmmExpr +constantFoldExprOpt e = wrapRecExpOpt f e + where + f (CmmMachOp op args) + = do + cfg <- getConfig + case cmmMachOpFold (cmmPlatform cfg) op args of + CmmMachOp op' args' -> fromMaybe (CmmMachOp op' args') <$> cmmMachOpFoldOptM cfg op' args' + e -> pure e + f (CmmRegOff r 0) = pure (CmmReg r) + f e = pure e constantFoldExpr :: Platform -> CmmExpr -> CmmExpr constantFoldExpr platform = wrapRecExp f @@ -281,7 +305,7 @@ cmmMachOpFoldM platform cmp [CmmMachOp conv [x], CmmLit (CmmInt i _)] maybe_comparison (MO_S_Le _) rep False = Just (MO_U_Le rep) maybe_comparison _ _ _ = Nothing --- We can often do something with constants of 0 and 1 ... +-- We can often do something with constants of 0, 1 and (-1) ... -- See Note [Comparison operators] cmmMachOpFoldM platform mop [x, y@(CmmLit (CmmInt 0 _))] @@ -352,6 +376,8 @@ cmmMachOpFoldM platform mop [x, (CmmLit (CmmInt n _))] MO_Mul rep | Just p <- exactLog2 n -> Just $! (cmmMachOpFold platform (MO_Shl rep) [x, CmmLit (CmmInt p $ wordWidth platform)]) + -- The optimization for division by power of 2 is technically duplicated, but since at least one other part of ghc uses + -- the pure `constantFoldExpr` this remains MO_U_Quot rep | Just p <- exactLog2 n -> Just $! (cmmMachOpFold platform (MO_U_Shr rep) [x, CmmLit (CmmInt p $ wordWidth platform)]) @@ -360,46 +386,19 @@ cmmMachOpFoldM platform mop [x, (CmmLit (CmmInt n _))] Just $! (cmmMachOpFold platform (MO_And rep) [x, CmmLit (CmmInt (n - 1) rep)]) MO_S_Quot rep | Just p <- exactLog2 n, - CmmReg _ <- x -> -- We duplicate x in signedQuotRemHelper, hence require - -- it is a reg. FIXME: remove this restriction. + CmmReg _ <- x -> Just $! (cmmMachOpFold platform (MO_S_Shr rep) - [signedQuotRemHelper rep p, CmmLit (CmmInt p $ wordWidth platform)]) + [signedQuotRemHelper platform n x rep p, CmmLit (CmmInt p $ wordWidth platform)]) MO_S_Rem rep | Just p <- exactLog2 n, - CmmReg _ <- x -> -- We duplicate x in signedQuotRemHelper, hence require - -- it is a reg. FIXME: remove this restriction. + CmmReg _ <- x -> -- We replace (x `rem` 2^p) by (x - (x `quot` 2^p) * 2^p). -- Moreover, we fuse MO_S_Shr (last operation of MO_S_Quot) -- and MO_S_Shl (multiplication by 2^p) into a single MO_And operation. Just $! (cmmMachOpFold platform (MO_Sub rep) [x, cmmMachOpFold platform (MO_And rep) - [signedQuotRemHelper rep p, CmmLit (CmmInt (- n) rep)]]) + [signedQuotRemHelper platform n x rep p, CmmLit (CmmInt (- n) rep)]]) _ -> Nothing - where - -- In contrast with unsigned integers, for signed ones - -- shift right is not the same as quot, because it rounds - -- to minus infinity, whereas quot rounds toward zero. - -- To fix this up, we add one less than the divisor to the - -- dividend if it is a negative number. - -- - -- to avoid a test/jump, we use the following sequence: - -- x1 = x >> word_size-1 (all 1s if -ve, all 0s if +ve) - -- x2 = y & (divisor-1) - -- result = x + x2 - -- this could be done a bit more simply using conditional moves, - -- but we're processor independent here. - -- - -- we optimise the divide by 2 case slightly, generating - -- x1 = x >> word_size-1 (unsigned) - -- return = x + x1 - signedQuotRemHelper :: Width -> Integer -> CmmExpr - signedQuotRemHelper rep p = CmmMachOp (MO_Add rep) [x, x2] - where - bits = fromIntegral (widthInBits rep) - 1 - shr = if p == 1 then MO_U_Shr rep else MO_S_Shr rep - x1 = CmmMachOp shr [x, CmmLit (CmmInt bits $ wordWidth platform)] - x2 = if p == 1 then x1 else - CmmMachOp (MO_And rep) [x1, CmmLit (CmmInt (n-1) rep)] -- ToDo (#7116): optimise floating-point multiplication, e.g. x*2.0 -> x+x -- Unfortunately this needs a unique supply because x might not be a @@ -420,10 +419,541 @@ we really want to convert to That's what the constant-folding operations on comparison operators do above. -} - -- ----------------------------------------------------------------------------- -- Utils isPicReg :: CmmExpr -> Bool isPicReg (CmmReg (CmmGlobal (GlobalRegUse PicBaseReg _))) = True isPicReg _ = False + +canOptimizeDivision :: CmmConfig -> Width -> Bool +canOptimizeDivision cfg rep = cmmOptConstDivision cfg && + -- we can either widen the arguments to simulate mul2 or use mul2 directly for the platform word size + (rep < wordWidth platform || (rep == wordWidth platform && cmmAllowMul2 cfg)) + where platform = cmmPlatform cfg + +-- ----------------------------------------------------------------------------- +-- Folding callish machops + +cmmCallishMachOpFold :: CallishMachOp -> [CmmFormal] -> [CmmActual] -> Opt (CmmNode O O) +cmmCallishMachOpFold op res args = + fromMaybe (CmmUnsafeForeignCall (PrimTarget op) res args) <$> (getConfig >>= \cfg -> cmmCallishMachOpFoldM cfg op res args) + +cmmCallishMachOpFoldM :: CmmConfig -> CallishMachOp -> [CmmFormal] -> [CmmActual] -> Opt (Maybe (CmmNode O O)) + +-- If possible move the literals to the right, the following cases assume that to be the case +cmmCallishMachOpFoldM cfg op res [x@(CmmLit _),y] + | isCommutableCallishMachOp op && not (isLit y) = cmmCallishMachOpFoldM cfg op res [y,x] + +-- Both arguments are literals, replace with the result +cmmCallishMachOpFoldM _ op res [CmmLit (CmmInt x _), CmmLit (CmmInt y _)] + = case op of + MO_S_Mul2 rep + | [rHiNeeded,rHi,rLo] <- res -> do + let resSz = widthInBits rep + resVal = (narrowS rep x) * (narrowS rep y) + high = resVal `shiftR` resSz + low = narrowS rep resVal + isHiNeeded = high /= low `shiftR` resSz + isHiNeededVal = if isHiNeeded then 1 else 0 + prependNode $! CmmAssign (CmmLocal rHiNeeded) (CmmLit $ CmmInt isHiNeededVal rep) + prependNode $! CmmAssign (CmmLocal rHi) (CmmLit $ CmmInt high rep) + pure . Just $! CmmAssign (CmmLocal rLo) (CmmLit $ CmmInt low rep) + MO_U_Mul2 rep + | [rHi,rLo] <- res -> do + let resSz = widthInBits rep + resVal = (narrowU rep x) * (narrowU rep y) + high = resVal `shiftR` resSz + low = narrowU rep resVal + prependNode $! CmmAssign (CmmLocal rHi) (CmmLit $ CmmInt high rep) + pure . Just $! CmmAssign (CmmLocal rLo) (CmmLit $ CmmInt low rep) + MO_S_QuotRem rep + | [rQuot, rRem] <- res, + y /= 0 -> do + let (q,r) = quotRem (narrowS rep x) (narrowS rep y) + prependNode $! CmmAssign (CmmLocal rQuot) (CmmLit $ CmmInt q rep) + pure . Just $! CmmAssign (CmmLocal rRem) (CmmLit $ CmmInt r rep) + MO_U_QuotRem rep + | [rQuot, rRem] <- res, + y /= 0 -> do + let (q,r) = quotRem (narrowU rep x) (narrowU rep y) + prependNode $! CmmAssign (CmmLocal rQuot) (CmmLit $ CmmInt q rep) + pure . Just $! CmmAssign (CmmLocal rRem) (CmmLit $ CmmInt r rep) + _ -> pure Nothing + +-- 0, 1 or -1 as one of the constants + +cmmCallishMachOpFoldM _ op res [_, CmmLit (CmmInt 0 _)] + = case op of + -- x * 0 == 0 + MO_S_Mul2 rep + | [rHiNeeded, rHi, rLo] <- res -> do + prependNode $! CmmAssign (CmmLocal rHiNeeded) (CmmLit $ CmmInt 0 rep) + prependNode $! CmmAssign (CmmLocal rHi) (CmmLit $ CmmInt 0 rep) + pure . Just $! CmmAssign (CmmLocal rLo) (CmmLit $ CmmInt 0 rep) + -- x * 0 == 0 + MO_U_Mul2 rep + | [rHi, rLo] <- res -> do + prependNode $! CmmAssign (CmmLocal rHi) (CmmLit $ CmmInt 0 rep) + pure . Just $! CmmAssign (CmmLocal rLo) (CmmLit $ CmmInt 0 rep) + _ -> pure Nothing + +cmmCallishMachOpFoldM _ op res [CmmLit (CmmInt 0 _), _] + = case op of + -- 0 quotRem d == (0,0) + MO_S_QuotRem rep + | [rQuot, rRem] <- res -> do + prependNode $! CmmAssign (CmmLocal rQuot) (CmmLit $ CmmInt 0 rep) + pure . Just $! CmmAssign (CmmLocal rRem) (CmmLit $ CmmInt 0 rep) + -- 0 quotRem d == (0,0) + MO_U_QuotRem rep + | [rQuot,rRem] <- res -> do + prependNode $! CmmAssign (CmmLocal rQuot) (CmmLit $ CmmInt 0 rep) + pure . Just $! CmmAssign (CmmLocal rRem) (CmmLit $ CmmInt 0 rep) + _ -> pure Nothing + +cmmCallishMachOpFoldM cfg op res [x, CmmLit (CmmInt 1 _)] + = case op of + -- x * 1 == x -- Note: The high word needs to be a sign extension of the low word, so we use a sign extending shift + MO_S_Mul2 rep + | [rHiNeeded, rHi, rLo] <- res -> do + let platform = cmmPlatform cfg + wordRep = wordWidth platform + repInBits = toInteger $ widthInBits rep + prependNode $! CmmAssign (CmmLocal rHiNeeded) (CmmLit $ CmmInt 0 rep) + prependNode $! CmmAssign (CmmLocal rHi) (cmmMachOpFold platform (MO_S_Shr rep) [x, CmmLit $ CmmInt (repInBits - 1) wordRep]) + pure . Just $! CmmAssign (CmmLocal rLo) x + -- x * 1 == x + MO_U_Mul2 rep + | [rHi, rLo] <- res -> do + prependNode $! CmmAssign (CmmLocal rHi) (CmmLit $ CmmInt 0 rep) + pure . Just $! CmmAssign (CmmLocal rLo) x + -- x quotRem 1 == (x, 0) + MO_S_QuotRem rep + | [rQuot, rRem] <- res -> do + prependNode $! CmmAssign (CmmLocal rQuot) x + pure . Just $! CmmAssign (CmmLocal rRem) (CmmLit $ CmmInt 0 rep) + -- x quotRem 1 == (x, 0) + MO_U_QuotRem rep + | [rQuot, rRem] <- res -> do + prependNode $! CmmAssign (CmmLocal rQuot) x + pure . Just $! CmmAssign (CmmLocal rRem) (CmmLit $ CmmInt 0 rep) + _ -> pure Nothing + +-- handle quotRem with a constant divisor + +cmmCallishMachOpFoldM cfg op res [n, CmmLit (CmmInt d' _)] + = case op of + MO_S_QuotRem rep + | Just p <- exactLog2 d, + [rQuot,rRem] <- res -> do + n' <- intoRegister n (cmmBits rep) + -- first prepend the optimized division by a power 2 + prependNode $! CmmAssign (CmmLocal rQuot) + (cmmMachOpFold platform (MO_S_Shr rep) + [signedQuotRemHelper platform d n' rep p, CmmLit (CmmInt p $ wordWidth platform)]) + -- then output an optimized remainder by a power of 2 + pure . Just $! CmmAssign (CmmLocal rRem) + (cmmMachOpFold platform (MO_Sub rep) + [n', cmmMachOpFold platform (MO_And rep) + [signedQuotRemHelper platform d n' rep p, CmmLit (CmmInt (- d) rep)]]) + | canOptimizeDivision cfg rep, + d /= (-1), d /= 0, d /= 1, + [rQuot,rRem] <- res -> do + -- we are definitely going to use n multiple times, so put it into a register + n' <- intoRegister n (cmmBits rep) + -- generate an optimized (signed) division of n by d + q <- generateDivisionBySigned platform cfg rep n' d + -- we also need the result multiple times to calculate the remainder + q' <- intoRegister q (cmmBits rep) + + prependNode $! CmmAssign (CmmLocal rQuot) q' + -- The remainder now becomes n - q * d + pure . Just $! CmmAssign (CmmLocal rRem) $ CmmMachOp (MO_Sub rep) [n', CmmMachOp (MO_Mul rep) [q', CmmLit $ CmmInt d rep]] + where + platform = cmmPlatform cfg + d = narrowS rep d' + MO_U_QuotRem rep + | Just p <- exactLog2 d, + [rQuot,rRem] <- res -> do + -- first prepend the optimized division by a power 2 + prependNode $! CmmAssign (CmmLocal rQuot) $ CmmMachOp (MO_U_Shr rep) [n, CmmLit (CmmInt p $ wordWidth platform)] + -- then output an optimized remainder by a power of 2 + pure . Just $! CmmAssign (CmmLocal rRem) $ CmmMachOp (MO_And rep) [n, CmmLit (CmmInt (d - 1) rep)] + | canOptimizeDivision cfg rep, + d /= 0, d /= 1, + [rQuot,rRem] <- res -> do + -- we are definitely going to use n multiple times, so put it into a register + n' <- intoRegister n (cmmBits rep) + -- generate an optimized (unsigned) division of n by d + q <- generateDivisionByUnsigned platform cfg rep n' d + -- we also need the result multiple times to calculate the remainder + q' <- intoRegister q (cmmBits rep) + + prependNode $! CmmAssign (CmmLocal rQuot) q' + -- The remainder now becomes n - q * d + pure . Just $! CmmAssign (CmmLocal rRem) $ CmmMachOp (MO_Sub rep) [n', CmmMachOp (MO_Mul rep) [q', CmmLit $ CmmInt d rep]] + where + platform = cmmPlatform cfg + d = narrowU rep d' + _ -> pure Nothing + +cmmCallishMachOpFoldM _ _ _ _ = pure Nothing + +-- ----------------------------------------------------------------------------- +-- Specialized constant folding for MachOps which sometimes need to expand into multiple nodes + +cmmMachOpFoldOptM :: CmmConfig -> MachOp -> [CmmExpr] -> Opt (Maybe CmmExpr) + +cmmMachOpFoldOptM cfg op [n, CmmLit (CmmInt d' _)] = + case op of + MO_S_Quot rep + -- recheck for power of 2 division. This may not be handled by cmmMachOpFoldM if n is not in a register + | Just p <- exactLog2 d -> do + n' <- intoRegister n (cmmBits rep) + pure . Just $! cmmMachOpFold platform (MO_S_Shr rep) + [ signedQuotRemHelper platform d n' rep p + , CmmLit (CmmInt p $ wordWidth platform) + ] + | canOptimizeDivision cfg rep, + d /= (-1), d /= 0, d /= 1 -> Just <$!> generateDivisionBySigned platform cfg rep n d + where d = narrowS rep d' + MO_S_Rem rep + -- recheck for power of 2 remainder. This may not be handled by cmmMachOpFoldM if n is not in a register + | Just p <- exactLog2 d -> do + n' <- intoRegister n (cmmBits rep) + pure . Just $! cmmMachOpFold platform (MO_Sub rep) + [ n' + , cmmMachOpFold platform (MO_And rep) + [ signedQuotRemHelper platform d n' rep p + , CmmLit (CmmInt (- d) rep) + ] + ] + | canOptimizeDivision cfg rep, + d /= (-1), d /= 0, d /= 1 -> do + n' <- intoRegister n (cmmBits rep) + -- first generate the division + q <- generateDivisionBySigned platform cfg rep n' d + -- then calculate the remainder by n - q * d + pure . Just $! CmmMachOp (MO_Sub rep) [n', CmmMachOp (MO_Mul rep) [q, CmmLit $ CmmInt d rep]] + where d = narrowS rep d' + MO_U_Quot rep + -- No need to recheck power of 2 division because cmmMachOpFoldM always handles that case + | canOptimizeDivision cfg rep, + d /= 0, d /= 1, Nothing <- exactLog2 d -> Just <$!> generateDivisionByUnsigned platform cfg rep n d + where d = narrowU rep d' + MO_U_Rem rep + -- No need to recheck power of 2 remainder because cmmMachOpFoldM always handles that case + | canOptimizeDivision cfg rep, + d /= 0, d /= 1, Nothing <- exactLog2 d -> do + n' <- intoRegister n (cmmBits rep) + -- first generate the division + q <- generateDivisionByUnsigned platform cfg rep n d + -- then calculate the remainder by n - q * d + pure . Just $! CmmMachOp (MO_Sub rep) [n', CmmMachOp (MO_Mul rep) [q, CmmLit $ CmmInt d rep]] + where d = narrowU rep d' + _ -> pure Nothing + where platform = cmmPlatform cfg + +cmmMachOpFoldOptM _ _ _ = pure Nothing + +-- ----------------------------------------------------------------------------- +-- Utils for prepending new nodes + +-- Move an expression into a register to possibly use it multiple times +intoRegister :: CmmExpr -> CmmType -> Opt CmmExpr +intoRegister e@(CmmReg _) _ = pure e +intoRegister expr ty = do + u <- getUniqueM + let reg = LocalReg u ty + CmmReg (CmmLocal reg) <$ prependNode (CmmAssign (CmmLocal reg) expr) + +prependNode :: CmmNode O O -> Opt () +prependNode n = Opt $ \_ xs -> pure (xs ++ [n], ()) + +-- ----------------------------------------------------------------------------- +-- Division by constants utils + +-- Helper for division by a power of 2 +-- In contrast with unsigned integers, for signed ones +-- shift right is not the same as quot, because it rounds +-- to minus infinity, whereas quot rounds toward zero. +-- To fix this up, we add one less than the divisor to the +-- dividend if it is a negative number. +-- +-- to avoid a test/jump, we use the following sequence: +-- x1 = x >> word_size-1 (all 1s if -ve, all 0s if +ve) +-- x2 = y & (divisor-1) +-- result = x + x2 +-- this could be done a bit more simply using conditional moves, +-- but we're processor independent here. +-- +-- we optimize the divide by 2 case slightly, generating +-- x1 = x >> word_size-1 (unsigned) +-- return = x + x1 +signedQuotRemHelper :: Platform -> Integer -> CmmExpr -> Width -> Integer -> CmmExpr +signedQuotRemHelper platform n x rep p = CmmMachOp (MO_Add rep) [x, x2] + where + bits = fromIntegral (widthInBits rep) - 1 + shr = if p == 1 then MO_U_Shr rep else MO_S_Shr rep + x1 = CmmMachOp shr [x, CmmLit (CmmInt bits $ wordWidth platform)] + x2 = if p == 1 then x1 else + CmmMachOp (MO_And rep) [x1, CmmLit (CmmInt (n-1) rep)] + +{- Note: [Division by constants] + +Integer division is floor(n / d), the goal is to find m,p +such that floor((m * n) / 2^p) = floor(n / d). + +The idea being: n/d = n * (1/d). But we cannot store 1/d in an integer without +some error, so we choose some 2^p / d such that the error ends up small and +thus vanishes when we divide by 2^p again. + +The algorithm below to generate these numbers is taken from Hacker's Delight +Second Edition Chapter 10 "Integer division by constants". The chapter also +contains proof that this method does indeed produce correct results. + +However this is a much more literal interpretation of the algorithm, +which we can use because of the unbounded Integer type. Hacker's Delight +also provides a much more complex algorithm which computes these numbers +without the need to exceed the word size, but that is not necessary here. +-} + +generateDivisionBySigned :: Platform -> CmmConfig -> Width -> CmmExpr -> Integer -> Opt CmmExpr + +-- Sanity checks, division will generate incorrect results or undesirable code for these cases +-- cmmMachOpFoldM and cmmMachOpFoldOptM should have already handled these cases! +generateDivisionBySigned _ _ _ _ 0 = panic "generate signed division with 0" +generateDivisionBySigned _ _ _ _ 1 = panic "generate signed division with 1" +generateDivisionBySigned _ _ _ _ (-1) = panic "generate signed division with -1" +generateDivisionBySigned _ _ _ _ d | Just _ <- exactLog2 d = panic $ "generate signed division with " ++ show d + +generateDivisionBySigned platform _cfg rep n divisor = do + -- We only duplicate n' if we actually need to add/subtract it, so we may not need it in a register + n' <- if sign == 0 then pure n else intoRegister n resRep + + -- Set up mul2 + (shift', qExpr) <- mul2 n' + + -- add/subtract n if necessary + let qExpr' = case sign of + 1 -> CmmMachOp (MO_Add rep) [qExpr, n'] + -1 -> CmmMachOp (MO_Sub rep) [qExpr, n'] + _ -> qExpr + + qExpr'' <- intoRegister (cmmMachOpFold platform (MO_S_Shr rep) [qExpr', CmmLit $ CmmInt shift' wordRep]) resRep + + -- Lastly add the sign of the quotient to correct for negative results + pure $! cmmMachOpFold platform + (MO_Add rep) [qExpr'', cmmMachOpFold platform (MO_U_Shr rep) [qExpr'', CmmLit $ CmmInt (toInteger $ widthInBits rep - 1) wordRep]] + where + resRep = cmmBits rep + wordRep = wordWidth platform + (magic, sign, shift) = divisionMagicS rep divisor + -- generate the multiply with the magic number + mul2 n + -- Using mul2 for sub-word sizes regresses for signed integers only + | rep == wordWidth platform = do + (r1, r2, r3) <- (,,) <$> getUniqueM <*> getUniqueM <*> getUniqueM + let rg1 = LocalReg r1 resRep + resReg = LocalReg r2 resRep + rg3 = LocalReg r3 resRep + res <- CmmReg (CmmLocal resReg) <$ prependNode (CmmUnsafeForeignCall (PrimTarget (MO_S_Mul2 rep)) [rg1, resReg, rg3] [n, CmmLit $ CmmInt magic rep]) + pure (shift, res) + -- widen the register and multiply without the MUL2 instruction + -- if we don't need an additional add after this we can combine the shifts + | otherwise = pure (if sign == 0 then 0 else shift, res) + where + wordRep = wordWidth platform + -- (n * magic) >> widthInBits + (if sign == 0 then shift else 0) -- With conversion in between to not overflow + res = cmmMachOpFold platform (MO_SS_Conv wordRep rep) + [ cmmMachOpFold platform (MO_S_Shr wordRep) + [ cmmMachOpFold platform (MO_Mul wordRep) + [ cmmMachOpFold platform (MO_SS_Conv rep wordRep) [n] + , CmmLit $ CmmInt magic wordRep + ] + -- Check if we need to generate an add/subtract later. If not we can combine this with the postshift + , CmmLit $ CmmInt ((if sign == 0 then toInteger shift else 0) + (toInteger $ widthInBits rep)) wordRep + ] + ] + +-- See hackers delight for how and why this works (chapter in note [Division by constants]) +divisionMagicS :: Width -> Integer -> (Integer, Integer, Integer) +divisionMagicS rep divisor = (magic, sign, toInteger $ p - wSz) + where + sign = if divisor > 0 + then if magic < 0 then 1 else 0 + else if magic < 0 then 0 else -1 + wSz = widthInBits rep + ad = abs divisor + t = (1 `shiftL` (wSz - 1)) + if divisor > 0 then 0 else 1 + anc = t - 1 - rem t ad + go p' + | twoP > anc * (ad - rem twoP ad) = p' + | otherwise = go (p' + 1) + where twoP = 1 `shiftL` p' + p = go wSz + am = (twoP + ad - rem twoP ad) `quot` ad + where twoP = 1 `shiftL` p + magic = narrowS rep $ if divisor > 0 then am else -am + +generateDivisionByUnsigned :: Platform -> CmmConfig -> Width -> CmmExpr -> Integer -> Opt CmmExpr +-- Sanity checks, division will generate incorrect results or undesirable code for these cases +-- cmmMachOpFoldM and cmmMachOpFoldOptM should have already handled these cases! +generateDivisionByUnsigned _ _ _ _ 0 = panic "generate signed division with 0" +generateDivisionByUnsigned _ _ _ _ 1 = panic "generate signed division with 1" +generateDivisionByUnsigned _ _ _ _ d | Just _ <- exactLog2 d = panic $ "generate signed division with " ++ show d + +generateDivisionByUnsigned platform cfg rep n divisor = do + -- We only duplicate n' if we actually need to add/subtract it, so we may not need it in a register + n' <- if not needsAdd -- Invariant: We also never preshift if we need an add, thus we don't need n in a register + then pure $! cmmMachOpFold platform (MO_U_Shr rep) [n, CmmLit $ CmmInt preShift wordRep] + else intoRegister n resRep + + -- Set up mul2 + (postShift', qExpr) <- mul2 n' + + -- add/subtract n if necessary + let qExpr' = if needsAdd + -- This is qExpr + (n - qExpr) / 2 = (qExpr + n) / 2 but with a guarantee that it'll not overflow + then cmmMachOpFold platform (MO_Add rep) + [ cmmMachOpFold platform (MO_U_Shr rep) + [ cmmMachOpFold platform (MO_Sub rep) [n', qExpr] + , CmmLit $ CmmInt 1 wordRep + ] + , qExpr + ] + else qExpr + -- If we already divided by 2 in the add, remember to shift one bit less + -- Hacker's Delight, Edition 2 Page 234: postShift > 0 if we needed an add, except if the divisor + -- is 1, which we checked for above + finalShift = if needsAdd then postShift' - 1 else postShift' + + -- apply the final postShift + pure $! cmmMachOpFold platform (MO_U_Shr rep) [qExpr', CmmLit $ CmmInt finalShift wordRep] + where + resRep = cmmBits rep + wordRep = wordWidth platform + (preShift, magic, needsAdd, postShift) = + let withPre = divisionMagicU rep True divisor + noPre = divisionMagicU rep False divisor + in case (withPre, noPre) of + -- Use whatever does not cause us to take the expensive case + ((_, _, False, _), (_, _, True, _)) -> withPre + -- If we cannot avoid the expensive case, don't bother with the pre shift + _ -> noPre + -- generate the multiply with the magic number + mul2 n + | rep == wordWidth platform || (cmmAllowMul2 cfg && needsAdd) = do + (r1, r2) <- (,) <$> getUniqueM <*> getUniqueM + let rg1 = LocalReg r1 resRep + resReg = LocalReg r2 resRep + res <- CmmReg (CmmLocal resReg) <$ prependNode (CmmUnsafeForeignCall (PrimTarget (MO_U_Mul2 rep)) [resReg, rg1] [n, CmmLit $ CmmInt magic rep]) + pure (postShift, res) + | otherwise = do + pure (if needsAdd then postShift else 0, res) + where + wordRep = wordWidth platform + -- (n * magic) >> widthInBits + (if sign == 0 then shift else 0) -- With conversion in between to not overflow + res = cmmMachOpFold platform (MO_UU_Conv wordRep rep) + [ cmmMachOpFold platform (MO_U_Shr wordRep) + [ cmmMachOpFold platform (MO_Mul wordRep) + [ cmmMachOpFold platform (MO_UU_Conv rep wordRep) [n] + , CmmLit $ CmmInt magic wordRep + ] + -- Check if we need to generate an add later. If not we can combine this with the postshift + , CmmLit $ CmmInt ((if needsAdd then 0 else postShift) + (toInteger $ widthInBits rep)) wordRep + ] + ] + +-- See hackers delight for how and why this works (chapter in note [Division by constants]) +-- The preshift isn't described there, but the idea is: +-- If a divisor d has n trailing zeros, then d is a multiple of 2^n. Since we want to divide x by d +-- we can also calculate (x / 2^n) / (d / 2^n) which may then not require an extra addition. +-- +-- The addition performs: quotient + dividend, but we need to avoid overflows, so we actually need to +-- calculate: quotient + (dividend - quotient) / 2 = (quotient + dividend) / 2 +-- Thus if the preshift can avoid all of this, we have 1 operation in place of 3. +-- +-- The decision to use the preshift is made somewhere else, here we only report if the addition is needed +divisionMagicU :: Width -> Bool -> Integer -> (Integer, Integer, Bool, Integer) +divisionMagicU rep doPreShift divisor = (toInteger zeros, magic, needsAdd, toInteger $ p - wSz) + where + wSz = widthInBits rep + zeros = if doPreShift then countTrailingZeros $ fromInteger @Word64 divisor else 0 + d = divisor `shiftR` zeros + ones = ((1 `shiftL` wSz) - 1) `shiftR` zeros + nc = ones - rem (ones - d) d + go p' + | twoP > nc * (d - 1 - rem (twoP - 1) d) = p' + | otherwise = go (p' + 1) + where twoP = 1 `shiftL` p' + p = go wSz + m = (twoP + d - 1 - rem (twoP - 1) d) `quot` d + where twoP = 1 `shiftL` p + needsAdd = d < 1 `shiftL` (p - wSz) + magic = if needsAdd then m - (ones + 1) else m + +-- ----------------------------------------------------------------------------- +-- Opt monad + +newtype Opt a = OptI { runOptI :: CmmConfig -> [CmmNode O O] -> UniqSM ([CmmNode O O], a) } + +-- | Pattern synonym for 'Opt', as described in Note [The one-shot state +-- monad trick]. +pattern Opt :: (CmmConfig -> [CmmNode O O] -> UniqSM ([CmmNode O O], a)) -> Opt a +pattern Opt f <- OptI f + where Opt f = OptI . oneShot $ \cfg -> oneShot $ \out -> f cfg out +{-# COMPLETE Opt #-} + +runOpt :: CmmConfig -> Opt a -> UniqSM ([CmmNode O O], a) +runOpt cf (Opt g) = g cf [] + +getConfig :: Opt CmmConfig +getConfig = Opt $ \cf xs -> pure (xs, cf) + +instance Functor Opt where + fmap f (Opt g) = Opt $ \cf xs -> fmap (fmap f) (g cf xs) + +instance Applicative Opt where + pure a = Opt $ \_ xs -> pure (xs, a) + ff <*> fa = do + f <- ff + f <$> fa + +instance Monad Opt where + Opt g >>= f = Opt $ \cf xs -> do + (ys, a) <- g cf xs + runOptI (f a) cf ys + +instance MonadUnique Opt where + getUniqueSupplyM = Opt $ \_ xs -> (xs,) <$> getUniqueSupplyM + getUniqueM = Opt $ \_ xs -> (xs,) <$> getUniqueM + getUniquesM = Opt $ \_ xs -> (xs,) <$> getUniquesM + +mapForeignTargetOpt :: (CmmExpr -> Opt CmmExpr) -> ForeignTarget -> Opt ForeignTarget +mapForeignTargetOpt exp (ForeignTarget e c) = flip ForeignTarget c <$> exp e +mapForeignTargetOpt _ m@(PrimTarget _) = pure m + +wrapRecExpOpt :: (CmmExpr -> Opt CmmExpr) -> CmmExpr -> Opt CmmExpr +wrapRecExpOpt f (CmmMachOp op es) = traverse (wrapRecExpOpt f) es >>= f . CmmMachOp op +wrapRecExpOpt f (CmmLoad addr ty align) = wrapRecExpOpt f addr >>= \newAddr -> f (CmmLoad newAddr ty align) +wrapRecExpOpt f e = f e + +mapExpOpt :: (CmmExpr -> Opt CmmExpr) -> CmmNode e x -> Opt (CmmNode e x) +mapExpOpt _ f@(CmmEntry{}) = pure f +mapExpOpt _ m@(CmmComment _) = pure m +mapExpOpt _ m@(CmmTick _) = pure m +mapExpOpt f (CmmUnwind regs) = CmmUnwind <$> traverse (traverse (traverse f)) regs +mapExpOpt f (CmmAssign r e) = CmmAssign r <$> f e +mapExpOpt f (CmmStore addr e align) = CmmStore <$> f addr <*> f e <*> pure align +mapExpOpt f (CmmUnsafeForeignCall tgt fs as) = CmmUnsafeForeignCall <$> mapForeignTargetOpt f tgt <*> pure fs <*> traverse f as +mapExpOpt _ l@(CmmBranch _) = pure l +mapExpOpt f (CmmCondBranch e ti fi l) = f e >>= \newE -> pure (CmmCondBranch newE ti fi l) +mapExpOpt f (CmmSwitch e ids) = flip CmmSwitch ids <$> f e +mapExpOpt f n@CmmCall {cml_target=tgt} = f tgt >>= \newTgt -> pure n{cml_target = newTgt} +mapExpOpt f (CmmForeignCall tgt fs as succ ret_args updfr intrbl) + = do + newTgt <- mapForeignTargetOpt f tgt + newAs <- traverse f as + pure $ CmmForeignCall newTgt fs newAs succ ret_args updfr intrbl diff --git a/compiler/GHC/Cmm/Pipeline.hs b/compiler/GHC/Cmm/Pipeline.hs index 3bd48f9152ca..1828d3eed1ed 100644 --- a/compiler/GHC/Cmm/Pipeline.hs +++ b/compiler/GHC/Cmm/Pipeline.hs @@ -128,8 +128,11 @@ cpsTop logger platform cfg proc = ----------- Sink and inline assignments -------------------------------- g <- {-# SCC "sink" #-} -- See Note [Sinking after stack layout] - condPass (cmmOptSink cfg) (cmmSink platform) g - Opt_D_dump_cmm_sink "Sink assignments" + if cmmOptSink cfg + then runUniqSM $ cmmSink cfg g + else return g + dump Opt_D_dump_cmm_sink "Sink assignments" g + ------------- CAF analysis ---------------------------------------------- let cafEnv = {-# SCC "cafAnal" #-} cafAnal platform call_pps l g diff --git a/compiler/GHC/Cmm/Sink.hs b/compiler/GHC/Cmm/Sink.hs index 3fb2a0ff1d94..b193f479bccb 100644 --- a/compiler/GHC/Cmm/Sink.hs +++ b/compiler/GHC/Cmm/Sink.hs @@ -1,5 +1,6 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE MultiWayIf #-} module GHC.Cmm.Sink ( cmmSink @@ -19,6 +20,8 @@ import GHC.Platform.Regs import GHC.Platform import GHC.Types.Unique.FM +import GHC.Types.Unique.Supply +import GHC.Cmm.Config import qualified GHC.Data.Word64Set as Word64Set import Data.List (partition) @@ -150,9 +153,10 @@ type Assignments = [Assignment] -- y = e2 -- x = e1 -cmmSink :: Platform -> CmmGraph -> CmmGraph -cmmSink platform graph = ofBlockList (g_entry graph) $ sink mapEmpty $ blocks +cmmSink :: CmmConfig -> CmmGraph -> UniqSM CmmGraph +cmmSink cfg graph = ofBlockList (g_entry graph) <$> sink mapEmpty blocks where + platform = cmmPlatform cfg liveness = cmmLocalLivenessL platform graph getLive l = mapFindWithDefault emptyLRegSet l liveness @@ -160,11 +164,41 @@ cmmSink platform graph = ofBlockList (g_entry graph) $ sink mapEmpty $ blocks join_pts = findJoinPoints blocks - sink :: LabelMap Assignments -> [CmmBlock] -> [CmmBlock] - sink _ [] = [] - sink sunk (b:bs) = - -- pprTrace "sink" (ppr lbl) $ - blockJoin first final_middle final_last : sink sunk' bs + sink :: LabelMap Assignments -> [CmmBlock] -> UniqSM [CmmBlock] + sink _ [] = pure [] + sink sunk (b:bs) = do + -- Now sink and inline in this block + (prepend, last_fold) <- runOpt cfg $ constantFoldNode last + + (middle', assigs) <- walk cfg (ann_middles ++ annotate platform live_middle prepend) (mapFindWithDefault [] lbl sunk) + + let (final_last, assigs') = tryToInline platform live last_fold assigs + -- Now, drop any assignments that we will not sink any further. + (dropped_last, assigs'') = dropAssignments platform drop_if init_live_sets assigs' + drop_if :: (LocalReg, CmmExpr, AbsMem) + -> [LRegSet] -> (Bool, [LRegSet]) + drop_if a@(r,rhs,_) live_sets = (should_drop, live_sets') + where + should_drop = conflicts platform a final_last + || not (isTrivial platform rhs) && live_in_multi live_sets r + || r `elemLRegSet` live_in_joins + + live_sets' | should_drop = live_sets + | otherwise = map upd live_sets + + upd set | r `elemLRegSet` set = set `Word64Set.union` live_rhs + | otherwise = set + + live_rhs = foldRegsUsed platform (flip insertLRegSet) emptyLRegSet rhs + + final_middle = foldl' blockSnoc middle' dropped_last + + sunk' = mapUnion sunk $ + mapFromList [ (l, filterAssignments platform (getLive l) assigs'') + | l <- succs ] + + (blockJoin first final_middle final_last :) <$> sink sunk' bs + where lbl = entryLabel b (first, middle, last) = blockSplit b @@ -178,11 +212,6 @@ cmmSink platform graph = ofBlockList (g_entry graph) $ sink mapEmpty $ blocks live_middle = gen_killL platform last live ann_middles = annotate platform live_middle (blockToList middle) - -- Now sink and inline in this block - (middle', assigs) = walk platform ann_middles (mapFindWithDefault [] lbl sunk) - fold_last = constantFoldNode platform last - (final_last, assigs') = tryToInline platform live fold_last assigs - -- We cannot sink into join points (successors with more than -- one predecessor), so identify the join points and the set -- of registers live in them. @@ -200,31 +229,6 @@ cmmSink platform graph = ofBlockList (g_entry graph) $ sink mapEmpty $ blocks (_one:_two:_) -> True _ -> False - -- Now, drop any assignments that we will not sink any further. - (dropped_last, assigs'') = dropAssignments platform drop_if init_live_sets assigs' - - drop_if :: (LocalReg, CmmExpr, AbsMem) - -> [LRegSet] -> (Bool, [LRegSet]) - drop_if a@(r,rhs,_) live_sets = (should_drop, live_sets') - where - should_drop = conflicts platform a final_last - || not (isTrivial platform rhs) && live_in_multi live_sets r - || r `elemLRegSet` live_in_joins - - live_sets' | should_drop = live_sets - | otherwise = map upd live_sets - - upd set | r `elemLRegSet` set = set `Word64Set.union` live_rhs - | otherwise = set - - live_rhs = foldRegsUsed platform (flip insertLRegSet) emptyLRegSet rhs - - final_middle = foldl' blockSnoc middle' dropped_last - - sunk' = mapUnion sunk $ - mapFromList [ (l, filterAssignments platform (getLive l) assigs'') - | l <- succs ] - {- TODO: enable this later, when we have some good tests in place to measure the effect and tune it. @@ -299,7 +303,7 @@ filterAssignments platform live assigs = reverse (go assigs []) -- * a list of assignments that will be placed *after* that block. -- -walk :: Platform +walk :: CmmConfig -> [(LRegSet, CmmNode O O)] -- nodes of the block, annotated with -- the set of registers live *after* -- this node. @@ -309,36 +313,39 @@ walk :: Platform -- Earlier assignments may refer -- to later ones. - -> ( Block CmmNode O O -- The new block - , Assignments -- Assignments to sink further - ) + -> UniqSM ( Block CmmNode O O -- The new block + , Assignments -- Assignments to sink further + ) -walk platform nodes assigs = go nodes emptyBlock assigs +walk cfg nodes assigs = go nodes emptyBlock assigs where - go [] block as = (block, as) + platform = cmmPlatform cfg + go [] block as = pure (block, as) go ((live,node):ns) block as -- discard nodes representing dead assignment | shouldDiscard node live = go ns block as - -- sometimes only after simplification we can tell we can discard the node. - -- See Note [Discard simplified nodes] - | noOpAssignment node2 = go ns block as - -- Pick up interesting assignments - | Just a <- shouldSink platform node2 = go ns block (a : as1) - -- Try inlining, drop assignments and move on - | otherwise = go ns block' as' - where - -- Simplify node - node1 = constantFoldNode platform node - - -- Inline assignments - (node2, as1) = tryToInline platform live node1 as - - -- Drop any earlier assignments conflicting with node2 - (dropped, as') = dropAssignmentsSimple platform - (\a -> conflicts platform a node2) as1 - - -- Walk over the rest of the block. Includes dropped assignments - block' = foldl' blockSnoc block dropped `blockSnoc` node2 + | otherwise = do + (prepend, node1) <- runOpt cfg $ constantFoldNode node + if not (null prepend) + then go (annotate platform live (prepend ++ [node1]) ++ ns) block as + else do + let -- Inline assignments + (node2, as1) = tryToInline platform live node1 as + -- Drop any earlier assignments conflicting with node2 + (dropped, as') = dropAssignmentsSimple platform + (\a -> conflicts platform a node2) as1 + -- Walk over the rest of the block. Includes dropped assignments + block' = foldl' blockSnoc block dropped `blockSnoc` node2 + + (prepend2, node3) <- runOpt cfg $ constantFoldNode node2 + if | not (null prepend2) -> go (annotate platform live (prepend2 ++ [node3]) ++ ns) block as + -- sometimes only after simplification we can tell we can discard the node. + -- See Note [Discard simplified nodes] + | noOpAssignment node3 -> go ns block as + -- Pick up interesting assignments + | Just a <- shouldSink platform node3 -> go ns block (a : as1) + -- Try inlining, drop assignments and move on + | otherwise -> go ns block' as' {- Note [Discard simplified nodes] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -519,7 +526,7 @@ tryToInline platform liveAfter node assigs = {- Note [Keeping assignments mentioned in skipped RHSs] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - If we have to assignments: [z = y, y = e1] and we skip + If we have two assignments: [z = y, y = e1] and we skip z we *must* retain the assignment y = e1. This is because we might inline "z = y" into another node later on so we must ensure y is still defined at this point. diff --git a/compiler/GHC/Driver/Config/Cmm.hs b/compiler/GHC/Driver/Config/Cmm.hs index 0118022ab9f9..0cee96e4c3b9 100644 --- a/compiler/GHC/Driver/Config/Cmm.hs +++ b/compiler/GHC/Driver/Config/Cmm.hs @@ -26,9 +26,21 @@ initCmmConfig dflags = CmmConfig , cmmSplitProcPoints = not (backendSupportsUnsplitProcPoints (backend dflags)) || not (platformTablesNextToCode platform) || usingInconsistentPicReg + , cmmAllowMul2 = (ncg && x86ish) || llvm + , cmmOptConstDivision = not llvm } where platform = targetPlatform dflags usingInconsistentPicReg = case (platformArch platform, platformOS platform, positionIndependent dflags) of (ArchX86, OSDarwin, pic) -> pic _ -> False + -- Copied from StgToCmm + (ncg, llvm) = case backendPrimitiveImplementation (backend dflags) of + GenericPrimitives -> (False, False) + NcgPrimitives -> (True, False) + LlvmPrimitives -> (False, True) + JSPrimitives -> (False, False) + x86ish = case platformArch platform of + ArchX86 -> True + ArchX86_64 -> True + _ -> False diff --git a/compiler/GHC/StgToCmm/Prim.hs b/compiler/GHC/StgToCmm/Prim.hs index 90e5f24f8265..c19377de807e 100644 --- a/compiler/GHC/StgToCmm/Prim.hs +++ b/compiler/GHC/StgToCmm/Prim.hs @@ -1553,27 +1553,27 @@ emitPrimOp cfg primop = DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) IntQuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_S_QuotRem (wordWidth platform)) else Right (genericIntQuotRemOp (wordWidth platform)) Int8QuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_S_QuotRem W8) else Right (genericIntQuotRemOp W8) Int16QuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_S_QuotRem W16) else Right (genericIntQuotRemOp W16) Int32QuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_S_QuotRem W32) else Right (genericIntQuotRemOp W32) WordQuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_U_QuotRem (wordWidth platform)) else Right (genericWordQuotRemOp (wordWidth platform)) @@ -1583,17 +1583,17 @@ emitPrimOp cfg primop = else Right (genericWordQuotRem2Op platform) Word8QuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_U_QuotRem W8) else Right (genericWordQuotRemOp W8) Word16QuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_U_QuotRem W16) else Right (genericWordQuotRemOp W16) Word32QuotRemOp -> \args -> opCallishHandledLater args $ - if allowQuotRem && not (quotRemCanBeOptimized args) + if allowQuotRem then Left (MO_U_QuotRem W32) else Right (genericWordQuotRemOp W32) @@ -1827,23 +1827,6 @@ emitPrimOp cfg primop = pure $ map (CmmReg . CmmLocal) regs alwaysExternal = \_ -> PrimopCmmEmit_External - -- Note [QuotRem optimization] - -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -- `quot` and `rem` with constant divisor can be implemented with fast bit-ops - -- (shift, .&.). - -- - -- Currently we only support optimization (performed in GHC.Cmm.Opt) when the - -- constant is a power of 2. #9041 tracks the implementation of the general - -- optimization. - -- - -- `quotRem` can be optimized in the same way. However as it returns two values, - -- it is implemented as a "callish" primop which is harder to match and - -- to transform later on. For simplicity, the current implementation detects cases - -- that can be optimized (see `quotRemCanBeOptimized`) and converts STG quotRem - -- primop into two CMM quot and rem primops. - quotRemCanBeOptimized = \case - [_, CmmLit (CmmInt n _) ] -> isJust (exactLog2 n) - _ -> False allowQuotRem = stgToCmmAllowQuotRemInstr cfg allowQuotRem2 = stgToCmmAllowQuotRem2 cfg diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index dd6c42093329..6dc4c3bff9b0 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -83,3 +83,4 @@ test('T22282', normal, compile_and_run, ['']) test('T22671', js_fragile(24259), compile_and_run, ['']) test('foundation', [when(js_arch(), run_timeout_multiplier(2)), js_fragile(24259)], compile_and_run, ['-O -package transformers']) test('T24066', normal, compile_and_run, ['']) +test('div01', normal, compile_and_run, ['']) diff --git a/testsuite/tests/numeric/should_run/div01.hs b/testsuite/tests/numeric/should_run/div01.hs new file mode 100644 index 000000000000..cc1acfd77819 --- /dev/null +++ b/testsuite/tests/numeric/should_run/div01.hs @@ -0,0 +1,109 @@ +-- !!! Testing Int and Word and specifically integer division by constants +module Main(main) where + +import Data.Int +import Data.Word +import Control.Monad (when, void) +import Data.Bits (Bits, isSigned) + +main :: IO () +main = test + +test :: IO () +test = do + testIntlike "Int" (0::Int ) + testIntlike "Int8" (0::Int8 ) + testIntlike "Int16" (0::Int16) + testIntlike "Int32" (0::Int32) + testIntlike "Int64" (0::Int64) + + testIntlike "Word" (0::Word ) + testIntlike "Word8" (0::Word8 ) + testIntlike "Word16" (0::Word16) + testIntlike "Word32" (0::Word32) + testIntlike "Word64" (0::Word64) + +testIntlike :: (Bounded a, Integral a, Show a, Bits a) => String -> a -> IO () +testIntlike name zero = do + putStrLn $ "--------------------------------" + putStrLn $ "--Testing " ++ name + putStrLn $ "--------------------------------" + -- 1 + putStrLn "divide by 1" + testWith (1 `asTypeOf` zero) + + -- Powers of 2 + putStrLn "divide by 2" + testWith (2 `asTypeOf` zero) + putStrLn "divide by 4" + testWith (4 `asTypeOf` zero) + -- Positive constants + putStrLn "divide by 3" + testWith (3 `asTypeOf` zero) + putStrLn "divide by 5" + testWith (5 `asTypeOf` zero) + putStrLn "divide by 7" + testWith (7 `asTypeOf` zero) + putStrLn "divide by 14" + testWith (14 `asTypeOf` zero) + putStrLn "divide by 25" + testWith (25 `asTypeOf` zero) + putStrLn "divide by maxBound" + testWith (maxBound `asTypeOf` zero) + putStrLn "divide by (maxBound - 1)" + testWith ((maxBound - 1) `asTypeOf` zero) + + when (isSigned zero) $ do + -- (-1) + putStrLn "divide by -1" + testWith ((-1) `asTypeOf` zero) + + -- Negative powers of 2 + putStrLn "divide by -2" + testWith ((-2) `asTypeOf` zero) + putStrLn "divide by -4" + testWith ((-4) `asTypeOf` zero) + + -- Negative constants + putStrLn "divide by -3" + testWith ((-3) `asTypeOf` zero) + putStrLn "divide by -5" + testWith ((-5) `asTypeOf` zero) + putStrLn "divide by -7" + testWith ((-7) `asTypeOf` zero) + putStrLn "divide by -14" + testWith ((-14) `asTypeOf` zero) + putStrLn "divide by -25" + testWith ((-25) `asTypeOf` zero) + + -- minBound + putStrLn "divide by minBound" + testWith (minBound `asTypeOf` zero) + putStrLn "divide by (minBound + 1)" + testWith ((minBound + 1) `asTypeOf` zero) + where + testWith d = void $ traverse qr (samples d) + where + qr x = do + print x + print $ x `quotRem` d + print $ x `quot` d + print $ x `rem` d + putStrLn "#" + {-# INLINE qr #-} + {-# INLINE testWith #-} + samples d = + [maxBound] + ++ plusMinusOne 0 + -- avoid quot minBound + -- ghc defines quot minBound (-1) = error and has overflow on quot<Int<N>># as undefined behavior + ++ (if d == (-1) then [] else plusMinusOne largest) + ++ plusMinusOne large + ++ plusMinusOne small + ++ plusMinusOne smallest + where + plusMinusOne x = [x - 1, x, x + 1] + largest = d * (maxBound `quot` d) + large = d * ((maxBound `quot` 2) `quot` d) + small = d * 4 + smallest = d diff --git a/testsuite/tests/numeric/should_run/div01.stdout b/testsuite/tests/numeric/should_run/div01.stdout new file mode 100644 index 000000000000..1c71891d5199 --- /dev/null +++ b/testsuite/tests/numeric/should_run/div01.stdout @@ -0,0 +1,12030 @@ +-------------------------------- +--Testing Int +-------------------------------- +divide by 1 +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +9223372036854775806 +(9223372036854775806,0) +9223372036854775806 +0 +# +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +-9223372036854775808 +(-9223372036854775808,0) +-9223372036854775808 +0 +# +4611686018427387902 +(4611686018427387902,0) +4611686018427387902 +0 +# +4611686018427387903 +(4611686018427387903,0) +4611686018427387903 +0 +# +4611686018427387904 +(4611686018427387904,0) +4611686018427387904 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(4611686018427387902,1) +4611686018427387902 +1 +# +9223372036854775806 +(4611686018427387903,0) +4611686018427387903 +0 +# +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +4611686018427387901 +(2305843009213693950,1) +2305843009213693950 +1 +# +4611686018427387902 +(2305843009213693951,0) +2305843009213693951 +0 +# +4611686018427387903 +(2305843009213693951,1) +2305843009213693951 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +9223372036854775807 +(2305843009213693951,3) +2305843009213693951 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775803 +(2305843009213693950,3) +2305843009213693950 +3 +# +9223372036854775804 +(2305843009213693951,0) +2305843009213693951 +0 +# +9223372036854775805 +(2305843009213693951,1) +2305843009213693951 +1 +# +4611686018427387899 +(1152921504606846974,3) +1152921504606846974 +3 +# +4611686018427387900 +(1152921504606846975,0) +1152921504606846975 +0 +# +4611686018427387901 +(1152921504606846975,1) +1152921504606846975 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(3074457345618258601,2) +3074457345618258601 +2 +# +9223372036854775806 +(3074457345618258602,0) +3074457345618258602 +0 +# +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +4611686018427387902 +(1537228672809129300,2) +1537228672809129300 +2 +# +4611686018427387903 +(1537228672809129301,0) +1537228672809129301 +0 +# +4611686018427387904 +(1537228672809129301,1) +1537228672809129301 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +9223372036854775807 +(1844674407370955161,2) +1844674407370955161 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775804 +(1844674407370955160,4) +1844674407370955160 +4 +# +9223372036854775805 +(1844674407370955161,0) +1844674407370955161 +0 +# +9223372036854775806 +(1844674407370955161,1) +1844674407370955161 +1 +# +4611686018427387899 +(922337203685477579,4) +922337203685477579 +4 +# +4611686018427387900 +(922337203685477580,0) +922337203685477580 +0 +# +4611686018427387901 +(922337203685477580,1) +922337203685477580 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(1317624576693539400,6) +1317624576693539400 +6 +# +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +-9223372036854775808 +(-1317624576693539401,-1) +-1317624576693539401 +-1 +# +4611686018427387899 +(658812288346769699,6) +658812288346769699 +6 +# +4611686018427387900 +(658812288346769700,0) +658812288346769700 +0 +# +4611686018427387901 +(658812288346769700,1) +658812288346769700 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +9223372036854775807 +(658812288346769700,7) +658812288346769700 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(658812288346769699,13) +658812288346769699 +13 +# +9223372036854775800 +(658812288346769700,0) +658812288346769700 +0 +# +9223372036854775801 +(658812288346769700,1) +658812288346769700 +1 +# +4611686018427387899 +(329406144173384849,13) +329406144173384849 +13 +# +4611686018427387900 +(329406144173384850,0) +329406144173384850 +0 +# +4611686018427387901 +(329406144173384850,1) +329406144173384850 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +9223372036854775807 +(368934881474191032,7) +368934881474191032 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(368934881474191031,24) +368934881474191031 +24 +# +9223372036854775800 +(368934881474191032,0) +368934881474191032 +0 +# +9223372036854775801 +(368934881474191032,1) +368934881474191032 +1 +# +4611686018427387899 +(184467440737095515,24) +184467440737095515 +24 +# +4611686018427387900 +(184467440737095516,0) +184467440737095516 +0 +# +4611686018427387901 +(184467440737095516,1) +184467440737095516 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +9223372036854775807 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775808 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775808 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +9223372036854775807 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(0,9223372036854775805) +0 +9223372036854775805 +# +9223372036854775806 +(1,0) +1 +0 +# +9223372036854775807 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +9223372036854775805 +(0,9223372036854775805) +0 +9223372036854775805 +# +9223372036854775806 +(1,0) +1 +0 +# +9223372036854775807 +(1,1) +1 +1 +# +divide by -1 +9223372036854775807 +(-9223372036854775807,0) +-9223372036854775807 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +4611686018427387902 +(-4611686018427387902,0) +-4611686018427387902 +0 +# +4611686018427387903 +(-4611686018427387903,0) +-4611686018427387903 +0 +# +4611686018427387904 +(-4611686018427387904,0) +-4611686018427387904 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +9223372036854775807 +(-4611686018427387903,1) +-4611686018427387903 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(-4611686018427387902,1) +-4611686018427387902 +1 +# +9223372036854775806 +(-4611686018427387903,0) +-4611686018427387903 +0 +# +9223372036854775807 +(-4611686018427387903,1) +-4611686018427387903 +1 +# +4611686018427387901 +(-2305843009213693950,1) +-2305843009213693950 +1 +# +4611686018427387902 +(-2305843009213693951,0) +-2305843009213693951 +0 +# +4611686018427387903 +(-2305843009213693951,1) +-2305843009213693951 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +9223372036854775807 +(-2305843009213693951,3) +-2305843009213693951 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775803 +(-2305843009213693950,3) +-2305843009213693950 +3 +# +9223372036854775804 +(-2305843009213693951,0) +-2305843009213693951 +0 +# +9223372036854775805 +(-2305843009213693951,1) +-2305843009213693951 +1 +# +4611686018427387899 +(-1152921504606846974,3) +-1152921504606846974 +3 +# +4611686018427387900 +(-1152921504606846975,0) +-1152921504606846975 +0 +# +4611686018427387901 +(-1152921504606846975,1) +-1152921504606846975 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +9223372036854775807 +(-3074457345618258602,1) +-3074457345618258602 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(-3074457345618258601,2) +-3074457345618258601 +2 +# +9223372036854775806 +(-3074457345618258602,0) +-3074457345618258602 +0 +# +9223372036854775807 +(-3074457345618258602,1) +-3074457345618258602 +1 +# +4611686018427387902 +(-1537228672809129300,2) +-1537228672809129300 +2 +# +4611686018427387903 +(-1537228672809129301,0) +-1537228672809129301 +0 +# +4611686018427387904 +(-1537228672809129301,1) +-1537228672809129301 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +9223372036854775807 +(-1844674407370955161,2) +-1844674407370955161 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775804 +(-1844674407370955160,4) +-1844674407370955160 +4 +# +9223372036854775805 +(-1844674407370955161,0) +-1844674407370955161 +0 +# +9223372036854775806 +(-1844674407370955161,1) +-1844674407370955161 +1 +# +4611686018427387899 +(-922337203685477579,4) +-922337203685477579 +4 +# +4611686018427387900 +(-922337203685477580,0) +-922337203685477580 +0 +# +4611686018427387901 +(-922337203685477580,1) +-922337203685477580 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +9223372036854775807 +(-1317624576693539401,0) +-1317624576693539401 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(-1317624576693539400,6) +-1317624576693539400 +6 +# +9223372036854775807 +(-1317624576693539401,0) +-1317624576693539401 +0 +# +-9223372036854775808 +(1317624576693539401,-1) +1317624576693539401 +-1 +# +4611686018427387899 +(-658812288346769699,6) +-658812288346769699 +6 +# +4611686018427387900 +(-658812288346769700,0) +-658812288346769700 +0 +# +4611686018427387901 +(-658812288346769700,1) +-658812288346769700 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +9223372036854775807 +(-658812288346769700,7) +-658812288346769700 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(-658812288346769699,13) +-658812288346769699 +13 +# +9223372036854775800 +(-658812288346769700,0) +-658812288346769700 +0 +# +9223372036854775801 +(-658812288346769700,1) +-658812288346769700 +1 +# +4611686018427387899 +(-329406144173384849,13) +-329406144173384849 +13 +# +4611686018427387900 +(-329406144173384850,0) +-329406144173384850 +0 +# +4611686018427387901 +(-329406144173384850,1) +-329406144173384850 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +9223372036854775807 +(-368934881474191032,7) +-368934881474191032 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(-368934881474191031,24) +-368934881474191031 +24 +# +9223372036854775800 +(-368934881474191032,0) +-368934881474191032 +0 +# +9223372036854775801 +(-368934881474191032,1) +-368934881474191032 +1 +# +4611686018427387899 +(-184467440737095515,24) +-184467440737095515 +24 +# +4611686018427387900 +(-184467440737095516,0) +-184467440737095516 +0 +# +4611686018427387901 +(-184467440737095516,1) +-184467440737095516 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +9223372036854775807 +(0,9223372036854775807) +0 +9223372036854775807 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775807 +(0,9223372036854775807) +0 +9223372036854775807 +# +-9223372036854775808 +(1,0) +1 +0 +# +-9223372036854775807 +(0,-9223372036854775807) +0 +-9223372036854775807 +# +divide by (minBound + 1) +9223372036854775807 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(-1,0) +-1 +0 +# +-9223372036854775808 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-9223372036854775808 +(1,-1) +1 +-1 +# +-9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775806 +(0,-9223372036854775806) +0 +-9223372036854775806 +# +-------------------------------- +--Testing Int8 +-------------------------------- +divide by 1 +127 +(127,0) +127 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +126 +(126,0) +126 +0 +# +127 +(127,0) +127 +0 +# +-128 +(-128,0) +-128 +0 +# +62 +(62,0) +62 +0 +# +63 +(63,0) +63 +0 +# +64 +(64,0) +64 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +127 +(63,1) +63 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(62,1) +62 +1 +# +126 +(63,0) +63 +0 +# +127 +(63,1) +63 +1 +# +61 +(30,1) +30 +1 +# +62 +(31,0) +31 +0 +# +63 +(31,1) +31 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +127 +(31,3) +31 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +123 +(30,3) +30 +3 +# +124 +(31,0) +31 +0 +# +125 +(31,1) +31 +1 +# +59 +(14,3) +14 +3 +# +60 +(15,0) +15 +0 +# +61 +(15,1) +15 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +127 +(42,1) +42 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(41,2) +41 +2 +# +126 +(42,0) +42 +0 +# +127 +(42,1) +42 +1 +# +62 +(20,2) +20 +2 +# +63 +(21,0) +21 +0 +# +64 +(21,1) +21 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +127 +(25,2) +25 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(24,4) +24 +4 +# +125 +(25,0) +25 +0 +# +126 +(25,1) +25 +1 +# +59 +(11,4) +11 +4 +# +60 +(12,0) +12 +0 +# +61 +(12,1) +12 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +127 +(18,1) +18 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(17,6) +17 +6 +# +126 +(18,0) +18 +0 +# +127 +(18,1) +18 +1 +# +62 +(8,6) +8 +6 +# +63 +(9,0) +9 +0 +# +64 +(9,1) +9 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +127 +(9,1) +9 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(8,13) +8 +13 +# +126 +(9,0) +9 +0 +# +127 +(9,1) +9 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +127 +(5,2) +5 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(4,24) +4 +24 +# +125 +(5,0) +5 +0 +# +126 +(5,1) +5 +1 +# +49 +(1,24) +1 +24 +# +50 +(2,0) +2 +0 +# +51 +(2,1) +2 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +127 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +126 +(0,126) +0 +126 +# +127 +(1,0) +1 +0 +# +-128 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +126 +(0,126) +0 +126 +# +127 +(1,0) +1 +0 +# +-128 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +127 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(0,125) +0 +125 +# +126 +(1,0) +1 +0 +# +127 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +125 +(0,125) +0 +125 +# +126 +(1,0) +1 +0 +# +127 +(1,1) +1 +1 +# +divide by -1 +127 +(-127,0) +-127 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +62 +(-62,0) +-62 +0 +# +63 +(-63,0) +-63 +0 +# +64 +(-64,0) +-64 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +127 +(-63,1) +-63 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-62,1) +-62 +1 +# +126 +(-63,0) +-63 +0 +# +127 +(-63,1) +-63 +1 +# +61 +(-30,1) +-30 +1 +# +62 +(-31,0) +-31 +0 +# +63 +(-31,1) +-31 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +127 +(-31,3) +-31 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +123 +(-30,3) +-30 +3 +# +124 +(-31,0) +-31 +0 +# +125 +(-31,1) +-31 +1 +# +59 +(-14,3) +-14 +3 +# +60 +(-15,0) +-15 +0 +# +61 +(-15,1) +-15 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +127 +(-42,1) +-42 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-41,2) +-41 +2 +# +126 +(-42,0) +-42 +0 +# +127 +(-42,1) +-42 +1 +# +62 +(-20,2) +-20 +2 +# +63 +(-21,0) +-21 +0 +# +64 +(-21,1) +-21 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +127 +(-25,2) +-25 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(-24,4) +-24 +4 +# +125 +(-25,0) +-25 +0 +# +126 +(-25,1) +-25 +1 +# +59 +(-11,4) +-11 +4 +# +60 +(-12,0) +-12 +0 +# +61 +(-12,1) +-12 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +127 +(-18,1) +-18 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-17,6) +-17 +6 +# +126 +(-18,0) +-18 +0 +# +127 +(-18,1) +-18 +1 +# +62 +(-8,6) +-8 +6 +# +63 +(-9,0) +-9 +0 +# +64 +(-9,1) +-9 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +127 +(-9,1) +-9 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-8,13) +-8 +13 +# +126 +(-9,0) +-9 +0 +# +127 +(-9,1) +-9 +1 +# +55 +(-3,13) +-3 +13 +# +56 +(-4,0) +-4 +0 +# +57 +(-4,1) +-4 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +127 +(-5,2) +-5 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(-4,24) +-4 +24 +# +125 +(-5,0) +-5 +0 +# +126 +(-5,1) +-5 +1 +# +49 +(-1,24) +-1 +24 +# +50 +(-2,0) +-2 +0 +# +51 +(-2,1) +-2 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +127 +(0,127) +0 +127 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +127 +(0,127) +0 +127 +# +-128 +(1,0) +1 +0 +# +-127 +(0,-127) +0 +-127 +# +divide by (minBound + 1) +127 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +126 +(0,126) +0 +126 +# +127 +(-1,0) +-1 +0 +# +-128 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-128 +(1,-1) +1 +-1 +# +-127 +(1,0) +1 +0 +# +-126 +(0,-126) +0 +-126 +# +-------------------------------- +--Testing Int16 +-------------------------------- +divide by 1 +32767 +(32767,0) +32767 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +32766 +(32766,0) +32766 +0 +# +32767 +(32767,0) +32767 +0 +# +-32768 +(-32768,0) +-32768 +0 +# +16382 +(16382,0) +16382 +0 +# +16383 +(16383,0) +16383 +0 +# +16384 +(16384,0) +16384 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +32767 +(16383,1) +16383 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(16382,1) +16382 +1 +# +32766 +(16383,0) +16383 +0 +# +32767 +(16383,1) +16383 +1 +# +16381 +(8190,1) +8190 +1 +# +16382 +(8191,0) +8191 +0 +# +16383 +(8191,1) +8191 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +32767 +(8191,3) +8191 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32763 +(8190,3) +8190 +3 +# +32764 +(8191,0) +8191 +0 +# +32765 +(8191,1) +8191 +1 +# +16379 +(4094,3) +4094 +3 +# +16380 +(4095,0) +4095 +0 +# +16381 +(4095,1) +4095 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +32767 +(10922,1) +10922 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(10921,2) +10921 +2 +# +32766 +(10922,0) +10922 +0 +# +32767 +(10922,1) +10922 +1 +# +16382 +(5460,2) +5460 +2 +# +16383 +(5461,0) +5461 +0 +# +16384 +(5461,1) +5461 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +32767 +(6553,2) +6553 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32764 +(6552,4) +6552 +4 +# +32765 +(6553,0) +6553 +0 +# +32766 +(6553,1) +6553 +1 +# +16379 +(3275,4) +3275 +4 +# +16380 +(3276,0) +3276 +0 +# +16381 +(3276,1) +3276 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +32767 +(4681,0) +4681 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(4680,6) +4680 +6 +# +32767 +(4681,0) +4681 +0 +# +-32768 +(-4681,-1) +-4681 +-1 +# +16379 +(2339,6) +2339 +6 +# +16380 +(2340,0) +2340 +0 +# +16381 +(2340,1) +2340 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +32767 +(2340,7) +2340 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32759 +(2339,13) +2339 +13 +# +32760 +(2340,0) +2340 +0 +# +32761 +(2340,1) +2340 +1 +# +16379 +(1169,13) +1169 +13 +# +16380 +(1170,0) +1170 +0 +# +16381 +(1170,1) +1170 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +32767 +(1310,17) +1310 +17 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32749 +(1309,24) +1309 +24 +# +32750 +(1310,0) +1310 +0 +# +32751 +(1310,1) +1310 +1 +# +16374 +(654,24) +654 +24 +# +16375 +(655,0) +655 +0 +# +16376 +(655,1) +655 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +32767 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(0,32766) +0 +32766 +# +32767 +(1,0) +1 +0 +# +-32768 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +32766 +(0,32766) +0 +32766 +# +32767 +(1,0) +1 +0 +# +-32768 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +32767 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(0,32765) +0 +32765 +# +32766 +(1,0) +1 +0 +# +32767 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +32765 +(0,32765) +0 +32765 +# +32766 +(1,0) +1 +0 +# +32767 +(1,1) +1 +1 +# +divide by -1 +32767 +(-32767,0) +-32767 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +16382 +(-16382,0) +-16382 +0 +# +16383 +(-16383,0) +-16383 +0 +# +16384 +(-16384,0) +-16384 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +32767 +(-16383,1) +-16383 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(-16382,1) +-16382 +1 +# +32766 +(-16383,0) +-16383 +0 +# +32767 +(-16383,1) +-16383 +1 +# +16381 +(-8190,1) +-8190 +1 +# +16382 +(-8191,0) +-8191 +0 +# +16383 +(-8191,1) +-8191 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +32767 +(-8191,3) +-8191 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32763 +(-8190,3) +-8190 +3 +# +32764 +(-8191,0) +-8191 +0 +# +32765 +(-8191,1) +-8191 +1 +# +16379 +(-4094,3) +-4094 +3 +# +16380 +(-4095,0) +-4095 +0 +# +16381 +(-4095,1) +-4095 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +32767 +(-10922,1) +-10922 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(-10921,2) +-10921 +2 +# +32766 +(-10922,0) +-10922 +0 +# +32767 +(-10922,1) +-10922 +1 +# +16382 +(-5460,2) +-5460 +2 +# +16383 +(-5461,0) +-5461 +0 +# +16384 +(-5461,1) +-5461 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +32767 +(-6553,2) +-6553 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32764 +(-6552,4) +-6552 +4 +# +32765 +(-6553,0) +-6553 +0 +# +32766 +(-6553,1) +-6553 +1 +# +16379 +(-3275,4) +-3275 +4 +# +16380 +(-3276,0) +-3276 +0 +# +16381 +(-3276,1) +-3276 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +32767 +(-4681,0) +-4681 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(-4680,6) +-4680 +6 +# +32767 +(-4681,0) +-4681 +0 +# +-32768 +(4681,-1) +4681 +-1 +# +16379 +(-2339,6) +-2339 +6 +# +16380 +(-2340,0) +-2340 +0 +# +16381 +(-2340,1) +-2340 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +32767 +(-2340,7) +-2340 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32759 +(-2339,13) +-2339 +13 +# +32760 +(-2340,0) +-2340 +0 +# +32761 +(-2340,1) +-2340 +1 +# +16379 +(-1169,13) +-1169 +13 +# +16380 +(-1170,0) +-1170 +0 +# +16381 +(-1170,1) +-1170 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +32767 +(-1310,17) +-1310 +17 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32749 +(-1309,24) +-1309 +24 +# +32750 +(-1310,0) +-1310 +0 +# +32751 +(-1310,1) +-1310 +1 +# +16374 +(-654,24) +-654 +24 +# +16375 +(-655,0) +-655 +0 +# +16376 +(-655,1) +-655 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +32767 +(0,32767) +0 +32767 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32767 +(0,32767) +0 +32767 +# +-32768 +(1,0) +1 +0 +# +-32767 +(0,-32767) +0 +-32767 +# +divide by (minBound + 1) +32767 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(0,32766) +0 +32766 +# +32767 +(-1,0) +-1 +0 +# +-32768 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-32768 +(1,-1) +1 +-1 +# +-32767 +(1,0) +1 +0 +# +-32766 +(0,-32766) +0 +-32766 +# +-------------------------------- +--Testing Int32 +-------------------------------- +divide by 1 +2147483647 +(2147483647,0) +2147483647 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2147483646 +(2147483646,0) +2147483646 +0 +# +2147483647 +(2147483647,0) +2147483647 +0 +# +-2147483648 +(-2147483648,0) +-2147483648 +0 +# +1073741822 +(1073741822,0) +1073741822 +0 +# +1073741823 +(1073741823,0) +1073741823 +0 +# +1073741824 +(1073741824,0) +1073741824 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +2147483647 +(1073741823,1) +1073741823 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(1073741822,1) +1073741822 +1 +# +2147483646 +(1073741823,0) +1073741823 +0 +# +2147483647 +(1073741823,1) +1073741823 +1 +# +1073741821 +(536870910,1) +536870910 +1 +# +1073741822 +(536870911,0) +536870911 +0 +# +1073741823 +(536870911,1) +536870911 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +2147483647 +(536870911,3) +536870911 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483643 +(536870910,3) +536870910 +3 +# +2147483644 +(536870911,0) +536870911 +0 +# +2147483645 +(536870911,1) +536870911 +1 +# +1073741819 +(268435454,3) +268435454 +3 +# +1073741820 +(268435455,0) +268435455 +0 +# +1073741821 +(268435455,1) +268435455 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +2147483647 +(715827882,1) +715827882 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(715827881,2) +715827881 +2 +# +2147483646 +(715827882,0) +715827882 +0 +# +2147483647 +(715827882,1) +715827882 +1 +# +1073741822 +(357913940,2) +357913940 +2 +# +1073741823 +(357913941,0) +357913941 +0 +# +1073741824 +(357913941,1) +357913941 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +2147483647 +(429496729,2) +429496729 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483644 +(429496728,4) +429496728 +4 +# +2147483645 +(429496729,0) +429496729 +0 +# +2147483646 +(429496729,1) +429496729 +1 +# +1073741819 +(214748363,4) +214748363 +4 +# +1073741820 +(214748364,0) +214748364 +0 +# +1073741821 +(214748364,1) +214748364 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +2147483647 +(306783378,1) +306783378 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(306783377,6) +306783377 +6 +# +2147483646 +(306783378,0) +306783378 +0 +# +2147483647 +(306783378,1) +306783378 +1 +# +1073741822 +(153391688,6) +153391688 +6 +# +1073741823 +(153391689,0) +153391689 +0 +# +1073741824 +(153391689,1) +153391689 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +2147483647 +(153391689,1) +153391689 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(153391688,13) +153391688 +13 +# +2147483646 +(153391689,0) +153391689 +0 +# +2147483647 +(153391689,1) +153391689 +1 +# +1073741815 +(76695843,13) +76695843 +13 +# +1073741816 +(76695844,0) +76695844 +0 +# +1073741817 +(76695844,1) +76695844 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +2147483647 +(85899345,22) +85899345 +22 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483624 +(85899344,24) +85899344 +24 +# +2147483625 +(85899345,0) +85899345 +0 +# +2147483626 +(85899345,1) +85899345 +1 +# +1073741799 +(42949671,24) +42949671 +24 +# +1073741800 +(42949672,0) +42949672 +0 +# +1073741801 +(42949672,1) +42949672 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +2147483647 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(1,0) +1 +0 +# +-2147483648 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(1,0) +1 +0 +# +-2147483648 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +2147483647 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(0,2147483645) +0 +2147483645 +# +2147483646 +(1,0) +1 +0 +# +2147483647 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +2147483645 +(0,2147483645) +0 +2147483645 +# +2147483646 +(1,0) +1 +0 +# +2147483647 +(1,1) +1 +1 +# +divide by -1 +2147483647 +(-2147483647,0) +-2147483647 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +1073741822 +(-1073741822,0) +-1073741822 +0 +# +1073741823 +(-1073741823,0) +-1073741823 +0 +# +1073741824 +(-1073741824,0) +-1073741824 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +2147483647 +(-1073741823,1) +-1073741823 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-1073741822,1) +-1073741822 +1 +# +2147483646 +(-1073741823,0) +-1073741823 +0 +# +2147483647 +(-1073741823,1) +-1073741823 +1 +# +1073741821 +(-536870910,1) +-536870910 +1 +# +1073741822 +(-536870911,0) +-536870911 +0 +# +1073741823 +(-536870911,1) +-536870911 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +2147483647 +(-536870911,3) +-536870911 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483643 +(-536870910,3) +-536870910 +3 +# +2147483644 +(-536870911,0) +-536870911 +0 +# +2147483645 +(-536870911,1) +-536870911 +1 +# +1073741819 +(-268435454,3) +-268435454 +3 +# +1073741820 +(-268435455,0) +-268435455 +0 +# +1073741821 +(-268435455,1) +-268435455 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +2147483647 +(-715827882,1) +-715827882 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-715827881,2) +-715827881 +2 +# +2147483646 +(-715827882,0) +-715827882 +0 +# +2147483647 +(-715827882,1) +-715827882 +1 +# +1073741822 +(-357913940,2) +-357913940 +2 +# +1073741823 +(-357913941,0) +-357913941 +0 +# +1073741824 +(-357913941,1) +-357913941 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +2147483647 +(-429496729,2) +-429496729 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483644 +(-429496728,4) +-429496728 +4 +# +2147483645 +(-429496729,0) +-429496729 +0 +# +2147483646 +(-429496729,1) +-429496729 +1 +# +1073741819 +(-214748363,4) +-214748363 +4 +# +1073741820 +(-214748364,0) +-214748364 +0 +# +1073741821 +(-214748364,1) +-214748364 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +2147483647 +(-306783378,1) +-306783378 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-306783377,6) +-306783377 +6 +# +2147483646 +(-306783378,0) +-306783378 +0 +# +2147483647 +(-306783378,1) +-306783378 +1 +# +1073741822 +(-153391688,6) +-153391688 +6 +# +1073741823 +(-153391689,0) +-153391689 +0 +# +1073741824 +(-153391689,1) +-153391689 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +2147483647 +(-153391689,1) +-153391689 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-153391688,13) +-153391688 +13 +# +2147483646 +(-153391689,0) +-153391689 +0 +# +2147483647 +(-153391689,1) +-153391689 +1 +# +1073741815 +(-76695843,13) +-76695843 +13 +# +1073741816 +(-76695844,0) +-76695844 +0 +# +1073741817 +(-76695844,1) +-76695844 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +2147483647 +(-85899345,22) +-85899345 +22 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483624 +(-85899344,24) +-85899344 +24 +# +2147483625 +(-85899345,0) +-85899345 +0 +# +2147483626 +(-85899345,1) +-85899345 +1 +# +1073741799 +(-42949671,24) +-42949671 +24 +# +1073741800 +(-42949672,0) +-42949672 +0 +# +1073741801 +(-42949672,1) +-42949672 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +2147483647 +(0,2147483647) +0 +2147483647 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483647 +(0,2147483647) +0 +2147483647 +# +-2147483648 +(1,0) +1 +0 +# +-2147483647 +(0,-2147483647) +0 +-2147483647 +# +divide by (minBound + 1) +2147483647 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(-1,0) +-1 +0 +# +-2147483648 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-2147483648 +(1,-1) +1 +-1 +# +-2147483647 +(1,0) +1 +0 +# +-2147483646 +(0,-2147483646) +0 +-2147483646 +# +-------------------------------- +--Testing Int64 +-------------------------------- +divide by 1 +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +9223372036854775806 +(9223372036854775806,0) +9223372036854775806 +0 +# +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +-9223372036854775808 +(-9223372036854775808,0) +-9223372036854775808 +0 +# +4611686018427387902 +(4611686018427387902,0) +4611686018427387902 +0 +# +4611686018427387903 +(4611686018427387903,0) +4611686018427387903 +0 +# +4611686018427387904 +(4611686018427387904,0) +4611686018427387904 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(4611686018427387902,1) +4611686018427387902 +1 +# +9223372036854775806 +(4611686018427387903,0) +4611686018427387903 +0 +# +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +4611686018427387901 +(2305843009213693950,1) +2305843009213693950 +1 +# +4611686018427387902 +(2305843009213693951,0) +2305843009213693951 +0 +# +4611686018427387903 +(2305843009213693951,1) +2305843009213693951 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +9223372036854775807 +(2305843009213693951,3) +2305843009213693951 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775803 +(2305843009213693950,3) +2305843009213693950 +3 +# +9223372036854775804 +(2305843009213693951,0) +2305843009213693951 +0 +# +9223372036854775805 +(2305843009213693951,1) +2305843009213693951 +1 +# +4611686018427387899 +(1152921504606846974,3) +1152921504606846974 +3 +# +4611686018427387900 +(1152921504606846975,0) +1152921504606846975 +0 +# +4611686018427387901 +(1152921504606846975,1) +1152921504606846975 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(3074457345618258601,2) +3074457345618258601 +2 +# +9223372036854775806 +(3074457345618258602,0) +3074457345618258602 +0 +# +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +4611686018427387902 +(1537228672809129300,2) +1537228672809129300 +2 +# +4611686018427387903 +(1537228672809129301,0) +1537228672809129301 +0 +# +4611686018427387904 +(1537228672809129301,1) +1537228672809129301 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +9223372036854775807 +(1844674407370955161,2) +1844674407370955161 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775804 +(1844674407370955160,4) +1844674407370955160 +4 +# +9223372036854775805 +(1844674407370955161,0) +1844674407370955161 +0 +# +9223372036854775806 +(1844674407370955161,1) +1844674407370955161 +1 +# +4611686018427387899 +(922337203685477579,4) +922337203685477579 +4 +# +4611686018427387900 +(922337203685477580,0) +922337203685477580 +0 +# +4611686018427387901 +(922337203685477580,1) +922337203685477580 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(1317624576693539400,6) +1317624576693539400 +6 +# +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +-9223372036854775808 +(-1317624576693539401,-1) +-1317624576693539401 +-1 +# +4611686018427387899 +(658812288346769699,6) +658812288346769699 +6 +# +4611686018427387900 +(658812288346769700,0) +658812288346769700 +0 +# +4611686018427387901 +(658812288346769700,1) +658812288346769700 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +9223372036854775807 +(658812288346769700,7) +658812288346769700 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(658812288346769699,13) +658812288346769699 +13 +# +9223372036854775800 +(658812288346769700,0) +658812288346769700 +0 +# +9223372036854775801 +(658812288346769700,1) +658812288346769700 +1 +# +4611686018427387899 +(329406144173384849,13) +329406144173384849 +13 +# +4611686018427387900 +(329406144173384850,0) +329406144173384850 +0 +# +4611686018427387901 +(329406144173384850,1) +329406144173384850 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +9223372036854775807 +(368934881474191032,7) +368934881474191032 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(368934881474191031,24) +368934881474191031 +24 +# +9223372036854775800 +(368934881474191032,0) +368934881474191032 +0 +# +9223372036854775801 +(368934881474191032,1) +368934881474191032 +1 +# +4611686018427387899 +(184467440737095515,24) +184467440737095515 +24 +# +4611686018427387900 +(184467440737095516,0) +184467440737095516 +0 +# +4611686018427387901 +(184467440737095516,1) +184467440737095516 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +9223372036854775807 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775808 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775808 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +9223372036854775807 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(0,9223372036854775805) +0 +9223372036854775805 +# +9223372036854775806 +(1,0) +1 +0 +# +9223372036854775807 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +9223372036854775805 +(0,9223372036854775805) +0 +9223372036854775805 +# +9223372036854775806 +(1,0) +1 +0 +# +9223372036854775807 +(1,1) +1 +1 +# +divide by -1 +9223372036854775807 +(-9223372036854775807,0) +-9223372036854775807 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +4611686018427387902 +(-4611686018427387902,0) +-4611686018427387902 +0 +# +4611686018427387903 +(-4611686018427387903,0) +-4611686018427387903 +0 +# +4611686018427387904 +(-4611686018427387904,0) +-4611686018427387904 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +9223372036854775807 +(-4611686018427387903,1) +-4611686018427387903 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(-4611686018427387902,1) +-4611686018427387902 +1 +# +9223372036854775806 +(-4611686018427387903,0) +-4611686018427387903 +0 +# +9223372036854775807 +(-4611686018427387903,1) +-4611686018427387903 +1 +# +4611686018427387901 +(-2305843009213693950,1) +-2305843009213693950 +1 +# +4611686018427387902 +(-2305843009213693951,0) +-2305843009213693951 +0 +# +4611686018427387903 +(-2305843009213693951,1) +-2305843009213693951 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +9223372036854775807 +(-2305843009213693951,3) +-2305843009213693951 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775803 +(-2305843009213693950,3) +-2305843009213693950 +3 +# +9223372036854775804 +(-2305843009213693951,0) +-2305843009213693951 +0 +# +9223372036854775805 +(-2305843009213693951,1) +-2305843009213693951 +1 +# +4611686018427387899 +(-1152921504606846974,3) +-1152921504606846974 +3 +# +4611686018427387900 +(-1152921504606846975,0) +-1152921504606846975 +0 +# +4611686018427387901 +(-1152921504606846975,1) +-1152921504606846975 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +9223372036854775807 +(-3074457345618258602,1) +-3074457345618258602 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(-3074457345618258601,2) +-3074457345618258601 +2 +# +9223372036854775806 +(-3074457345618258602,0) +-3074457345618258602 +0 +# +9223372036854775807 +(-3074457345618258602,1) +-3074457345618258602 +1 +# +4611686018427387902 +(-1537228672809129300,2) +-1537228672809129300 +2 +# +4611686018427387903 +(-1537228672809129301,0) +-1537228672809129301 +0 +# +4611686018427387904 +(-1537228672809129301,1) +-1537228672809129301 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +9223372036854775807 +(-1844674407370955161,2) +-1844674407370955161 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775804 +(-1844674407370955160,4) +-1844674407370955160 +4 +# +9223372036854775805 +(-1844674407370955161,0) +-1844674407370955161 +0 +# +9223372036854775806 +(-1844674407370955161,1) +-1844674407370955161 +1 +# +4611686018427387899 +(-922337203685477579,4) +-922337203685477579 +4 +# +4611686018427387900 +(-922337203685477580,0) +-922337203685477580 +0 +# +4611686018427387901 +(-922337203685477580,1) +-922337203685477580 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +9223372036854775807 +(-1317624576693539401,0) +-1317624576693539401 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(-1317624576693539400,6) +-1317624576693539400 +6 +# +9223372036854775807 +(-1317624576693539401,0) +-1317624576693539401 +0 +# +-9223372036854775808 +(1317624576693539401,-1) +1317624576693539401 +-1 +# +4611686018427387899 +(-658812288346769699,6) +-658812288346769699 +6 +# +4611686018427387900 +(-658812288346769700,0) +-658812288346769700 +0 +# +4611686018427387901 +(-658812288346769700,1) +-658812288346769700 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +9223372036854775807 +(-658812288346769700,7) +-658812288346769700 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(-658812288346769699,13) +-658812288346769699 +13 +# +9223372036854775800 +(-658812288346769700,0) +-658812288346769700 +0 +# +9223372036854775801 +(-658812288346769700,1) +-658812288346769700 +1 +# +4611686018427387899 +(-329406144173384849,13) +-329406144173384849 +13 +# +4611686018427387900 +(-329406144173384850,0) +-329406144173384850 +0 +# +4611686018427387901 +(-329406144173384850,1) +-329406144173384850 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +9223372036854775807 +(-368934881474191032,7) +-368934881474191032 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(-368934881474191031,24) +-368934881474191031 +24 +# +9223372036854775800 +(-368934881474191032,0) +-368934881474191032 +0 +# +9223372036854775801 +(-368934881474191032,1) +-368934881474191032 +1 +# +4611686018427387899 +(-184467440737095515,24) +-184467440737095515 +24 +# +4611686018427387900 +(-184467440737095516,0) +-184467440737095516 +0 +# +4611686018427387901 +(-184467440737095516,1) +-184467440737095516 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +9223372036854775807 +(0,9223372036854775807) +0 +9223372036854775807 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775807 +(0,9223372036854775807) +0 +9223372036854775807 +# +-9223372036854775808 +(1,0) +1 +0 +# +-9223372036854775807 +(0,-9223372036854775807) +0 +-9223372036854775807 +# +divide by (minBound + 1) +9223372036854775807 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(-1,0) +-1 +0 +# +-9223372036854775808 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-9223372036854775808 +(1,-1) +1 +-1 +# +-9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775806 +(0,-9223372036854775806) +0 +-9223372036854775806 +# +-------------------------------- +--Testing Word +-------------------------------- +divide by 1 +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +18446744073709551614 +(18446744073709551614,0) +18446744073709551614 +0 +# +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775806 +(9223372036854775806,0) +9223372036854775806 +0 +# +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +9223372036854775808 +(9223372036854775808,0) +9223372036854775808 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(9223372036854775806,1) +9223372036854775806 +1 +# +18446744073709551614 +(9223372036854775807,0) +9223372036854775807 +0 +# +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +9223372036854775805 +(4611686018427387902,1) +4611686018427387902 +1 +# +9223372036854775806 +(4611686018427387903,0) +4611686018427387903 +0 +# +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +18446744073709551615 +(4611686018427387903,3) +4611686018427387903 +3 +# +18446744073709551615 +(4611686018427387903,3) +4611686018427387903 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551611 +(4611686018427387902,3) +4611686018427387902 +3 +# +18446744073709551612 +(4611686018427387903,0) +4611686018427387903 +0 +# +18446744073709551613 +(4611686018427387903,1) +4611686018427387903 +1 +# +9223372036854775803 +(2305843009213693950,3) +2305843009213693950 +3 +# +9223372036854775804 +(2305843009213693951,0) +2305843009213693951 +0 +# +9223372036854775805 +(2305843009213693951,1) +2305843009213693951 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551614 +(6148914691236517204,2) +6148914691236517204 +2 +# +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775805 +(3074457345618258601,2) +3074457345618258601 +2 +# +9223372036854775806 +(3074457345618258602,0) +3074457345618258602 +0 +# +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551614 +(3689348814741910322,4) +3689348814741910322 +4 +# +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775804 +(1844674407370955160,4) +1844674407370955160 +4 +# +9223372036854775805 +(1844674407370955161,0) +1844674407370955161 +0 +# +9223372036854775806 +(1844674407370955161,1) +1844674407370955161 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(2635249153387078801,6) +2635249153387078801 +6 +# +18446744073709551614 +(2635249153387078802,0) +2635249153387078802 +0 +# +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +9223372036854775806 +(1317624576693539400,6) +1317624576693539400 +6 +# +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +9223372036854775808 +(1317624576693539401,1) +1317624576693539401 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(1317624576693539400,13) +1317624576693539400 +13 +# +18446744073709551614 +(1317624576693539401,0) +1317624576693539401 +0 +# +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +9223372036854775799 +(658812288346769699,13) +658812288346769699 +13 +# +9223372036854775800 +(658812288346769700,0) +658812288346769700 +0 +# +9223372036854775801 +(658812288346769700,1) +658812288346769700 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +18446744073709551615 +(737869762948382064,15) +737869762948382064 +15 +# +18446744073709551615 +(737869762948382064,15) +737869762948382064 +15 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551599 +(737869762948382063,24) +737869762948382063 +24 +# +18446744073709551600 +(737869762948382064,0) +737869762948382064 +0 +# +18446744073709551601 +(737869762948382064,1) +737869762948382064 +1 +# +9223372036854775799 +(368934881474191031,24) +368934881474191031 +24 +# +9223372036854775800 +(368934881474191032,0) +368934881474191032 +0 +# +9223372036854775801 +(368934881474191032,1) +368934881474191032 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +18446744073709551615 +(1,0) +1 +0 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551611 +(0,18446744073709551611) +0 +18446744073709551611 +# +18446744073709551612 +(0,18446744073709551612) +0 +18446744073709551612 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(0,18446744073709551614) +0 +18446744073709551614 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +18446744073709551615 +(1,1) +1 +1 +# +18446744073709551615 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(1,0) +1 +0 +# +18446744073709551615 +(1,1) +1 +1 +# +18446744073709551615 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551607 +(0,18446744073709551607) +0 +18446744073709551607 +# +18446744073709551608 +(0,18446744073709551608) +0 +18446744073709551608 +# +18446744073709551609 +(0,18446744073709551609) +0 +18446744073709551609 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(1,0) +1 +0 +# +18446744073709551615 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word8 +-------------------------------- +divide by 1 +255 +(255,0) +255 +0 +# +255 +(255,0) +255 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +254 +(254,0) +254 +0 +# +255 +(255,0) +255 +0 +# +0 +(0,0) +0 +0 +# +126 +(126,0) +126 +0 +# +127 +(127,0) +127 +0 +# +128 +(128,0) +128 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +255 +(127,1) +127 +1 +# +255 +(127,1) +127 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +253 +(126,1) +126 +1 +# +254 +(127,0) +127 +0 +# +255 +(127,1) +127 +1 +# +125 +(62,1) +62 +1 +# +126 +(63,0) +63 +0 +# +127 +(63,1) +63 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +255 +(63,3) +63 +3 +# +255 +(63,3) +63 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(62,3) +62 +3 +# +252 +(63,0) +63 +0 +# +253 +(63,1) +63 +1 +# +123 +(30,3) +30 +3 +# +124 +(31,0) +31 +0 +# +125 +(31,1) +31 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +255 +(85,0) +85 +0 +# +255 +(85,0) +85 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +254 +(84,2) +84 +2 +# +255 +(85,0) +85 +0 +# +0 +(0,0) +0 +0 +# +125 +(41,2) +41 +2 +# +126 +(42,0) +42 +0 +# +127 +(42,1) +42 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +255 +(51,0) +51 +0 +# +255 +(51,0) +51 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +254 +(50,4) +50 +4 +# +255 +(51,0) +51 +0 +# +0 +(0,0) +0 +0 +# +124 +(24,4) +24 +4 +# +125 +(25,0) +25 +0 +# +126 +(25,1) +25 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +255 +(36,3) +36 +3 +# +255 +(36,3) +36 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(35,6) +35 +6 +# +252 +(36,0) +36 +0 +# +253 +(36,1) +36 +1 +# +125 +(17,6) +17 +6 +# +126 +(18,0) +18 +0 +# +127 +(18,1) +18 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +255 +(18,3) +18 +3 +# +255 +(18,3) +18 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(17,13) +17 +13 +# +252 +(18,0) +18 +0 +# +253 +(18,1) +18 +1 +# +125 +(8,13) +8 +13 +# +126 +(9,0) +9 +0 +# +127 +(9,1) +9 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +255 +(10,5) +10 +5 +# +255 +(10,5) +10 +5 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +249 +(9,24) +9 +24 +# +250 +(10,0) +10 +0 +# +251 +(10,1) +10 +1 +# +124 +(4,24) +4 +24 +# +125 +(5,0) +5 +0 +# +126 +(5,1) +5 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +255 +(1,0) +1 +0 +# +255 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +255 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(0,251) +0 +251 +# +252 +(0,252) +0 +252 +# +253 +(0,253) +0 +253 +# +254 +(0,254) +0 +254 +# +255 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +255 +(1,1) +1 +1 +# +255 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +253 +(0,253) +0 +253 +# +254 +(1,0) +1 +0 +# +255 +(1,1) +1 +1 +# +255 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +247 +(0,247) +0 +247 +# +248 +(0,248) +0 +248 +# +249 +(0,249) +0 +249 +# +253 +(0,253) +0 +253 +# +254 +(1,0) +1 +0 +# +255 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word16 +-------------------------------- +divide by 1 +65535 +(65535,0) +65535 +0 +# +65535 +(65535,0) +65535 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +65534 +(65534,0) +65534 +0 +# +65535 +(65535,0) +65535 +0 +# +0 +(0,0) +0 +0 +# +32766 +(32766,0) +32766 +0 +# +32767 +(32767,0) +32767 +0 +# +32768 +(32768,0) +32768 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +65535 +(32767,1) +32767 +1 +# +65535 +(32767,1) +32767 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(32766,1) +32766 +1 +# +65534 +(32767,0) +32767 +0 +# +65535 +(32767,1) +32767 +1 +# +32765 +(16382,1) +16382 +1 +# +32766 +(16383,0) +16383 +0 +# +32767 +(16383,1) +16383 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +65535 +(16383,3) +16383 +3 +# +65535 +(16383,3) +16383 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65531 +(16382,3) +16382 +3 +# +65532 +(16383,0) +16383 +0 +# +65533 +(16383,1) +16383 +1 +# +32763 +(8190,3) +8190 +3 +# +32764 +(8191,0) +8191 +0 +# +32765 +(8191,1) +8191 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +65535 +(21845,0) +21845 +0 +# +65535 +(21845,0) +21845 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65534 +(21844,2) +21844 +2 +# +65535 +(21845,0) +21845 +0 +# +0 +(0,0) +0 +0 +# +32765 +(10921,2) +10921 +2 +# +32766 +(10922,0) +10922 +0 +# +32767 +(10922,1) +10922 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +65535 +(13107,0) +13107 +0 +# +65535 +(13107,0) +13107 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65534 +(13106,4) +13106 +4 +# +65535 +(13107,0) +13107 +0 +# +0 +(0,0) +0 +0 +# +32764 +(6552,4) +6552 +4 +# +32765 +(6553,0) +6553 +0 +# +32766 +(6553,1) +6553 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +65535 +(9362,1) +9362 +1 +# +65535 +(9362,1) +9362 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(9361,6) +9361 +6 +# +65534 +(9362,0) +9362 +0 +# +65535 +(9362,1) +9362 +1 +# +32766 +(4680,6) +4680 +6 +# +32767 +(4681,0) +4681 +0 +# +32768 +(4681,1) +4681 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +65535 +(4681,1) +4681 +1 +# +65535 +(4681,1) +4681 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(4680,13) +4680 +13 +# +65534 +(4681,0) +4681 +0 +# +65535 +(4681,1) +4681 +1 +# +32759 +(2339,13) +2339 +13 +# +32760 +(2340,0) +2340 +0 +# +32761 +(2340,1) +2340 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +65535 +(2621,10) +2621 +10 +# +65535 +(2621,10) +2621 +10 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65524 +(2620,24) +2620 +24 +# +65525 +(2621,0) +2621 +0 +# +65526 +(2621,1) +2621 +1 +# +32749 +(1309,24) +1309 +24 +# +32750 +(1310,0) +1310 +0 +# +32751 +(1310,1) +1310 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +65535 +(1,0) +1 +0 +# +65535 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65535 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65531 +(0,65531) +0 +65531 +# +65532 +(0,65532) +0 +65532 +# +65533 +(0,65533) +0 +65533 +# +65534 +(0,65534) +0 +65534 +# +65535 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +65535 +(1,1) +1 +1 +# +65535 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(0,65533) +0 +65533 +# +65534 +(1,0) +1 +0 +# +65535 +(1,1) +1 +1 +# +65535 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65527 +(0,65527) +0 +65527 +# +65528 +(0,65528) +0 +65528 +# +65529 +(0,65529) +0 +65529 +# +65533 +(0,65533) +0 +65533 +# +65534 +(1,0) +1 +0 +# +65535 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word32 +-------------------------------- +divide by 1 +4294967295 +(4294967295,0) +4294967295 +0 +# +4294967295 +(4294967295,0) +4294967295 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +4294967294 +(4294967294,0) +4294967294 +0 +# +4294967295 +(4294967295,0) +4294967295 +0 +# +0 +(0,0) +0 +0 +# +2147483646 +(2147483646,0) +2147483646 +0 +# +2147483647 +(2147483647,0) +2147483647 +0 +# +2147483648 +(2147483648,0) +2147483648 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +4294967295 +(2147483647,1) +2147483647 +1 +# +4294967295 +(2147483647,1) +2147483647 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967293 +(2147483646,1) +2147483646 +1 +# +4294967294 +(2147483647,0) +2147483647 +0 +# +4294967295 +(2147483647,1) +2147483647 +1 +# +2147483645 +(1073741822,1) +1073741822 +1 +# +2147483646 +(1073741823,0) +1073741823 +0 +# +2147483647 +(1073741823,1) +1073741823 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +4294967295 +(1073741823,3) +1073741823 +3 +# +4294967295 +(1073741823,3) +1073741823 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(1073741822,3) +1073741822 +3 +# +4294967292 +(1073741823,0) +1073741823 +0 +# +4294967293 +(1073741823,1) +1073741823 +1 +# +2147483643 +(536870910,3) +536870910 +3 +# +2147483644 +(536870911,0) +536870911 +0 +# +2147483645 +(536870911,1) +536870911 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +4294967295 +(1431655765,0) +1431655765 +0 +# +4294967295 +(1431655765,0) +1431655765 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967294 +(1431655764,2) +1431655764 +2 +# +4294967295 +(1431655765,0) +1431655765 +0 +# +0 +(0,0) +0 +0 +# +2147483645 +(715827881,2) +715827881 +2 +# +2147483646 +(715827882,0) +715827882 +0 +# +2147483647 +(715827882,1) +715827882 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +4294967295 +(858993459,0) +858993459 +0 +# +4294967295 +(858993459,0) +858993459 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967294 +(858993458,4) +858993458 +4 +# +4294967295 +(858993459,0) +858993459 +0 +# +0 +(0,0) +0 +0 +# +2147483644 +(429496728,4) +429496728 +4 +# +2147483645 +(429496729,0) +429496729 +0 +# +2147483646 +(429496729,1) +429496729 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +4294967295 +(613566756,3) +613566756 +3 +# +4294967295 +(613566756,3) +613566756 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(613566755,6) +613566755 +6 +# +4294967292 +(613566756,0) +613566756 +0 +# +4294967293 +(613566756,1) +613566756 +1 +# +2147483645 +(306783377,6) +306783377 +6 +# +2147483646 +(306783378,0) +306783378 +0 +# +2147483647 +(306783378,1) +306783378 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +4294967295 +(306783378,3) +306783378 +3 +# +4294967295 +(306783378,3) +306783378 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(306783377,13) +306783377 +13 +# +4294967292 +(306783378,0) +306783378 +0 +# +4294967293 +(306783378,1) +306783378 +1 +# +2147483645 +(153391688,13) +153391688 +13 +# +2147483646 +(153391689,0) +153391689 +0 +# +2147483647 +(153391689,1) +153391689 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +4294967295 +(171798691,20) +171798691 +20 +# +4294967295 +(171798691,20) +171798691 +20 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967274 +(171798690,24) +171798690 +24 +# +4294967275 +(171798691,0) +171798691 +0 +# +4294967276 +(171798691,1) +171798691 +1 +# +2147483624 +(85899344,24) +85899344 +24 +# +2147483625 +(85899345,0) +85899345 +0 +# +2147483626 +(85899345,1) +85899345 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +4294967295 +(1,0) +1 +0 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(0,4294967291) +0 +4294967291 +# +4294967292 +(0,4294967292) +0 +4294967292 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(0,4294967294) +0 +4294967294 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +4294967295 +(1,1) +1 +1 +# +4294967295 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(1,0) +1 +0 +# +4294967295 +(1,1) +1 +1 +# +4294967295 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967287 +(0,4294967287) +0 +4294967287 +# +4294967288 +(0,4294967288) +0 +4294967288 +# +4294967289 +(0,4294967289) +0 +4294967289 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(1,0) +1 +0 +# +4294967295 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word64 +-------------------------------- +divide by 1 +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +18446744073709551614 +(18446744073709551614,0) +18446744073709551614 +0 +# +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775806 +(9223372036854775806,0) +9223372036854775806 +0 +# +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +9223372036854775808 +(9223372036854775808,0) +9223372036854775808 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(9223372036854775806,1) +9223372036854775806 +1 +# +18446744073709551614 +(9223372036854775807,0) +9223372036854775807 +0 +# +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +9223372036854775805 +(4611686018427387902,1) +4611686018427387902 +1 +# +9223372036854775806 +(4611686018427387903,0) +4611686018427387903 +0 +# +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +18446744073709551615 +(4611686018427387903,3) +4611686018427387903 +3 +# +18446744073709551615 +(4611686018427387903,3) +4611686018427387903 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551611 +(4611686018427387902,3) +4611686018427387902 +3 +# +18446744073709551612 +(4611686018427387903,0) +4611686018427387903 +0 +# +18446744073709551613 +(4611686018427387903,1) +4611686018427387903 +1 +# +9223372036854775803 +(2305843009213693950,3) +2305843009213693950 +3 +# +9223372036854775804 +(2305843009213693951,0) +2305843009213693951 +0 +# +9223372036854775805 +(2305843009213693951,1) +2305843009213693951 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551614 +(6148914691236517204,2) +6148914691236517204 +2 +# +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775805 +(3074457345618258601,2) +3074457345618258601 +2 +# +9223372036854775806 +(3074457345618258602,0) +3074457345618258602 +0 +# +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551614 +(3689348814741910322,4) +3689348814741910322 +4 +# +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775804 +(1844674407370955160,4) +1844674407370955160 +4 +# +9223372036854775805 +(1844674407370955161,0) +1844674407370955161 +0 +# +9223372036854775806 +(1844674407370955161,1) +1844674407370955161 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(2635249153387078801,6) +2635249153387078801 +6 +# +18446744073709551614 +(2635249153387078802,0) +2635249153387078802 +0 +# +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +9223372036854775806 +(1317624576693539400,6) +1317624576693539400 +6 +# +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +9223372036854775808 +(1317624576693539401,1) +1317624576693539401 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(1317624576693539400,13) +1317624576693539400 +13 +# +18446744073709551614 +(1317624576693539401,0) +1317624576693539401 +0 +# +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +9223372036854775799 +(658812288346769699,13) +658812288346769699 +13 +# +9223372036854775800 +(658812288346769700,0) +658812288346769700 +0 +# +9223372036854775801 +(658812288346769700,1) +658812288346769700 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +18446744073709551615 +(737869762948382064,15) +737869762948382064 +15 +# +18446744073709551615 +(737869762948382064,15) +737869762948382064 +15 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551599 +(737869762948382063,24) +737869762948382063 +24 +# +18446744073709551600 +(737869762948382064,0) +737869762948382064 +0 +# +18446744073709551601 +(737869762948382064,1) +737869762948382064 +1 +# +9223372036854775799 +(368934881474191031,24) +368934881474191031 +24 +# +9223372036854775800 +(368934881474191032,0) +368934881474191032 +0 +# +9223372036854775801 +(368934881474191032,1) +368934881474191032 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +18446744073709551615 +(1,0) +1 +0 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551611 +(0,18446744073709551611) +0 +18446744073709551611 +# +18446744073709551612 +(0,18446744073709551612) +0 +18446744073709551612 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(0,18446744073709551614) +0 +18446744073709551614 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +18446744073709551615 +(1,1) +1 +1 +# +18446744073709551615 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(1,0) +1 +0 +# +18446744073709551615 +(1,1) +1 +1 +# +18446744073709551615 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551607 +(0,18446744073709551607) +0 +18446744073709551607 +# +18446744073709551608 +(0,18446744073709551608) +0 +18446744073709551608 +# +18446744073709551609 +(0,18446744073709551609) +0 +18446744073709551609 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(1,0) +1 +0 +# +18446744073709551615 +(1,1) +1 +1 +# diff --git a/testsuite/tests/numeric/should_run/div01.stdout-ws-32 b/testsuite/tests/numeric/should_run/div01.stdout-ws-32 new file mode 100644 index 000000000000..c39364f5e74e --- /dev/null +++ b/testsuite/tests/numeric/should_run/div01.stdout-ws-32 @@ -0,0 +1,12030 @@ +-------------------------------- +--Testing Int +-------------------------------- +divide by 1 +2147483647 +(2147483647,0) +2147483647 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2147483646 +(2147483646,0) +2147483646 +0 +# +2147483647 +(2147483647,0) +2147483647 +0 +# +-2147483648 +(-2147483648,0) +-2147483648 +0 +# +1073741822 +(1073741822,0) +1073741822 +0 +# +1073741823 +(1073741823,0) +1073741823 +0 +# +1073741824 +(1073741824,0) +1073741824 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +2147483647 +(1073741823,1) +1073741823 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(1073741822,1) +1073741822 +1 +# +2147483646 +(1073741823,0) +1073741823 +0 +# +2147483647 +(1073741823,1) +1073741823 +1 +# +1073741821 +(536870910,1) +536870910 +1 +# +1073741822 +(536870911,0) +536870911 +0 +# +1073741823 +(536870911,1) +536870911 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +2147483647 +(536870911,3) +536870911 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483643 +(536870910,3) +536870910 +3 +# +2147483644 +(536870911,0) +536870911 +0 +# +2147483645 +(536870911,1) +536870911 +1 +# +1073741819 +(268435454,3) +268435454 +3 +# +1073741820 +(268435455,0) +268435455 +0 +# +1073741821 +(268435455,1) +268435455 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +2147483647 +(715827882,1) +715827882 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(715827881,2) +715827881 +2 +# +2147483646 +(715827882,0) +715827882 +0 +# +2147483647 +(715827882,1) +715827882 +1 +# +1073741822 +(357913940,2) +357913940 +2 +# +1073741823 +(357913941,0) +357913941 +0 +# +1073741824 +(357913941,1) +357913941 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +2147483647 +(429496729,2) +429496729 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483644 +(429496728,4) +429496728 +4 +# +2147483645 +(429496729,0) +429496729 +0 +# +2147483646 +(429496729,1) +429496729 +1 +# +1073741819 +(214748363,4) +214748363 +4 +# +1073741820 +(214748364,0) +214748364 +0 +# +1073741821 +(214748364,1) +214748364 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +2147483647 +(306783378,1) +306783378 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(306783377,6) +306783377 +6 +# +2147483646 +(306783378,0) +306783378 +0 +# +2147483647 +(306783378,1) +306783378 +1 +# +1073741822 +(153391688,6) +153391688 +6 +# +1073741823 +(153391689,0) +153391689 +0 +# +1073741824 +(153391689,1) +153391689 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +2147483647 +(153391689,1) +153391689 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(153391688,13) +153391688 +13 +# +2147483646 +(153391689,0) +153391689 +0 +# +2147483647 +(153391689,1) +153391689 +1 +# +1073741815 +(76695843,13) +76695843 +13 +# +1073741816 +(76695844,0) +76695844 +0 +# +1073741817 +(76695844,1) +76695844 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +2147483647 +(85899345,22) +85899345 +22 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483624 +(85899344,24) +85899344 +24 +# +2147483625 +(85899345,0) +85899345 +0 +# +2147483626 +(85899345,1) +85899345 +1 +# +1073741799 +(42949671,24) +42949671 +24 +# +1073741800 +(42949672,0) +42949672 +0 +# +1073741801 +(42949672,1) +42949672 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +2147483647 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(1,0) +1 +0 +# +-2147483648 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(1,0) +1 +0 +# +-2147483648 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +2147483647 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(0,2147483645) +0 +2147483645 +# +2147483646 +(1,0) +1 +0 +# +2147483647 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +2147483645 +(0,2147483645) +0 +2147483645 +# +2147483646 +(1,0) +1 +0 +# +2147483647 +(1,1) +1 +1 +# +divide by -1 +2147483647 +(-2147483647,0) +-2147483647 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +1073741822 +(-1073741822,0) +-1073741822 +0 +# +1073741823 +(-1073741823,0) +-1073741823 +0 +# +1073741824 +(-1073741824,0) +-1073741824 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +2147483647 +(-1073741823,1) +-1073741823 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-1073741822,1) +-1073741822 +1 +# +2147483646 +(-1073741823,0) +-1073741823 +0 +# +2147483647 +(-1073741823,1) +-1073741823 +1 +# +1073741821 +(-536870910,1) +-536870910 +1 +# +1073741822 +(-536870911,0) +-536870911 +0 +# +1073741823 +(-536870911,1) +-536870911 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +2147483647 +(-536870911,3) +-536870911 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483643 +(-536870910,3) +-536870910 +3 +# +2147483644 +(-536870911,0) +-536870911 +0 +# +2147483645 +(-536870911,1) +-536870911 +1 +# +1073741819 +(-268435454,3) +-268435454 +3 +# +1073741820 +(-268435455,0) +-268435455 +0 +# +1073741821 +(-268435455,1) +-268435455 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +2147483647 +(-715827882,1) +-715827882 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-715827881,2) +-715827881 +2 +# +2147483646 +(-715827882,0) +-715827882 +0 +# +2147483647 +(-715827882,1) +-715827882 +1 +# +1073741822 +(-357913940,2) +-357913940 +2 +# +1073741823 +(-357913941,0) +-357913941 +0 +# +1073741824 +(-357913941,1) +-357913941 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +2147483647 +(-429496729,2) +-429496729 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483644 +(-429496728,4) +-429496728 +4 +# +2147483645 +(-429496729,0) +-429496729 +0 +# +2147483646 +(-429496729,1) +-429496729 +1 +# +1073741819 +(-214748363,4) +-214748363 +4 +# +1073741820 +(-214748364,0) +-214748364 +0 +# +1073741821 +(-214748364,1) +-214748364 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +2147483647 +(-306783378,1) +-306783378 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-306783377,6) +-306783377 +6 +# +2147483646 +(-306783378,0) +-306783378 +0 +# +2147483647 +(-306783378,1) +-306783378 +1 +# +1073741822 +(-153391688,6) +-153391688 +6 +# +1073741823 +(-153391689,0) +-153391689 +0 +# +1073741824 +(-153391689,1) +-153391689 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +2147483647 +(-153391689,1) +-153391689 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-153391688,13) +-153391688 +13 +# +2147483646 +(-153391689,0) +-153391689 +0 +# +2147483647 +(-153391689,1) +-153391689 +1 +# +1073741815 +(-76695843,13) +-76695843 +13 +# +1073741816 +(-76695844,0) +-76695844 +0 +# +1073741817 +(-76695844,1) +-76695844 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +2147483647 +(-85899345,22) +-85899345 +22 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483624 +(-85899344,24) +-85899344 +24 +# +2147483625 +(-85899345,0) +-85899345 +0 +# +2147483626 +(-85899345,1) +-85899345 +1 +# +1073741799 +(-42949671,24) +-42949671 +24 +# +1073741800 +(-42949672,0) +-42949672 +0 +# +1073741801 +(-42949672,1) +-42949672 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +2147483647 +(0,2147483647) +0 +2147483647 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483647 +(0,2147483647) +0 +2147483647 +# +-2147483648 +(1,0) +1 +0 +# +-2147483647 +(0,-2147483647) +0 +-2147483647 +# +divide by (minBound + 1) +2147483647 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(-1,0) +-1 +0 +# +-2147483648 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-2147483648 +(1,-1) +1 +-1 +# +-2147483647 +(1,0) +1 +0 +# +-2147483646 +(0,-2147483646) +0 +-2147483646 +# +-------------------------------- +--Testing Int8 +-------------------------------- +divide by 1 +127 +(127,0) +127 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +126 +(126,0) +126 +0 +# +127 +(127,0) +127 +0 +# +-128 +(-128,0) +-128 +0 +# +62 +(62,0) +62 +0 +# +63 +(63,0) +63 +0 +# +64 +(64,0) +64 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +127 +(63,1) +63 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(62,1) +62 +1 +# +126 +(63,0) +63 +0 +# +127 +(63,1) +63 +1 +# +61 +(30,1) +30 +1 +# +62 +(31,0) +31 +0 +# +63 +(31,1) +31 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +127 +(31,3) +31 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +123 +(30,3) +30 +3 +# +124 +(31,0) +31 +0 +# +125 +(31,1) +31 +1 +# +59 +(14,3) +14 +3 +# +60 +(15,0) +15 +0 +# +61 +(15,1) +15 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +127 +(42,1) +42 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(41,2) +41 +2 +# +126 +(42,0) +42 +0 +# +127 +(42,1) +42 +1 +# +62 +(20,2) +20 +2 +# +63 +(21,0) +21 +0 +# +64 +(21,1) +21 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +127 +(25,2) +25 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(24,4) +24 +4 +# +125 +(25,0) +25 +0 +# +126 +(25,1) +25 +1 +# +59 +(11,4) +11 +4 +# +60 +(12,0) +12 +0 +# +61 +(12,1) +12 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +127 +(18,1) +18 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(17,6) +17 +6 +# +126 +(18,0) +18 +0 +# +127 +(18,1) +18 +1 +# +62 +(8,6) +8 +6 +# +63 +(9,0) +9 +0 +# +64 +(9,1) +9 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +127 +(9,1) +9 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(8,13) +8 +13 +# +126 +(9,0) +9 +0 +# +127 +(9,1) +9 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +127 +(5,2) +5 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(4,24) +4 +24 +# +125 +(5,0) +5 +0 +# +126 +(5,1) +5 +1 +# +49 +(1,24) +1 +24 +# +50 +(2,0) +2 +0 +# +51 +(2,1) +2 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +127 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +126 +(0,126) +0 +126 +# +127 +(1,0) +1 +0 +# +-128 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +126 +(0,126) +0 +126 +# +127 +(1,0) +1 +0 +# +-128 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +127 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(0,125) +0 +125 +# +126 +(1,0) +1 +0 +# +127 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +125 +(0,125) +0 +125 +# +126 +(1,0) +1 +0 +# +127 +(1,1) +1 +1 +# +divide by -1 +127 +(-127,0) +-127 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +62 +(-62,0) +-62 +0 +# +63 +(-63,0) +-63 +0 +# +64 +(-64,0) +-64 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +127 +(-63,1) +-63 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-62,1) +-62 +1 +# +126 +(-63,0) +-63 +0 +# +127 +(-63,1) +-63 +1 +# +61 +(-30,1) +-30 +1 +# +62 +(-31,0) +-31 +0 +# +63 +(-31,1) +-31 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +127 +(-31,3) +-31 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +123 +(-30,3) +-30 +3 +# +124 +(-31,0) +-31 +0 +# +125 +(-31,1) +-31 +1 +# +59 +(-14,3) +-14 +3 +# +60 +(-15,0) +-15 +0 +# +61 +(-15,1) +-15 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +127 +(-42,1) +-42 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-41,2) +-41 +2 +# +126 +(-42,0) +-42 +0 +# +127 +(-42,1) +-42 +1 +# +62 +(-20,2) +-20 +2 +# +63 +(-21,0) +-21 +0 +# +64 +(-21,1) +-21 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +127 +(-25,2) +-25 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(-24,4) +-24 +4 +# +125 +(-25,0) +-25 +0 +# +126 +(-25,1) +-25 +1 +# +59 +(-11,4) +-11 +4 +# +60 +(-12,0) +-12 +0 +# +61 +(-12,1) +-12 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +127 +(-18,1) +-18 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-17,6) +-17 +6 +# +126 +(-18,0) +-18 +0 +# +127 +(-18,1) +-18 +1 +# +62 +(-8,6) +-8 +6 +# +63 +(-9,0) +-9 +0 +# +64 +(-9,1) +-9 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +127 +(-9,1) +-9 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +125 +(-8,13) +-8 +13 +# +126 +(-9,0) +-9 +0 +# +127 +(-9,1) +-9 +1 +# +55 +(-3,13) +-3 +13 +# +56 +(-4,0) +-4 +0 +# +57 +(-4,1) +-4 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +127 +(-5,2) +-5 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +124 +(-4,24) +-4 +24 +# +125 +(-5,0) +-5 +0 +# +126 +(-5,1) +-5 +1 +# +49 +(-1,24) +-1 +24 +# +50 +(-2,0) +-2 +0 +# +51 +(-2,1) +-2 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +127 +(0,127) +0 +127 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +127 +(0,127) +0 +127 +# +-128 +(1,0) +1 +0 +# +-127 +(0,-127) +0 +-127 +# +divide by (minBound + 1) +127 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +126 +(0,126) +0 +126 +# +127 +(-1,0) +-1 +0 +# +-128 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-128 +(1,-1) +1 +-1 +# +-127 +(1,0) +1 +0 +# +-126 +(0,-126) +0 +-126 +# +-------------------------------- +--Testing Int16 +-------------------------------- +divide by 1 +32767 +(32767,0) +32767 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +32766 +(32766,0) +32766 +0 +# +32767 +(32767,0) +32767 +0 +# +-32768 +(-32768,0) +-32768 +0 +# +16382 +(16382,0) +16382 +0 +# +16383 +(16383,0) +16383 +0 +# +16384 +(16384,0) +16384 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +32767 +(16383,1) +16383 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(16382,1) +16382 +1 +# +32766 +(16383,0) +16383 +0 +# +32767 +(16383,1) +16383 +1 +# +16381 +(8190,1) +8190 +1 +# +16382 +(8191,0) +8191 +0 +# +16383 +(8191,1) +8191 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +32767 +(8191,3) +8191 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32763 +(8190,3) +8190 +3 +# +32764 +(8191,0) +8191 +0 +# +32765 +(8191,1) +8191 +1 +# +16379 +(4094,3) +4094 +3 +# +16380 +(4095,0) +4095 +0 +# +16381 +(4095,1) +4095 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +32767 +(10922,1) +10922 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(10921,2) +10921 +2 +# +32766 +(10922,0) +10922 +0 +# +32767 +(10922,1) +10922 +1 +# +16382 +(5460,2) +5460 +2 +# +16383 +(5461,0) +5461 +0 +# +16384 +(5461,1) +5461 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +32767 +(6553,2) +6553 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32764 +(6552,4) +6552 +4 +# +32765 +(6553,0) +6553 +0 +# +32766 +(6553,1) +6553 +1 +# +16379 +(3275,4) +3275 +4 +# +16380 +(3276,0) +3276 +0 +# +16381 +(3276,1) +3276 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +32767 +(4681,0) +4681 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(4680,6) +4680 +6 +# +32767 +(4681,0) +4681 +0 +# +-32768 +(-4681,-1) +-4681 +-1 +# +16379 +(2339,6) +2339 +6 +# +16380 +(2340,0) +2340 +0 +# +16381 +(2340,1) +2340 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +32767 +(2340,7) +2340 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32759 +(2339,13) +2339 +13 +# +32760 +(2340,0) +2340 +0 +# +32761 +(2340,1) +2340 +1 +# +16379 +(1169,13) +1169 +13 +# +16380 +(1170,0) +1170 +0 +# +16381 +(1170,1) +1170 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +32767 +(1310,17) +1310 +17 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32749 +(1309,24) +1309 +24 +# +32750 +(1310,0) +1310 +0 +# +32751 +(1310,1) +1310 +1 +# +16374 +(654,24) +654 +24 +# +16375 +(655,0) +655 +0 +# +16376 +(655,1) +655 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +32767 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(0,32766) +0 +32766 +# +32767 +(1,0) +1 +0 +# +-32768 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +32766 +(0,32766) +0 +32766 +# +32767 +(1,0) +1 +0 +# +-32768 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +32767 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(0,32765) +0 +32765 +# +32766 +(1,0) +1 +0 +# +32767 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +32765 +(0,32765) +0 +32765 +# +32766 +(1,0) +1 +0 +# +32767 +(1,1) +1 +1 +# +divide by -1 +32767 +(-32767,0) +-32767 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +16382 +(-16382,0) +-16382 +0 +# +16383 +(-16383,0) +-16383 +0 +# +16384 +(-16384,0) +-16384 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +32767 +(-16383,1) +-16383 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(-16382,1) +-16382 +1 +# +32766 +(-16383,0) +-16383 +0 +# +32767 +(-16383,1) +-16383 +1 +# +16381 +(-8190,1) +-8190 +1 +# +16382 +(-8191,0) +-8191 +0 +# +16383 +(-8191,1) +-8191 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +32767 +(-8191,3) +-8191 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32763 +(-8190,3) +-8190 +3 +# +32764 +(-8191,0) +-8191 +0 +# +32765 +(-8191,1) +-8191 +1 +# +16379 +(-4094,3) +-4094 +3 +# +16380 +(-4095,0) +-4095 +0 +# +16381 +(-4095,1) +-4095 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +32767 +(-10922,1) +-10922 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32765 +(-10921,2) +-10921 +2 +# +32766 +(-10922,0) +-10922 +0 +# +32767 +(-10922,1) +-10922 +1 +# +16382 +(-5460,2) +-5460 +2 +# +16383 +(-5461,0) +-5461 +0 +# +16384 +(-5461,1) +-5461 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +32767 +(-6553,2) +-6553 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32764 +(-6552,4) +-6552 +4 +# +32765 +(-6553,0) +-6553 +0 +# +32766 +(-6553,1) +-6553 +1 +# +16379 +(-3275,4) +-3275 +4 +# +16380 +(-3276,0) +-3276 +0 +# +16381 +(-3276,1) +-3276 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +32767 +(-4681,0) +-4681 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(-4680,6) +-4680 +6 +# +32767 +(-4681,0) +-4681 +0 +# +-32768 +(4681,-1) +4681 +-1 +# +16379 +(-2339,6) +-2339 +6 +# +16380 +(-2340,0) +-2340 +0 +# +16381 +(-2340,1) +-2340 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +32767 +(-2340,7) +-2340 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32759 +(-2339,13) +-2339 +13 +# +32760 +(-2340,0) +-2340 +0 +# +32761 +(-2340,1) +-2340 +1 +# +16379 +(-1169,13) +-1169 +13 +# +16380 +(-1170,0) +-1170 +0 +# +16381 +(-1170,1) +-1170 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +32767 +(-1310,17) +-1310 +17 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32749 +(-1309,24) +-1309 +24 +# +32750 +(-1310,0) +-1310 +0 +# +32751 +(-1310,1) +-1310 +1 +# +16374 +(-654,24) +-654 +24 +# +16375 +(-655,0) +-655 +0 +# +16376 +(-655,1) +-655 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +32767 +(0,32767) +0 +32767 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32767 +(0,32767) +0 +32767 +# +-32768 +(1,0) +1 +0 +# +-32767 +(0,-32767) +0 +-32767 +# +divide by (minBound + 1) +32767 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +32766 +(0,32766) +0 +32766 +# +32767 +(-1,0) +-1 +0 +# +-32768 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-32768 +(1,-1) +1 +-1 +# +-32767 +(1,0) +1 +0 +# +-32766 +(0,-32766) +0 +-32766 +# +-------------------------------- +--Testing Int32 +-------------------------------- +divide by 1 +2147483647 +(2147483647,0) +2147483647 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2147483646 +(2147483646,0) +2147483646 +0 +# +2147483647 +(2147483647,0) +2147483647 +0 +# +-2147483648 +(-2147483648,0) +-2147483648 +0 +# +1073741822 +(1073741822,0) +1073741822 +0 +# +1073741823 +(1073741823,0) +1073741823 +0 +# +1073741824 +(1073741824,0) +1073741824 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +2147483647 +(1073741823,1) +1073741823 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(1073741822,1) +1073741822 +1 +# +2147483646 +(1073741823,0) +1073741823 +0 +# +2147483647 +(1073741823,1) +1073741823 +1 +# +1073741821 +(536870910,1) +536870910 +1 +# +1073741822 +(536870911,0) +536870911 +0 +# +1073741823 +(536870911,1) +536870911 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +2147483647 +(536870911,3) +536870911 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483643 +(536870910,3) +536870910 +3 +# +2147483644 +(536870911,0) +536870911 +0 +# +2147483645 +(536870911,1) +536870911 +1 +# +1073741819 +(268435454,3) +268435454 +3 +# +1073741820 +(268435455,0) +268435455 +0 +# +1073741821 +(268435455,1) +268435455 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +2147483647 +(715827882,1) +715827882 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(715827881,2) +715827881 +2 +# +2147483646 +(715827882,0) +715827882 +0 +# +2147483647 +(715827882,1) +715827882 +1 +# +1073741822 +(357913940,2) +357913940 +2 +# +1073741823 +(357913941,0) +357913941 +0 +# +1073741824 +(357913941,1) +357913941 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +2147483647 +(429496729,2) +429496729 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483644 +(429496728,4) +429496728 +4 +# +2147483645 +(429496729,0) +429496729 +0 +# +2147483646 +(429496729,1) +429496729 +1 +# +1073741819 +(214748363,4) +214748363 +4 +# +1073741820 +(214748364,0) +214748364 +0 +# +1073741821 +(214748364,1) +214748364 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +2147483647 +(306783378,1) +306783378 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(306783377,6) +306783377 +6 +# +2147483646 +(306783378,0) +306783378 +0 +# +2147483647 +(306783378,1) +306783378 +1 +# +1073741822 +(153391688,6) +153391688 +6 +# +1073741823 +(153391689,0) +153391689 +0 +# +1073741824 +(153391689,1) +153391689 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +2147483647 +(153391689,1) +153391689 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(153391688,13) +153391688 +13 +# +2147483646 +(153391689,0) +153391689 +0 +# +2147483647 +(153391689,1) +153391689 +1 +# +1073741815 +(76695843,13) +76695843 +13 +# +1073741816 +(76695844,0) +76695844 +0 +# +1073741817 +(76695844,1) +76695844 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +2147483647 +(85899345,22) +85899345 +22 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483624 +(85899344,24) +85899344 +24 +# +2147483625 +(85899345,0) +85899345 +0 +# +2147483626 +(85899345,1) +85899345 +1 +# +1073741799 +(42949671,24) +42949671 +24 +# +1073741800 +(42949672,0) +42949672 +0 +# +1073741801 +(42949672,1) +42949672 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +2147483647 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(1,0) +1 +0 +# +-2147483648 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(1,0) +1 +0 +# +-2147483648 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +2147483647 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(0,2147483645) +0 +2147483645 +# +2147483646 +(1,0) +1 +0 +# +2147483647 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +2147483645 +(0,2147483645) +0 +2147483645 +# +2147483646 +(1,0) +1 +0 +# +2147483647 +(1,1) +1 +1 +# +divide by -1 +2147483647 +(-2147483647,0) +-2147483647 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +1073741822 +(-1073741822,0) +-1073741822 +0 +# +1073741823 +(-1073741823,0) +-1073741823 +0 +# +1073741824 +(-1073741824,0) +-1073741824 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +2147483647 +(-1073741823,1) +-1073741823 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-1073741822,1) +-1073741822 +1 +# +2147483646 +(-1073741823,0) +-1073741823 +0 +# +2147483647 +(-1073741823,1) +-1073741823 +1 +# +1073741821 +(-536870910,1) +-536870910 +1 +# +1073741822 +(-536870911,0) +-536870911 +0 +# +1073741823 +(-536870911,1) +-536870911 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +2147483647 +(-536870911,3) +-536870911 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483643 +(-536870910,3) +-536870910 +3 +# +2147483644 +(-536870911,0) +-536870911 +0 +# +2147483645 +(-536870911,1) +-536870911 +1 +# +1073741819 +(-268435454,3) +-268435454 +3 +# +1073741820 +(-268435455,0) +-268435455 +0 +# +1073741821 +(-268435455,1) +-268435455 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +2147483647 +(-715827882,1) +-715827882 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-715827881,2) +-715827881 +2 +# +2147483646 +(-715827882,0) +-715827882 +0 +# +2147483647 +(-715827882,1) +-715827882 +1 +# +1073741822 +(-357913940,2) +-357913940 +2 +# +1073741823 +(-357913941,0) +-357913941 +0 +# +1073741824 +(-357913941,1) +-357913941 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +2147483647 +(-429496729,2) +-429496729 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483644 +(-429496728,4) +-429496728 +4 +# +2147483645 +(-429496729,0) +-429496729 +0 +# +2147483646 +(-429496729,1) +-429496729 +1 +# +1073741819 +(-214748363,4) +-214748363 +4 +# +1073741820 +(-214748364,0) +-214748364 +0 +# +1073741821 +(-214748364,1) +-214748364 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +2147483647 +(-306783378,1) +-306783378 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-306783377,6) +-306783377 +6 +# +2147483646 +(-306783378,0) +-306783378 +0 +# +2147483647 +(-306783378,1) +-306783378 +1 +# +1073741822 +(-153391688,6) +-153391688 +6 +# +1073741823 +(-153391689,0) +-153391689 +0 +# +1073741824 +(-153391689,1) +-153391689 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +2147483647 +(-153391689,1) +-153391689 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483645 +(-153391688,13) +-153391688 +13 +# +2147483646 +(-153391689,0) +-153391689 +0 +# +2147483647 +(-153391689,1) +-153391689 +1 +# +1073741815 +(-76695843,13) +-76695843 +13 +# +1073741816 +(-76695844,0) +-76695844 +0 +# +1073741817 +(-76695844,1) +-76695844 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +2147483647 +(-85899345,22) +-85899345 +22 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483624 +(-85899344,24) +-85899344 +24 +# +2147483625 +(-85899345,0) +-85899345 +0 +# +2147483626 +(-85899345,1) +-85899345 +1 +# +1073741799 +(-42949671,24) +-42949671 +24 +# +1073741800 +(-42949672,0) +-42949672 +0 +# +1073741801 +(-42949672,1) +-42949672 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +2147483647 +(0,2147483647) +0 +2147483647 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483647 +(0,2147483647) +0 +2147483647 +# +-2147483648 +(1,0) +1 +0 +# +-2147483647 +(0,-2147483647) +0 +-2147483647 +# +divide by (minBound + 1) +2147483647 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +2147483646 +(0,2147483646) +0 +2147483646 +# +2147483647 +(-1,0) +-1 +0 +# +-2147483648 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-2147483648 +(1,-1) +1 +-1 +# +-2147483647 +(1,0) +1 +0 +# +-2147483646 +(0,-2147483646) +0 +-2147483646 +# +-------------------------------- +--Testing Int64 +-------------------------------- +divide by 1 +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +-1 +(-1,0) +-1 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +9223372036854775806 +(9223372036854775806,0) +9223372036854775806 +0 +# +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +-9223372036854775808 +(-9223372036854775808,0) +-9223372036854775808 +0 +# +4611686018427387902 +(4611686018427387902,0) +4611686018427387902 +0 +# +4611686018427387903 +(4611686018427387903,0) +4611686018427387903 +0 +# +4611686018427387904 +(4611686018427387904,0) +4611686018427387904 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(4611686018427387902,1) +4611686018427387902 +1 +# +9223372036854775806 +(4611686018427387903,0) +4611686018427387903 +0 +# +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +4611686018427387901 +(2305843009213693950,1) +2305843009213693950 +1 +# +4611686018427387902 +(2305843009213693951,0) +2305843009213693951 +0 +# +4611686018427387903 +(2305843009213693951,1) +2305843009213693951 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +9223372036854775807 +(2305843009213693951,3) +2305843009213693951 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775803 +(2305843009213693950,3) +2305843009213693950 +3 +# +9223372036854775804 +(2305843009213693951,0) +2305843009213693951 +0 +# +9223372036854775805 +(2305843009213693951,1) +2305843009213693951 +1 +# +4611686018427387899 +(1152921504606846974,3) +1152921504606846974 +3 +# +4611686018427387900 +(1152921504606846975,0) +1152921504606846975 +0 +# +4611686018427387901 +(1152921504606846975,1) +1152921504606846975 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(3074457345618258601,2) +3074457345618258601 +2 +# +9223372036854775806 +(3074457345618258602,0) +3074457345618258602 +0 +# +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +4611686018427387902 +(1537228672809129300,2) +1537228672809129300 +2 +# +4611686018427387903 +(1537228672809129301,0) +1537228672809129301 +0 +# +4611686018427387904 +(1537228672809129301,1) +1537228672809129301 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +9223372036854775807 +(1844674407370955161,2) +1844674407370955161 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775804 +(1844674407370955160,4) +1844674407370955160 +4 +# +9223372036854775805 +(1844674407370955161,0) +1844674407370955161 +0 +# +9223372036854775806 +(1844674407370955161,1) +1844674407370955161 +1 +# +4611686018427387899 +(922337203685477579,4) +922337203685477579 +4 +# +4611686018427387900 +(922337203685477580,0) +922337203685477580 +0 +# +4611686018427387901 +(922337203685477580,1) +922337203685477580 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(1317624576693539400,6) +1317624576693539400 +6 +# +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +-9223372036854775808 +(-1317624576693539401,-1) +-1317624576693539401 +-1 +# +4611686018427387899 +(658812288346769699,6) +658812288346769699 +6 +# +4611686018427387900 +(658812288346769700,0) +658812288346769700 +0 +# +4611686018427387901 +(658812288346769700,1) +658812288346769700 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +9223372036854775807 +(658812288346769700,7) +658812288346769700 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(658812288346769699,13) +658812288346769699 +13 +# +9223372036854775800 +(658812288346769700,0) +658812288346769700 +0 +# +9223372036854775801 +(658812288346769700,1) +658812288346769700 +1 +# +4611686018427387899 +(329406144173384849,13) +329406144173384849 +13 +# +4611686018427387900 +(329406144173384850,0) +329406144173384850 +0 +# +4611686018427387901 +(329406144173384850,1) +329406144173384850 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +9223372036854775807 +(368934881474191032,7) +368934881474191032 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(368934881474191031,24) +368934881474191031 +24 +# +9223372036854775800 +(368934881474191032,0) +368934881474191032 +0 +# +9223372036854775801 +(368934881474191032,1) +368934881474191032 +1 +# +4611686018427387899 +(184467440737095515,24) +184467440737095515 +24 +# +4611686018427387900 +(184467440737095516,0) +184467440737095516 +0 +# +4611686018427387901 +(184467440737095516,1) +184467440737095516 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +9223372036854775807 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775808 +(-1,-1) +-1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-5 +(0,-5) +0 +-5 +# +-4 +(0,-4) +0 +-4 +# +-3 +(0,-3) +0 +-3 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775808 +(-1,-1) +-1 +-1 +# +divide by (maxBound - 1) +9223372036854775807 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(0,9223372036854775805) +0 +9223372036854775805 +# +9223372036854775806 +(1,0) +1 +0 +# +9223372036854775807 +(1,1) +1 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-9 +(0,-9) +0 +-9 +# +-8 +(0,-8) +0 +-8 +# +-7 +(0,-7) +0 +-7 +# +9223372036854775805 +(0,9223372036854775805) +0 +9223372036854775805 +# +9223372036854775806 +(1,0) +1 +0 +# +9223372036854775807 +(1,1) +1 +1 +# +divide by -1 +9223372036854775807 +(-9223372036854775807,0) +-9223372036854775807 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(-1,0) +-1 +0 +# +4611686018427387902 +(-4611686018427387902,0) +-4611686018427387902 +0 +# +4611686018427387903 +(-4611686018427387903,0) +-4611686018427387903 +0 +# +4611686018427387904 +(-4611686018427387904,0) +-4611686018427387904 +0 +# +-5 +(5,0) +5 +0 +# +-4 +(4,0) +4 +0 +# +-3 +(3,0) +3 +0 +# +-2 +(2,0) +2 +0 +# +-1 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by -2 +9223372036854775807 +(-4611686018427387903,1) +-4611686018427387903 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(-4611686018427387902,1) +-4611686018427387902 +1 +# +9223372036854775806 +(-4611686018427387903,0) +-4611686018427387903 +0 +# +9223372036854775807 +(-4611686018427387903,1) +-4611686018427387903 +1 +# +4611686018427387901 +(-2305843009213693950,1) +-2305843009213693950 +1 +# +4611686018427387902 +(-2305843009213693951,0) +-2305843009213693951 +0 +# +4611686018427387903 +(-2305843009213693951,1) +-2305843009213693951 +1 +# +-9 +(4,-1) +4 +-1 +# +-8 +(4,0) +4 +0 +# +-7 +(3,-1) +3 +-1 +# +-3 +(1,-1) +1 +-1 +# +-2 +(1,0) +1 +0 +# +-1 +(0,-1) +0 +-1 +# +divide by -4 +9223372036854775807 +(-2305843009213693951,3) +-2305843009213693951 +3 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775803 +(-2305843009213693950,3) +-2305843009213693950 +3 +# +9223372036854775804 +(-2305843009213693951,0) +-2305843009213693951 +0 +# +9223372036854775805 +(-2305843009213693951,1) +-2305843009213693951 +1 +# +4611686018427387899 +(-1152921504606846974,3) +-1152921504606846974 +3 +# +4611686018427387900 +(-1152921504606846975,0) +-1152921504606846975 +0 +# +4611686018427387901 +(-1152921504606846975,1) +-1152921504606846975 +1 +# +-17 +(4,-1) +4 +-1 +# +-16 +(4,0) +4 +0 +# +-15 +(3,-3) +3 +-3 +# +-5 +(1,-1) +1 +-1 +# +-4 +(1,0) +1 +0 +# +-3 +(0,-3) +0 +-3 +# +divide by -3 +9223372036854775807 +(-3074457345618258602,1) +-3074457345618258602 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775805 +(-3074457345618258601,2) +-3074457345618258601 +2 +# +9223372036854775806 +(-3074457345618258602,0) +-3074457345618258602 +0 +# +9223372036854775807 +(-3074457345618258602,1) +-3074457345618258602 +1 +# +4611686018427387902 +(-1537228672809129300,2) +-1537228672809129300 +2 +# +4611686018427387903 +(-1537228672809129301,0) +-1537228672809129301 +0 +# +4611686018427387904 +(-1537228672809129301,1) +-1537228672809129301 +1 +# +-13 +(4,-1) +4 +-1 +# +-12 +(4,0) +4 +0 +# +-11 +(3,-2) +3 +-2 +# +-4 +(1,-1) +1 +-1 +# +-3 +(1,0) +1 +0 +# +-2 +(0,-2) +0 +-2 +# +divide by -5 +9223372036854775807 +(-1844674407370955161,2) +-1844674407370955161 +2 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775804 +(-1844674407370955160,4) +-1844674407370955160 +4 +# +9223372036854775805 +(-1844674407370955161,0) +-1844674407370955161 +0 +# +9223372036854775806 +(-1844674407370955161,1) +-1844674407370955161 +1 +# +4611686018427387899 +(-922337203685477579,4) +-922337203685477579 +4 +# +4611686018427387900 +(-922337203685477580,0) +-922337203685477580 +0 +# +4611686018427387901 +(-922337203685477580,1) +-922337203685477580 +1 +# +-21 +(4,-1) +4 +-1 +# +-20 +(4,0) +4 +0 +# +-19 +(3,-4) +3 +-4 +# +-6 +(1,-1) +1 +-1 +# +-5 +(1,0) +1 +0 +# +-4 +(0,-4) +0 +-4 +# +divide by -7 +9223372036854775807 +(-1317624576693539401,0) +-1317624576693539401 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(-1317624576693539400,6) +-1317624576693539400 +6 +# +9223372036854775807 +(-1317624576693539401,0) +-1317624576693539401 +0 +# +-9223372036854775808 +(1317624576693539401,-1) +1317624576693539401 +-1 +# +4611686018427387899 +(-658812288346769699,6) +-658812288346769699 +6 +# +4611686018427387900 +(-658812288346769700,0) +-658812288346769700 +0 +# +4611686018427387901 +(-658812288346769700,1) +-658812288346769700 +1 +# +-29 +(4,-1) +4 +-1 +# +-28 +(4,0) +4 +0 +# +-27 +(3,-6) +3 +-6 +# +-8 +(1,-1) +1 +-1 +# +-7 +(1,0) +1 +0 +# +-6 +(0,-6) +0 +-6 +# +divide by -14 +9223372036854775807 +(-658812288346769700,7) +-658812288346769700 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(-658812288346769699,13) +-658812288346769699 +13 +# +9223372036854775800 +(-658812288346769700,0) +-658812288346769700 +0 +# +9223372036854775801 +(-658812288346769700,1) +-658812288346769700 +1 +# +4611686018427387899 +(-329406144173384849,13) +-329406144173384849 +13 +# +4611686018427387900 +(-329406144173384850,0) +-329406144173384850 +0 +# +4611686018427387901 +(-329406144173384850,1) +-329406144173384850 +1 +# +-57 +(4,-1) +4 +-1 +# +-56 +(4,0) +4 +0 +# +-55 +(3,-13) +3 +-13 +# +-15 +(1,-1) +1 +-1 +# +-14 +(1,0) +1 +0 +# +-13 +(0,-13) +0 +-13 +# +divide by -25 +9223372036854775807 +(-368934881474191032,7) +-368934881474191032 +7 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775799 +(-368934881474191031,24) +-368934881474191031 +24 +# +9223372036854775800 +(-368934881474191032,0) +-368934881474191032 +0 +# +9223372036854775801 +(-368934881474191032,1) +-368934881474191032 +1 +# +4611686018427387899 +(-184467440737095515,24) +-184467440737095515 +24 +# +4611686018427387900 +(-184467440737095516,0) +-184467440737095516 +0 +# +4611686018427387901 +(-184467440737095516,1) +-184467440737095516 +1 +# +-101 +(4,-1) +4 +-1 +# +-100 +(4,0) +4 +0 +# +-99 +(3,-24) +3 +-24 +# +-26 +(1,-1) +1 +-1 +# +-25 +(1,0) +1 +0 +# +-24 +(0,-24) +0 +-24 +# +divide by minBound +9223372036854775807 +(0,9223372036854775807) +0 +9223372036854775807 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775807 +(0,9223372036854775807) +0 +9223372036854775807 +# +-9223372036854775808 +(1,0) +1 +0 +# +-9223372036854775807 +(0,-9223372036854775807) +0 +-9223372036854775807 +# +divide by (minBound + 1) +9223372036854775807 +(-1,0) +-1 +0 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +9223372036854775806 +(0,9223372036854775806) +0 +9223372036854775806 +# +9223372036854775807 +(-1,0) +-1 +0 +# +-9223372036854775808 +(1,-1) +1 +-1 +# +-1 +(0,-1) +0 +-1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +3 +(0,3) +0 +3 +# +4 +(0,4) +0 +4 +# +5 +(0,5) +0 +5 +# +-9223372036854775808 +(1,-1) +1 +-1 +# +-9223372036854775807 +(1,0) +1 +0 +# +-9223372036854775806 +(0,-9223372036854775806) +0 +-9223372036854775806 +# +-------------------------------- +--Testing Word +-------------------------------- +divide by 1 +4294967295 +(4294967295,0) +4294967295 +0 +# +4294967295 +(4294967295,0) +4294967295 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +4294967294 +(4294967294,0) +4294967294 +0 +# +4294967295 +(4294967295,0) +4294967295 +0 +# +0 +(0,0) +0 +0 +# +2147483646 +(2147483646,0) +2147483646 +0 +# +2147483647 +(2147483647,0) +2147483647 +0 +# +2147483648 +(2147483648,0) +2147483648 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +4294967295 +(2147483647,1) +2147483647 +1 +# +4294967295 +(2147483647,1) +2147483647 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967293 +(2147483646,1) +2147483646 +1 +# +4294967294 +(2147483647,0) +2147483647 +0 +# +4294967295 +(2147483647,1) +2147483647 +1 +# +2147483645 +(1073741822,1) +1073741822 +1 +# +2147483646 +(1073741823,0) +1073741823 +0 +# +2147483647 +(1073741823,1) +1073741823 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +4294967295 +(1073741823,3) +1073741823 +3 +# +4294967295 +(1073741823,3) +1073741823 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(1073741822,3) +1073741822 +3 +# +4294967292 +(1073741823,0) +1073741823 +0 +# +4294967293 +(1073741823,1) +1073741823 +1 +# +2147483643 +(536870910,3) +536870910 +3 +# +2147483644 +(536870911,0) +536870911 +0 +# +2147483645 +(536870911,1) +536870911 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +4294967295 +(1431655765,0) +1431655765 +0 +# +4294967295 +(1431655765,0) +1431655765 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967294 +(1431655764,2) +1431655764 +2 +# +4294967295 +(1431655765,0) +1431655765 +0 +# +0 +(0,0) +0 +0 +# +2147483645 +(715827881,2) +715827881 +2 +# +2147483646 +(715827882,0) +715827882 +0 +# +2147483647 +(715827882,1) +715827882 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +4294967295 +(858993459,0) +858993459 +0 +# +4294967295 +(858993459,0) +858993459 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967294 +(858993458,4) +858993458 +4 +# +4294967295 +(858993459,0) +858993459 +0 +# +0 +(0,0) +0 +0 +# +2147483644 +(429496728,4) +429496728 +4 +# +2147483645 +(429496729,0) +429496729 +0 +# +2147483646 +(429496729,1) +429496729 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +4294967295 +(613566756,3) +613566756 +3 +# +4294967295 +(613566756,3) +613566756 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(613566755,6) +613566755 +6 +# +4294967292 +(613566756,0) +613566756 +0 +# +4294967293 +(613566756,1) +613566756 +1 +# +2147483645 +(306783377,6) +306783377 +6 +# +2147483646 +(306783378,0) +306783378 +0 +# +2147483647 +(306783378,1) +306783378 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +4294967295 +(306783378,3) +306783378 +3 +# +4294967295 +(306783378,3) +306783378 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(306783377,13) +306783377 +13 +# +4294967292 +(306783378,0) +306783378 +0 +# +4294967293 +(306783378,1) +306783378 +1 +# +2147483645 +(153391688,13) +153391688 +13 +# +2147483646 +(153391689,0) +153391689 +0 +# +2147483647 +(153391689,1) +153391689 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +4294967295 +(171798691,20) +171798691 +20 +# +4294967295 +(171798691,20) +171798691 +20 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967274 +(171798690,24) +171798690 +24 +# +4294967275 +(171798691,0) +171798691 +0 +# +4294967276 +(171798691,1) +171798691 +1 +# +2147483624 +(85899344,24) +85899344 +24 +# +2147483625 +(85899345,0) +85899345 +0 +# +2147483626 +(85899345,1) +85899345 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +4294967295 +(1,0) +1 +0 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(0,4294967291) +0 +4294967291 +# +4294967292 +(0,4294967292) +0 +4294967292 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(0,4294967294) +0 +4294967294 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +4294967295 +(1,1) +1 +1 +# +4294967295 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(1,0) +1 +0 +# +4294967295 +(1,1) +1 +1 +# +4294967295 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967287 +(0,4294967287) +0 +4294967287 +# +4294967288 +(0,4294967288) +0 +4294967288 +# +4294967289 +(0,4294967289) +0 +4294967289 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(1,0) +1 +0 +# +4294967295 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word8 +-------------------------------- +divide by 1 +255 +(255,0) +255 +0 +# +255 +(255,0) +255 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +254 +(254,0) +254 +0 +# +255 +(255,0) +255 +0 +# +0 +(0,0) +0 +0 +# +126 +(126,0) +126 +0 +# +127 +(127,0) +127 +0 +# +128 +(128,0) +128 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +255 +(127,1) +127 +1 +# +255 +(127,1) +127 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +253 +(126,1) +126 +1 +# +254 +(127,0) +127 +0 +# +255 +(127,1) +127 +1 +# +125 +(62,1) +62 +1 +# +126 +(63,0) +63 +0 +# +127 +(63,1) +63 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +255 +(63,3) +63 +3 +# +255 +(63,3) +63 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(62,3) +62 +3 +# +252 +(63,0) +63 +0 +# +253 +(63,1) +63 +1 +# +123 +(30,3) +30 +3 +# +124 +(31,0) +31 +0 +# +125 +(31,1) +31 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +255 +(85,0) +85 +0 +# +255 +(85,0) +85 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +254 +(84,2) +84 +2 +# +255 +(85,0) +85 +0 +# +0 +(0,0) +0 +0 +# +125 +(41,2) +41 +2 +# +126 +(42,0) +42 +0 +# +127 +(42,1) +42 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +255 +(51,0) +51 +0 +# +255 +(51,0) +51 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +254 +(50,4) +50 +4 +# +255 +(51,0) +51 +0 +# +0 +(0,0) +0 +0 +# +124 +(24,4) +24 +4 +# +125 +(25,0) +25 +0 +# +126 +(25,1) +25 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +255 +(36,3) +36 +3 +# +255 +(36,3) +36 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(35,6) +35 +6 +# +252 +(36,0) +36 +0 +# +253 +(36,1) +36 +1 +# +125 +(17,6) +17 +6 +# +126 +(18,0) +18 +0 +# +127 +(18,1) +18 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +255 +(18,3) +18 +3 +# +255 +(18,3) +18 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(17,13) +17 +13 +# +252 +(18,0) +18 +0 +# +253 +(18,1) +18 +1 +# +125 +(8,13) +8 +13 +# +126 +(9,0) +9 +0 +# +127 +(9,1) +9 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +255 +(10,5) +10 +5 +# +255 +(10,5) +10 +5 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +249 +(9,24) +9 +24 +# +250 +(10,0) +10 +0 +# +251 +(10,1) +10 +1 +# +124 +(4,24) +4 +24 +# +125 +(5,0) +5 +0 +# +126 +(5,1) +5 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +255 +(1,0) +1 +0 +# +255 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +255 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +251 +(0,251) +0 +251 +# +252 +(0,252) +0 +252 +# +253 +(0,253) +0 +253 +# +254 +(0,254) +0 +254 +# +255 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +255 +(1,1) +1 +1 +# +255 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +253 +(0,253) +0 +253 +# +254 +(1,0) +1 +0 +# +255 +(1,1) +1 +1 +# +255 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +247 +(0,247) +0 +247 +# +248 +(0,248) +0 +248 +# +249 +(0,249) +0 +249 +# +253 +(0,253) +0 +253 +# +254 +(1,0) +1 +0 +# +255 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word16 +-------------------------------- +divide by 1 +65535 +(65535,0) +65535 +0 +# +65535 +(65535,0) +65535 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +65534 +(65534,0) +65534 +0 +# +65535 +(65535,0) +65535 +0 +# +0 +(0,0) +0 +0 +# +32766 +(32766,0) +32766 +0 +# +32767 +(32767,0) +32767 +0 +# +32768 +(32768,0) +32768 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +65535 +(32767,1) +32767 +1 +# +65535 +(32767,1) +32767 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(32766,1) +32766 +1 +# +65534 +(32767,0) +32767 +0 +# +65535 +(32767,1) +32767 +1 +# +32765 +(16382,1) +16382 +1 +# +32766 +(16383,0) +16383 +0 +# +32767 +(16383,1) +16383 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +65535 +(16383,3) +16383 +3 +# +65535 +(16383,3) +16383 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65531 +(16382,3) +16382 +3 +# +65532 +(16383,0) +16383 +0 +# +65533 +(16383,1) +16383 +1 +# +32763 +(8190,3) +8190 +3 +# +32764 +(8191,0) +8191 +0 +# +32765 +(8191,1) +8191 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +65535 +(21845,0) +21845 +0 +# +65535 +(21845,0) +21845 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65534 +(21844,2) +21844 +2 +# +65535 +(21845,0) +21845 +0 +# +0 +(0,0) +0 +0 +# +32765 +(10921,2) +10921 +2 +# +32766 +(10922,0) +10922 +0 +# +32767 +(10922,1) +10922 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +65535 +(13107,0) +13107 +0 +# +65535 +(13107,0) +13107 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65534 +(13106,4) +13106 +4 +# +65535 +(13107,0) +13107 +0 +# +0 +(0,0) +0 +0 +# +32764 +(6552,4) +6552 +4 +# +32765 +(6553,0) +6553 +0 +# +32766 +(6553,1) +6553 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +65535 +(9362,1) +9362 +1 +# +65535 +(9362,1) +9362 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(9361,6) +9361 +6 +# +65534 +(9362,0) +9362 +0 +# +65535 +(9362,1) +9362 +1 +# +32766 +(4680,6) +4680 +6 +# +32767 +(4681,0) +4681 +0 +# +32768 +(4681,1) +4681 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +65535 +(4681,1) +4681 +1 +# +65535 +(4681,1) +4681 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(4680,13) +4680 +13 +# +65534 +(4681,0) +4681 +0 +# +65535 +(4681,1) +4681 +1 +# +32759 +(2339,13) +2339 +13 +# +32760 +(2340,0) +2340 +0 +# +32761 +(2340,1) +2340 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +65535 +(2621,10) +2621 +10 +# +65535 +(2621,10) +2621 +10 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65524 +(2620,24) +2620 +24 +# +65525 +(2621,0) +2621 +0 +# +65526 +(2621,1) +2621 +1 +# +32749 +(1309,24) +1309 +24 +# +32750 +(1310,0) +1310 +0 +# +32751 +(1310,1) +1310 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +65535 +(1,0) +1 +0 +# +65535 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65535 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65531 +(0,65531) +0 +65531 +# +65532 +(0,65532) +0 +65532 +# +65533 +(0,65533) +0 +65533 +# +65534 +(0,65534) +0 +65534 +# +65535 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +65535 +(1,1) +1 +1 +# +65535 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65533 +(0,65533) +0 +65533 +# +65534 +(1,0) +1 +0 +# +65535 +(1,1) +1 +1 +# +65535 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +65527 +(0,65527) +0 +65527 +# +65528 +(0,65528) +0 +65528 +# +65529 +(0,65529) +0 +65529 +# +65533 +(0,65533) +0 +65533 +# +65534 +(1,0) +1 +0 +# +65535 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word32 +-------------------------------- +divide by 1 +4294967295 +(4294967295,0) +4294967295 +0 +# +4294967295 +(4294967295,0) +4294967295 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +4294967294 +(4294967294,0) +4294967294 +0 +# +4294967295 +(4294967295,0) +4294967295 +0 +# +0 +(0,0) +0 +0 +# +2147483646 +(2147483646,0) +2147483646 +0 +# +2147483647 +(2147483647,0) +2147483647 +0 +# +2147483648 +(2147483648,0) +2147483648 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +4294967295 +(2147483647,1) +2147483647 +1 +# +4294967295 +(2147483647,1) +2147483647 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967293 +(2147483646,1) +2147483646 +1 +# +4294967294 +(2147483647,0) +2147483647 +0 +# +4294967295 +(2147483647,1) +2147483647 +1 +# +2147483645 +(1073741822,1) +1073741822 +1 +# +2147483646 +(1073741823,0) +1073741823 +0 +# +2147483647 +(1073741823,1) +1073741823 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +4294967295 +(1073741823,3) +1073741823 +3 +# +4294967295 +(1073741823,3) +1073741823 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(1073741822,3) +1073741822 +3 +# +4294967292 +(1073741823,0) +1073741823 +0 +# +4294967293 +(1073741823,1) +1073741823 +1 +# +2147483643 +(536870910,3) +536870910 +3 +# +2147483644 +(536870911,0) +536870911 +0 +# +2147483645 +(536870911,1) +536870911 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +4294967295 +(1431655765,0) +1431655765 +0 +# +4294967295 +(1431655765,0) +1431655765 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967294 +(1431655764,2) +1431655764 +2 +# +4294967295 +(1431655765,0) +1431655765 +0 +# +0 +(0,0) +0 +0 +# +2147483645 +(715827881,2) +715827881 +2 +# +2147483646 +(715827882,0) +715827882 +0 +# +2147483647 +(715827882,1) +715827882 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +4294967295 +(858993459,0) +858993459 +0 +# +4294967295 +(858993459,0) +858993459 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967294 +(858993458,4) +858993458 +4 +# +4294967295 +(858993459,0) +858993459 +0 +# +0 +(0,0) +0 +0 +# +2147483644 +(429496728,4) +429496728 +4 +# +2147483645 +(429496729,0) +429496729 +0 +# +2147483646 +(429496729,1) +429496729 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +4294967295 +(613566756,3) +613566756 +3 +# +4294967295 +(613566756,3) +613566756 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(613566755,6) +613566755 +6 +# +4294967292 +(613566756,0) +613566756 +0 +# +4294967293 +(613566756,1) +613566756 +1 +# +2147483645 +(306783377,6) +306783377 +6 +# +2147483646 +(306783378,0) +306783378 +0 +# +2147483647 +(306783378,1) +306783378 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +4294967295 +(306783378,3) +306783378 +3 +# +4294967295 +(306783378,3) +306783378 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(306783377,13) +306783377 +13 +# +4294967292 +(306783378,0) +306783378 +0 +# +4294967293 +(306783378,1) +306783378 +1 +# +2147483645 +(153391688,13) +153391688 +13 +# +2147483646 +(153391689,0) +153391689 +0 +# +2147483647 +(153391689,1) +153391689 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +4294967295 +(171798691,20) +171798691 +20 +# +4294967295 +(171798691,20) +171798691 +20 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967274 +(171798690,24) +171798690 +24 +# +4294967275 +(171798691,0) +171798691 +0 +# +4294967276 +(171798691,1) +171798691 +1 +# +2147483624 +(85899344,24) +85899344 +24 +# +2147483625 +(85899345,0) +85899345 +0 +# +2147483626 +(85899345,1) +85899345 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +4294967295 +(1,0) +1 +0 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967291 +(0,4294967291) +0 +4294967291 +# +4294967292 +(0,4294967292) +0 +4294967292 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(0,4294967294) +0 +4294967294 +# +4294967295 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +4294967295 +(1,1) +1 +1 +# +4294967295 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(1,0) +1 +0 +# +4294967295 +(1,1) +1 +1 +# +4294967295 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +4294967287 +(0,4294967287) +0 +4294967287 +# +4294967288 +(0,4294967288) +0 +4294967288 +# +4294967289 +(0,4294967289) +0 +4294967289 +# +4294967293 +(0,4294967293) +0 +4294967293 +# +4294967294 +(1,0) +1 +0 +# +4294967295 +(1,1) +1 +1 +# +-------------------------------- +--Testing Word64 +-------------------------------- +divide by 1 +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +18446744073709551614 +(18446744073709551614,0) +18446744073709551614 +0 +# +18446744073709551615 +(18446744073709551615,0) +18446744073709551615 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775806 +(9223372036854775806,0) +9223372036854775806 +0 +# +9223372036854775807 +(9223372036854775807,0) +9223372036854775807 +0 +# +9223372036854775808 +(9223372036854775808,0) +9223372036854775808 +0 +# +3 +(3,0) +3 +0 +# +4 +(4,0) +4 +0 +# +5 +(5,0) +5 +0 +# +0 +(0,0) +0 +0 +# +1 +(1,0) +1 +0 +# +2 +(2,0) +2 +0 +# +divide by 2 +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(9223372036854775806,1) +9223372036854775806 +1 +# +18446744073709551614 +(9223372036854775807,0) +9223372036854775807 +0 +# +18446744073709551615 +(9223372036854775807,1) +9223372036854775807 +1 +# +9223372036854775805 +(4611686018427387902,1) +4611686018427387902 +1 +# +9223372036854775806 +(4611686018427387903,0) +4611686018427387903 +0 +# +9223372036854775807 +(4611686018427387903,1) +4611686018427387903 +1 +# +7 +(3,1) +3 +1 +# +8 +(4,0) +4 +0 +# +9 +(4,1) +4 +1 +# +1 +(0,1) +0 +1 +# +2 +(1,0) +1 +0 +# +3 +(1,1) +1 +1 +# +divide by 4 +18446744073709551615 +(4611686018427387903,3) +4611686018427387903 +3 +# +18446744073709551615 +(4611686018427387903,3) +4611686018427387903 +3 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551611 +(4611686018427387902,3) +4611686018427387902 +3 +# +18446744073709551612 +(4611686018427387903,0) +4611686018427387903 +0 +# +18446744073709551613 +(4611686018427387903,1) +4611686018427387903 +1 +# +9223372036854775803 +(2305843009213693950,3) +2305843009213693950 +3 +# +9223372036854775804 +(2305843009213693951,0) +2305843009213693951 +0 +# +9223372036854775805 +(2305843009213693951,1) +2305843009213693951 +1 +# +15 +(3,3) +3 +3 +# +16 +(4,0) +4 +0 +# +17 +(4,1) +4 +1 +# +3 +(0,3) +0 +3 +# +4 +(1,0) +1 +0 +# +5 +(1,1) +1 +1 +# +divide by 3 +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551614 +(6148914691236517204,2) +6148914691236517204 +2 +# +18446744073709551615 +(6148914691236517205,0) +6148914691236517205 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775805 +(3074457345618258601,2) +3074457345618258601 +2 +# +9223372036854775806 +(3074457345618258602,0) +3074457345618258602 +0 +# +9223372036854775807 +(3074457345618258602,1) +3074457345618258602 +1 +# +11 +(3,2) +3 +2 +# +12 +(4,0) +4 +0 +# +13 +(4,1) +4 +1 +# +2 +(0,2) +0 +2 +# +3 +(1,0) +1 +0 +# +4 +(1,1) +1 +1 +# +divide by 5 +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551614 +(3689348814741910322,4) +3689348814741910322 +4 +# +18446744073709551615 +(3689348814741910323,0) +3689348814741910323 +0 +# +0 +(0,0) +0 +0 +# +9223372036854775804 +(1844674407370955160,4) +1844674407370955160 +4 +# +9223372036854775805 +(1844674407370955161,0) +1844674407370955161 +0 +# +9223372036854775806 +(1844674407370955161,1) +1844674407370955161 +1 +# +19 +(3,4) +3 +4 +# +20 +(4,0) +4 +0 +# +21 +(4,1) +4 +1 +# +4 +(0,4) +0 +4 +# +5 +(1,0) +1 +0 +# +6 +(1,1) +1 +1 +# +divide by 7 +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(2635249153387078801,6) +2635249153387078801 +6 +# +18446744073709551614 +(2635249153387078802,0) +2635249153387078802 +0 +# +18446744073709551615 +(2635249153387078802,1) +2635249153387078802 +1 +# +9223372036854775806 +(1317624576693539400,6) +1317624576693539400 +6 +# +9223372036854775807 +(1317624576693539401,0) +1317624576693539401 +0 +# +9223372036854775808 +(1317624576693539401,1) +1317624576693539401 +1 +# +27 +(3,6) +3 +6 +# +28 +(4,0) +4 +0 +# +29 +(4,1) +4 +1 +# +6 +(0,6) +0 +6 +# +7 +(1,0) +1 +0 +# +8 +(1,1) +1 +1 +# +divide by 14 +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(1317624576693539400,13) +1317624576693539400 +13 +# +18446744073709551614 +(1317624576693539401,0) +1317624576693539401 +0 +# +18446744073709551615 +(1317624576693539401,1) +1317624576693539401 +1 +# +9223372036854775799 +(658812288346769699,13) +658812288346769699 +13 +# +9223372036854775800 +(658812288346769700,0) +658812288346769700 +0 +# +9223372036854775801 +(658812288346769700,1) +658812288346769700 +1 +# +55 +(3,13) +3 +13 +# +56 +(4,0) +4 +0 +# +57 +(4,1) +4 +1 +# +13 +(0,13) +0 +13 +# +14 +(1,0) +1 +0 +# +15 +(1,1) +1 +1 +# +divide by 25 +18446744073709551615 +(737869762948382064,15) +737869762948382064 +15 +# +18446744073709551615 +(737869762948382064,15) +737869762948382064 +15 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551599 +(737869762948382063,24) +737869762948382063 +24 +# +18446744073709551600 +(737869762948382064,0) +737869762948382064 +0 +# +18446744073709551601 +(737869762948382064,1) +737869762948382064 +1 +# +9223372036854775799 +(368934881474191031,24) +368934881474191031 +24 +# +9223372036854775800 +(368934881474191032,0) +368934881474191032 +0 +# +9223372036854775801 +(368934881474191032,1) +368934881474191032 +1 +# +99 +(3,24) +3 +24 +# +100 +(4,0) +4 +0 +# +101 +(4,1) +4 +1 +# +24 +(0,24) +0 +24 +# +25 +(1,0) +1 +0 +# +26 +(1,1) +1 +1 +# +divide by maxBound +18446744073709551615 +(1,0) +1 +0 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551611 +(0,18446744073709551611) +0 +18446744073709551611 +# +18446744073709551612 +(0,18446744073709551612) +0 +18446744073709551612 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(0,18446744073709551614) +0 +18446744073709551614 +# +18446744073709551615 +(1,0) +1 +0 +# +0 +(0,0) +0 +0 +# +divide by (maxBound - 1) +18446744073709551615 +(1,1) +1 +1 +# +18446744073709551615 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(1,0) +1 +0 +# +18446744073709551615 +(1,1) +1 +1 +# +18446744073709551615 +(1,1) +1 +1 +# +0 +(0,0) +0 +0 +# +1 +(0,1) +0 +1 +# +18446744073709551607 +(0,18446744073709551607) +0 +18446744073709551607 +# +18446744073709551608 +(0,18446744073709551608) +0 +18446744073709551608 +# +18446744073709551609 +(0,18446744073709551609) +0 +18446744073709551609 +# +18446744073709551613 +(0,18446744073709551613) +0 +18446744073709551613 +# +18446744073709551614 +(1,0) +1 +0 +# +18446744073709551615 +(1,1) +1 +1 +# diff --git a/testsuite/tests/numeric/should_run/mul2.hs b/testsuite/tests/numeric/should_run/mul2.hs index 474e421b40cd..59030d3e4a35 100644 --- a/testsuite/tests/numeric/should_run/mul2.hs +++ b/testsuite/tests/numeric/should_run/mul2.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} - import GHC.Exts +import GHC.Int import GHC.Word import Data.Bits @@ -9,6 +9,9 @@ main :: IO () main = do f 5 6 f 0xFD94E3B7FE36FB18 49 f 0xFD94E3B7FE36FB18 0xFC1D8A3BFB29FC6A + g 5 6 + g 0xFD94E3B7FE36FB18 49 + g 0xFD94E3B7FE36FB18 0xFC1D8A3BFB29FC6A f :: Word -> Word -> IO () f wx@(W# x) wy@(W# y) @@ -23,4 +26,20 @@ f wx@(W# x) wy@(W# y) putStrLn ("High: " ++ show wh) putStrLn ("Low: " ++ show wl) putStrLn ("Result: " ++ show (r :: Integer)) +{-# INLINE f #-} +g :: Int -> Int -> IO () +g ix@(I# x) iy@(I# y) + = do putStrLn "-----" + putStrLn ("Doing " ++ show ix ++ " * " ++ show iy) + case x `timesInt2#` y of + (# needsHigh, h, l #) -> + do let ih = I# h + il = I# l + r = shiftL (fromIntegral ih) (bitSize ih) + .|. (fromIntegral @Word @Integer $ fromIntegral @Int @Word il) + putStrLn ("Needs high: " ++ show (isTrue# needsHigh)) + putStrLn ("High: " ++ show ih) + putStrLn ("Low: " ++ show il) + putStrLn ("Result: " ++ show (r :: Integer)) +{-# INLINE g #-} diff --git a/testsuite/tests/numeric/should_run/mul2.stdout b/testsuite/tests/numeric/should_run/mul2.stdout index 1a5107c9c7e2..b6730bc7c74b 100644 --- a/testsuite/tests/numeric/should_run/mul2.stdout +++ b/testsuite/tests/numeric/should_run/mul2.stdout @@ -13,3 +13,21 @@ Doing 18272479967532481304 * 18166828462103985258 High: 17995208684035254268 Low: 13422369508946319344 Result: 331953009147393985806713771139776616432 +----- +Doing 5 * 6 +Needs high: False +High: 0 +Low: 30 +Result: 30 +----- +Doing -174264106177070312 * 49 +Needs high: False +High: -1 +Low: -8538941202676445288 +Result: -8538941202676445288 +----- +Doing -174264106177070312 * -279915611605566358 +Needs high: True +High: 2644328108339322 +Low: -5024374564763232272 +Result: 48779243861451990681214403947763696 diff --git a/testsuite/tests/numeric/should_run/mul2.stdout-ws-32 b/testsuite/tests/numeric/should_run/mul2.stdout-ws-32 index 78b06d5c1b3c..23f0efdaa93e 100644 --- a/testsuite/tests/numeric/should_run/mul2.stdout-ws-32 +++ b/testsuite/tests/numeric/should_run/mul2.stdout-ws-32 @@ -13,3 +13,21 @@ Doing 4265016088 * 4213832810 High: 4184447398 Low: 549951472 Result: 17972064726792247280 +----- +Doing 5 * 6 +Needs high: False +High: 0 +Low: 30 +Result: 30 +----- +Doing -29951208 * 49 +Needs high: False +High: -1 +Low: -1467609192 +Result: -1467609192 +----- +Doing -29951208 * -81134486 +Needs high: True +High: 565796 +Low: 549951472 +Result: 2430075866159088 -- GitLab