<div dir="ltr"><div><div><div><font face="monospace, monospace">-- Not beautifully idiomatic, but not too bad, and O(n):</font></div></div><div><font face="monospace, monospace"><br></font></div><div><span style="font-family:monospace,monospace">data SolutionState = SSInitial | SS Int Int Int</span><br></div><div><div><font face="monospace, monospace"><br></font></div><div><span style="font-family:monospace,monospace">solve :: [Int] -> SolutionState</span><br></div><div><font face="monospace, monospace">solve = foldr go SSInitial where</font></div><div><span style="font-family:monospace,monospace">  go x (SS dense best sparse) =</span><br></div><div><font face="monospace, monospace">    let dense'  = max x (dense + x)</font></div><div><font face="monospace, monospace">        best'   = max best dense'</font></div><div><font face="monospace, monospace">        sparse' = max (sparse + x) (max sparse x)</font></div><div><font face="monospace, monospace">    in  SS dense' best' sparse'</font></div></div><div><div><font face="monospace, monospace">  go x SSInitial = SS x x x</font></div></div></div><div><font face="monospace, monospace"><br></font></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Sat, Jul 16, 2016 at 3:40 PM, Dominik Bollmann <span dir="ltr"><<a href="mailto:dominikbollmann@gmail.com" target="_blank">dominikbollmann@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Hi all,<br>
<br>
I've recently been trying to implement the "maximum subarray problem"<br>
from [1] in Haskell. My first, naive solution looked like this:<br>
<br>
maxSubArray :: [Int] -> [Int]<br>
maxSubArray []         = []<br>
maxSubArray [x]        = [x]<br>
maxSubArray xs@(_:_:_) = maxArr (maxArr maxHd maxTl) (maxCrossingArray hd tl)<br>
  where<br>
    (hd,tl) = splitAt (length xs `div` 2) xs<br>
    maxHd   = maxSubArray hd<br>
    maxTl   = maxSubArray tl<br>
<br>
maxCrossingArray :: [Int] -> [Int] -> [Int]<br>
maxCrossingArray hd tl<br>
  | null hd || null tl = error "maxArrayBetween: hd/tl empty!"<br>
maxCrossingArray hd tl = maxHd ++ maxTl<br>
  where<br>
    maxHd = reverse . foldr1 maxArr . tail $ inits (reverse hd)<br>
      -- we need to go from the center leftwards, which is why we<br>
      -- reverse the list `hd'.<br>
    maxTl = foldr1 maxArr . tail $ inits tl<br>
<br>
maxArr :: [Int] -> [Int] -> [Int]<br>
maxArr xs ys<br>
  | sum xs > sum ys = xs<br>
  | otherwise       = ys<br>
<br>
While I originally thought that this should run in O(n*log n), a closer<br>
examination revealed that the (++) as well as maxHd and maxTl<br>
computations inside function `maxCrossingArray` are O(n^2), which makes<br>
solving one of the provided test cases in [1] infeasible.<br>
<br>
Hence, I rewrote the above code using Data.Array into the following:<br>
<br>
data ArraySum = ArraySum {<br>
   from :: Int<br>
 , to   :: Int<br>
 , value :: Int<br>
 } deriving (Eq, Show)<br>
<br>
instance Ord ArraySum where<br>
  ArraySum _ _ v1 <= ArraySum _ _ v2 = v1 <= v2<br>
<br>
maxSubList :: [Int] -> [Int]<br>
maxSubList xs = take (to-from+1) . drop (from-1) $ xs<br>
  where<br>
    arr = array (1, length xs) [(i,v) | (i,v) <- zip [1..] xs]<br>
    ArraySum from to val = findMaxArr (1, length xs) arr<br>
<br>
findMaxArr :: (Int, Int) -> Array Int Int -> ArraySum<br>
findMaxArr (start, end) arr<br>
  | start > end  = error "findMaxArr: start > end"<br>
  | start == end = ArraySum start end (arr ! start)<br>
  | otherwise    = max (max hd tl) (ArraySum leftIdx rightIdx (leftVal+rightVal))<br>
  where<br>
    mid                  = (start + end) `div` 2<br>
    hd                   = findMaxArr (start, mid) arr<br>
    tl                   = findMaxArr (mid+1, end) arr<br>
    (leftIdx, leftVal)   = snd $ findMax mid     [mid-1,mid-2..start]<br>
    (rightIdx, rightVal) = snd $ findMax (mid+1) [mid+2,mid+3..end]<br>
    findMax pos          = foldl' go ((pos, arr ! pos), (pos, arr ! pos))<br>
    go ((currIdx, currSum), (maxIdx, maxSum)) idx<br>
      | newSum >= maxSum = ((idx, newSum), (idx, newSum))<br>
      | otherwise        = ((idx, newSum), (maxIdx, maxSum))<br>
      where newSum = currSum + (arr ! idx)<br>
<br>
I believe this runs in O(n*log n) now and is fast enough for the purpose<br>
of solving the Hackerrank challenge [1].<br>
<br>
However, I feel this second solution is not very idiomatic Haskell code<br>
and I would prefer the clarity of the first solution over the second, if<br>
somehow I could make it more efficient.<br>
<br>
Therefore my question: What would be an efficient, yet idiomatic<br>
solution to solving the "maximum subarray problem" in Haskell? (Note:<br>
I'm aware that this problem can be solved in O(n), but I'm also happy with<br>
idiomatic Haskell solutions running in O(n*log n))<br>
<br>
Thanks, Dominik.<br>
<br>
[1] <a href="https://www.hackerrank.com/challenges/maxsubarray" rel="noreferrer" target="_blank">https://www.hackerrank.com/challenges/maxsubarray</a><br>
_______________________________________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners</a><br>
</blockquote></div><br></div>