Skip to content

Instantly share code, notes, and snippets.

@fedelebron
Created August 19, 2013 01:21
Show Gist options
  • Star 2 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save fedelebron/6265040 to your computer and use it in GitHub Desktop.
Save fedelebron/6265040 to your computer and use it in GitHub Desktop.
A function to compute the permanent of a matrix in Haskell. The algorithm is not as efficient as it could be - it is using the Ryser formula for an O(n^2 * 2^n) runtime, where a O(n * 2^n) algorithm exists, which uses the same idea but adds Gray codes to compute the subsets in a better order, allowing a reuse of computations.
{-# LANGUAGE FlexibleContexts #-}
import Data.Array.IArray (IArray, bounds)
import Data.Array.Unboxed (UArray)
import Data.Array.Base (unsafeAt)
import Data.Bits (popCount, testBit)
permanent :: (Integral a, IArray UArray a) => UArray (Int, Int) a -> a
permanent arr | n == m = (if even n then negate else id) (sum entries)
where
((0, 0), (n, m)) = bounds arr
n' = n + 1
entries = do
i <- [1 .. 2^n' - 1] :: [Int]
let columnSums = map column [0 .. n]
bits = map (* n') $ filter (testBit i) [0 .. n]
column j = sum $ map (unsafeAt arr . (+ j)) bits
return . (if odd (popCount i) then negate else id) $ product columnSums
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment