Skip to content

Instantly share code, notes, and snippets.

@parsonsmatt
Created December 10, 2017 16:04
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 parsonsmatt/e8ef704e5f61177d8ef0b52f7bae1bf6 to your computer and use it in GitHub Desktop.
Save parsonsmatt/e8ef704e5f61177d8ef0b52f7bae1bf6 to your computer and use it in GitHub Desktop.
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
import GHC.TypeLits
import Data.Proxy
newtype ModList (mod :: Nat) a = ModList { unModList :: [a] }
deriving Show
instance (KnownNat mod, Integral a, Num a) => Num (ModList mod a) where
fromInteger = ModList . repeat . fromInteger . (`mod` natVal (Proxy :: Proxy mod))
ModList as + ModList bs =
ModList $ zipWith (\x y -> (x + y) `mod` m) as bs
where
m = fromInteger (natVal (Proxy :: Proxy mod))
ModList as * ModList bs =
error "WHat does multiplication mean here?"
negate (ModList as) =
error "What does negation mean?"
abs (ModList as) =
error "Figure this out, too"
signum (ModList as) =
error "I guess this is always positive?"
fromList :: forall a mod. (Integral a, Num a, KnownNat mod) => [a] -> ModList mod a
fromList = ModList . fmap (`mod` fromInteger (natVal (Proxy :: Proxy mod)))
fromListP :: forall a mod. (Integral a, Num a, KnownNat mod) => Proxy mod -> [a] -> ModList mod a
fromListP _ = ModList . fmap (`mod` fromInteger (natVal (Proxy :: Proxy mod)))
{-
λ> :set -XDataKinds
λ> fromList [1..5] :: ModList 3 Integer
ModList {unModList = [1,2,0,1,2]}
λ> let threes = 3 :: ModList 3 Integer
λ> threes + fromList [1..7]
ModList {unModList = [1,2,0,1,2,0,1]}
λ> threes + fromList [2..100]
ModList {unModList = [2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,
0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1,2,0,1]}
λ>
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment