Skip to content

Instantly share code, notes, and snippets.

@olligobber
Created November 29, 2021 04:55
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save olligobber/6279b1ca56d84ff87d22bc00b256c30b to your computer and use it in GitHub Desktop.
Save olligobber/6279b1ca56d84ff87d22bc00b256c30b to your computer and use it in GitHub Desktop.
A type for doing modulo arithmetic that forces all calculations to use the same mod at a type level, but allows the mod to be decided by a value
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
module ModArith
( WithMod
, IntMod
, doMod
) where
import Control.Applicative (liftA2)
newtype WithMod n x = WithMod { getMod :: Integer -> x }
instance Functor (WithMod n) where
fmap f (WithMod g) = WithMod $ f <$> g
instance Applicative (WithMod n) where
pure = WithMod . pure
WithMod f <*> WithMod g = WithMod $ f <*> g
instance Monad (WithMod n) where
WithMod f >>= g = WithMod $ \x -> (getMod $ g $ f x) x
doMod :: Integer -> (forall n. WithMod n x) -> x
doMod i (WithMod f) = f i
type IntMod n = WithMod n Integer
-- Force an IntMod into the range 0..n-1
normalise :: IntMod n -> IntMod n
normalise (WithMod f) = WithMod $ \x -> f x `mod` x
instance Num (WithMod n Integer) where
(+) = (normalise .) . liftA2 (+)
(-) = (normalise .) . liftA2 (-)
(*) = (normalise .) . liftA2 (*)
negate = normalise . fmap negate
abs = id
signum = id
fromInteger = normalise . pure
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment