Skip to content
Snippets Groups Projects
Commit 8eff62a4 authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

testsuite: Add test for #22282

This will complement mpickering's more general port of foundation's
numerical testsuite, providing a test for the specific case found
in #22282.
parent ee0deb80
No related branches found
No related tags found
No related merge requests found
import T22282A
main = print $ testF 217 161
217
{-# OPTIONS_GHC -O1 #-}
{-# LANGUAGE MagicHash #-}
module T22282A where
import Data.Word
import GHC.Prim
import GHC.Word
wtestF :: GHC.Prim.Word8# -> GHC.Prim.Word8# -> GHC.Prim.Word8#
wtestF a b = case word8ToWord# b of
0## -> a
_ -> plusWord8# (timesWord8# (quotWord8# a b) b) (remWord8# a b)
{-# NOINLINE wtestF #-}
testF :: Word8 -> Word8 -> Word8
testF (W8# a) (W8# b) = W8# (wtestF a b)
{-# INLINE testF #-}
......@@ -78,3 +78,4 @@ test('T19931', normal, compile_and_run, ['-O2'])
test('IntegerToFloat', normal, compile_and_run, [''])
test('T20291', normal, compile_and_run, [''])
test('T22282', normal, compile_and_run, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment