Navigation Menu

Skip to content

Instantly share code, notes, and snippets.

@nobsun
Created July 8, 2020 00:06
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 nobsun/a88d263dd15e1961db0d55235a277a61 to your computer and use it in GitHub Desktop.
Save nobsun/a88d263dd15e1961db0d55235a277a61 to your computer and use it in GitHub Desktop.
module Multiplication4 where
import Data.List
import Data.Ord
multi :: Int -> Int -> [Int] -> Int
multi n k as = case sg of
1 -> product' xs
0 -> 0
_ -> maxprod n k [ss,xs,ys,nxs,pxs,nys,pys]
where
ss = sortBy (flip (comparing abs)) as
(xs,ys) = splitAt' k ss
(nxs,pxs) = partition (0 >) xs
(nys,pys) = partition (0 >) ys
sg = foldl' ((signum .) . (*)) (1 :: Int) xs
maxprod :: Int -> Int -> [[Int]] -> Int
maxprod n k [ss,xs,ys,nxs,pxs,nys,pys]
= case pxs' of
{ Nothing -> case pys' of
{ Nothing -> product' $ drop (n-k) ss
; Just (0, _) -> 0
; Just (py,_) -> py >< product' rnxs
}
; Just (px, rpxs) -> case nys' of
{ Nothing -> case pys' of
{ Nothing -> product' xs
; Just (0, _) -> 0
; Just (py,_) -> py >< product' rnxs
}
; Just (ny, rnys) -> case pys' of
{ Nothing -> ny >< product' rpxs
; Just (0 , _) -> ny >< product' rpxs
; Just (py, _) -> if px * py <= nx * ny
then py >< product' rnxs >< product' pxs
else ny >< product' rpxs >< product' nxs
}
}
}
where
Just (nx, rnxs) = uncons nxs
pxs' = uncons pxs
nys' = uncons nys
pys' = uncons pys
splitAt' :: Int -> [a] -> ([a], [a])
splitAt' n = iter n []
where
iter 0 xs ys = (xs, ys)
iter _ xs [] = (xs, [])
iter n xs (y:ys) = iter (pred n) (y:xs) ys
base :: Int
base = 10^9 + 7
(><) :: Int -> Int -> Int
x >< y = (x * y) `mod` base
product' :: [Int] -> Int
product' = foldl' (><) 1
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment