Skip to content

Instantly share code, notes, and snippets.

@simonfxr
Created December 15, 2015 14:26
Show Gist options
  • Save simonfxr/df48613f9dafad4cc8a1 to your computer and use it in GitHub Desktop.
Save simonfxr/df48613f9dafad4cc8a1 to your computer and use it in GitHub Desktop.
Compute number of ways to combine coins giving a certain value
-- | compute the number of ways to get n cents using coins with values
-- 1ct, 2ct, 5ct, 10ct, 20ct, 50ct, 100ct, 200ct.
cnt :: Integer -> Integer
cnt n = sum [ bink7k k * coeff _PQ (fromIntegral $ n - 200 * k)
| k <- [max 0 (ceil_div (n - dPQ) 200) ..n `div` 200] ]
where
dPQ = fromIntegral $ deg _PQ
fac7 = product [1..7]
bink7k k = product [k+1..k+7] `div` fac7
_P = p_1 * p_2 * p_3 where
p_1 = mkPoly $ replicate 10 1
p_2 = mkPoly $ [1, 0, 1, 0, 1, 0, 1, 0, 1]
p_3 = mkPoly $ [1, 0, 0, 0, 0, 1]
_Q = q1^5 * q2^7 * q3^6 * q4^5 * q5^7 where
q1 = mkPoly [1, 1]
q2 = mkPoly [1, 0, 1]
q3 = mkPoly [1, -1, 1, -1, 1]
q4 = mkPoly [1, 1, 1, 1, 1]
q5 = mkPoly [1, 0, -1, 0, 1, 0, -1, 0, 1]
_PQ = _P * applyMonom _Q 10
-- represents Polynomial p(x) = a0 + a1 x + a2 x^2 + ... + an x^n
newtype Poly a = Poly { unPoly :: [a] }
deriving (Eq, Ord, Show)
mkPoly :: (Eq a, Num a) => [a] -> Poly a
mkPoly = Poly . reverse . dropWhile (== 0) . reverse where
scalarPoly :: (Eq a, Num a) => a -> Poly a
scalarPoly 0 = Poly []
scalarPoly x = Poly [x]
instance (Eq a, Num a) => Num (Poly a) where
Poly as + Poly bs = mkPoly (zipWith (+) (as ++ repeat 0) bs)
Poly as - Poly bs = mkPoly (zipWith (-) (as ++ repeat 0) bs)
negate (Poly as) = Poly (map negate as)
Poly as * Poly bs = mkPoly [ coeff k | k <- [0..p + q - 1] ]
where
(p, q) = (length as, length bs)
coeff n = sum [ (as !! k) * (bs !! (n - k)) |
k <- [n - min n (q - 1) .. min n (p - 1)] ]
fromInteger = scalarPoly . fromInteger
abs = id
signum = const 1
-- | monom n represents x^n
monom :: (Num a) => Int -> Poly a
monom n = Poly $ replicate n 0 ++ [1]
constantPart :: (Num a) => Poly a -> a
constantPart (Poly []) = 0
constantPart (Poly (a:_)) = a
-- | compute p(x^n)
applyMonom :: (Num a, Eq a) => Poly a -> Int -> Poly a
applyMonom p 0 = scalarPoly (constantPart p)
applyMonom (Poly as) n = Poly . drop (n - 1) . concatMap f $ as where
f x = replicate (n - 1) 0 ++ [x]
indexDef :: a -> [a] -> Int -> a
indexDef def = go where
go [] _ = def
go (x:_) 0 = x
go (_:xs) n = go xs (n - 1)
coeff :: (Num a) => Poly a -> Int -> a
coeff (Poly as) n
| n < 0 = 0
| otherwise = indexDef 0 as n
deg :: Poly a -> Int
deg = max 0 . subtract 1 . length . unPoly where
ceil_div :: Integral a => a -> a -> a
ceil_div p q = (p + q - 1) `div` q
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment