Skip to content

Instantly share code, notes, and snippets.

@erantapaa
Created September 28, 2015 17:06
Show Gist options
  • Save erantapaa/1aaf6928e2f205557bf5 to your computer and use it in GitHub Desktop.
Save erantapaa/1aaf6928e2f205557bf5 to your computer and use it in GitHub Desktop.
modular arithmetic example using Data.Reflection
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleContexts #-}
import Data.Reflection
import Data.Proxy
data M a s = M a -- Note the phantom comes *after* the concrete
-- In `normalize` we're tying the knot to get the phantom types to align
-- note that reflect :: Reifies s a => forall proxy. proxy s -> a
normalize :: (Reifies s a, Integral a) => a -> M a s
normalize a = b where b = M (mod a (reflect b))
instance (Reifies s a, Integral a) => Num (M a s) where
M a + M b = normalize (a + b)
M a - M b = normalize (a - b)
M a * M b = normalize (a * b)
fromInteger n = normalize (fromInteger n)
abs _ = error "abs not implemented"
signum _ = error "sgn not implemented"
withModulus :: Integral a => a -> (forall s. Reifies s a => M a s) -> a
withModulus m ma = reify m (runM . asProxyOf ma)
where asProxyOf :: f s -> Proxy s -> f s
asProxyOf a _ = a
runM :: M a s -> a
runM (M a) = a
example :: (Reifies s a, Integral a) => M a s
example = normalize 3
example2 :: (Reifies s a, Integral a, Num (M a s)) => M a s
example2 = 3*3 + 5*5
mfactorial :: (Reifies s a, Integral a, Num (M a s)) => Int -> M a s
mfactorial n = product $ map fromIntegral [1..n]
test1 p n = withModulus p $ mfactorial n
madd :: (Reifies s Int, Num (M Int s)) => M Int s -> M Int s -> M Int s
madd a b = a + b
test2 :: Int -> Int -> Int -> Int
test2 p a b = withModulus p $ madd (fromIntegral a) (fromIntegral b)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment