Skip to content
Snippets Groups Projects
Commit b0a1ed55 authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Add test for T15547 (#15547)

Fix #15547
parent 7b67724b
No related merge requests found
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module T15547 where
import GHC.TypeNats
import Data.Proxy
import GHC.Word
import GHC.Exts
nat2Word# :: KnownNat n => Proxy# n -> Word#
nat2Word# p = case fromIntegral (natVal' p) of
W# w -> w
foo (# #) = nat2Word# (proxy# :: Proxy# 18)
-- functions from the ticket
fd (_ :: Proxy n) = nat2Word# (proxy# @(Div (n + 63) 64))
fm (_ :: Proxy n) = nat2Word# (proxy# @(Mod (n - 1) 64 + 1))
fp (_ :: Proxy n) = nat2Word# (proxy# @(2^(Mod (n + 63) 64 + 1)))
d (# #) = fd (Proxy @137)
m (# #) = fm (Proxy @137)
p (# #) = fp (Proxy @137)
==================== Tidy Core ====================
Result size of Tidy Core
= {terms: 40, types: 100, coercions: 56, joins: 0/0}
nat2Word#
= \ @n $dKnownNat _ ->
integerToWord#
(integerFromNatural
($dKnownNat `cast` <Co:5> :: KnownNat n ~R# Natural))
foo = \ _ -> 18##
fd
= \ @n $dKnownNat _ ->
integerToWord#
(integerFromNatural
($dKnownNat
`cast` <Co:13> :: KnownNat (Div (n + 63) 64) ~R# Natural))
d = \ _ -> 3##
fm
= \ @n $dKnownNat _ ->
integerToWord#
(integerFromNatural
($dKnownNat
`cast` <Co:17> :: KnownNat (Mod (n - 1) 64 + 1) ~R# Natural))
m = \ _ -> 9##
fp
= \ @n $dKnownNat _ ->
integerToWord#
(integerFromNatural
($dKnownNat
`cast` <Co:21> :: KnownNat (2 ^ (Mod (n + 63) 64 + 1))
~R# Natural))
p = \ _ -> 512##
......@@ -18,3 +18,4 @@ test('T19769', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-b
test('T20347', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-binds -dsuppress-uniques'])
test('T20448', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-binds -dsuppress-uniques'])
test('T19641', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-binds -dsuppress-uniques'])
test('T15547', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-binds -dsuppress-uniques'])
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