module MyDet where type Matrix = [[Rational]] first :: [[a]] -> [a] first [] = [] first (xs:_) = xs pad a = [x ++ x | x <- a] sig n = case odd n of True -> -1 False -> 1 ind :: Int -> Int -> Matrix -> Rational ind i k mat = (mat !! (i-1)) !! (k-1) slice :: (Int,Int) -> (Int,Int) -> Matrix -> Matrix slice (i,j) (k,l) mat = let rowSliceFront = drop (i-1) mat rowSlice = take (k-i+1) rowSliceFront columnSliceFront = map (drop (j-1)) rowSlice in map (take (l-j+1)) columnSliceFront determinant :: Matrix -> Rational determinant mat = det (pad mat) (length mat) det :: Matrix -> Int -> Rational det mat 1 = ind 1 1 mat det mat size = let coeffs = zipWith (*) (cycle [1,sig newsize]) $ first mat newsize = size - 1 leastToMax = newsize - 1 slices = [slice (2,i) (size,i+leastToMax) mat | i <- [2 .. (size+1)]] in sum (zipWith (*) coeffs (map (\l -> det l newsize) (map pad slices)))