Skip to content

Instantly share code, notes, and snippets.

@corajr
Last active July 4, 2016 20:19
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save corajr/a7c9fa7325b27d3d8c581625271d582f to your computer and use it in GitHub Desktop.
Save corajr/a7c9fa7325b27d3d8c581625271d582f to your computer and use it in GitHub Desktop.
module Data.Vector.FindMax where
import Data.Vector (Vector, (!), (!?))
import qualified Data.Vector as V
import Data.Maybe (fromMaybe)
findMax :: Vector Int -> Maybe Int
findMax v
| V.null v = Nothing
| pivotValue > leftValue && pivotValue > rightValue = Just pivotValue
| pivotValue > leftValue = findMax $ V.drop pivot v
| otherwise = findMax $ V.take pivot v
where pivotValue = v ! pivot
leftValue = fromMaybe minBound (v !? (pivot - 1))
rightValue = fromMaybe minBound (v !? (pivot + 1))
pivot = V.length v `div` 2
module Data.Vector.FindMaxSpec (main, spec) where
import Test.Hspec
import Test.QuickCheck
import qualified Data.Vector as V
import qualified Data.Set as Set
import Data.Vector.FindMax
main :: IO ()
main = hspec spec
spec :: Spec
spec =
describe "findMax" $ do
it "returns nothing for an empty vector" $
findMax V.empty `shouldBe` Nothing
it "returns the single-element of a one-element vector" $ property $
\i -> findMax (V.singleton i) === Just i
it "returns the middle element from random unique vectors" $ property $
\set1 set2 ->
let combined = Set.union set1 set2
el = 1 + if not (Set.null combined) then Set.findMax combined else 0
v = V.concat [V.fromList (Set.toAscList set1), V.singleton el, V.fromList (Set.toDescList set2)]
in findMax v === Just el
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment