Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
47 changes: 17 additions & 30 deletions src/Data/Array.purs
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ module Data.Array
, delete
, deleteBy

, (\\)
, (\\), difference
, intersect
, intersectBy

Expand All @@ -101,21 +101,17 @@ module Data.Array
, foldM
) where

import Prelude
import Prelude (class Monad, class Applicative, class Eq, class Ord, Unit, Ordering(LT, EQ, GT), (>>=), return, eq, const, otherwise, ($), flip, (++), (==), not, (<<<), negate, compare, id, bind, pure, one, (-), zero, (+), (<*>), (<$>), (<))

import Control.Alt (Alt, (<|>))
import Control.Alternative (Alternative)
import Control.Lazy (Lazy, defer)
import Control.MonadPlus (MonadPlus)
import Control.Plus (Plus)
import Control.Alt ((<|>))
import Control.Alternative (class Alternative)
import Control.Lazy (class Lazy, defer)

import Data.Foldable (foldl)
import Data.Functor.Invariant (Invariant)
import Data.Maybe (Maybe(..), maybe, isJust)
import Data.Monoid (Monoid)
import Data.Traversable (sequence)
import Data.Tuple (Tuple(..))
import qualified Data.Maybe.Unsafe as U
import Data.Maybe.Unsafe as U

-- | Create an array of one element
singleton :: forall a. a -> Array a
Expand All @@ -124,11 +120,8 @@ singleton a = [a]
-- | Create an array containing a range of integers, including both endpoints.
foreign import range :: Int -> Int -> Array Int

infix 8 ..

-- | An infix synonym for `range`.
(..) :: Int -> Int -> Array Int
(..) = range
infix 8 range as ..

-- | Create an array with repeated instances of a value.
foreign import replicate :: forall a. Int -> a -> Array a
Expand Down Expand Up @@ -177,13 +170,10 @@ foreign import length :: forall a. Array a -> Int
-- | Note, the running time of this function is `O(n)`.
foreign import cons :: forall a. a -> Array a -> Array a

infixr 6 :

-- | An infix alias for `cons`.
-- |
-- | Note, the running time of this function is `O(n)`.
(:) :: forall a. a -> Array a -> Array a
(:) = cons
infixr 6 cons as :

-- | Append an element to the end of an array, creating a new array.
foreign import snoc :: forall a. Array a -> a -> Array a
Expand All @@ -196,7 +186,7 @@ insert = insertBy compare
-- | determine the ordering of elements.
insertBy :: forall a. (a -> a -> Ordering) -> a -> Array a -> Array a
insertBy cmp x ys =
let i = maybe 0 (+ 1) (findLastIndex (\y -> cmp x y == GT) ys)
let i = maybe 0 (_ + 1) (findLastIndex (\y -> cmp x y == GT) ys)
in U.fromJust (insertAt i x ys)

--------------------------------------------------------------------------------
Expand Down Expand Up @@ -265,19 +255,16 @@ foreign import indexImpl :: forall a. (forall r. r -> Maybe r)
-> Int
-> Maybe a

infixl 8 !!

-- | An infix version of `index`.
(!!) :: forall a. Array a -> Int -> Maybe a
(!!) = index
infixl 8 index as !!

-- | Find the index of the first element equal to the specified element.
elemIndex :: forall a. (Eq a) => a -> Array a -> Maybe Int
elemIndex x = findIndex (== x)
elemIndex x = findIndex (_ == x)

-- | Find the index of the last element equal to the specified element.
elemLastIndex :: forall a. (Eq a) => a -> Array a -> Maybe Int
elemLastIndex x = findLastIndex (== x)
elemLastIndex x = findLastIndex (_ == x)

-- | Find the first index for which a predicate holds.
findIndex :: forall a. (a -> Boolean) -> Array a -> Maybe Int
Expand Down Expand Up @@ -524,13 +511,13 @@ deleteBy :: forall a. (a -> a -> Boolean) -> a -> Array a -> Array a
deleteBy _ _ [] = []
deleteBy eq x ys = maybe ys (\i -> U.fromJust $ deleteAt i ys) (findIndex (eq x) ys)

infix 5 \\

-- | Delete the first occurrence of each element in the second array from the
-- | first array, creating a new array.
(\\) :: forall a. (Eq a) => Array a -> Array a -> Array a
(\\) xs ys | null xs = []
| otherwise = uncons' (const xs) (\y ys -> delete y xs \\ ys) ys
difference :: forall a. (Eq a) => Array a -> Array a -> Array a
difference xs ys | null xs = []
| otherwise = uncons' (const xs) (\z zs -> delete z xs \\ zs) ys

infix 5 difference as \\

-- | Calculate the intersection of two arrays, creating a new array.
intersect :: forall a. (Eq a) => Array a -> Array a -> Array a
Expand Down
2 changes: 1 addition & 1 deletion src/Data/Array/Unsafe.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

module Data.Array.Unsafe where

import Prelude
import Prelude ((-))

import Data.Array (length, slice)

Expand Down
46 changes: 27 additions & 19 deletions test/Test/Data/Array.purs
Original file line number Diff line number Diff line change
@@ -1,13 +1,21 @@
module Test.Data.Array (testArray) where

import Prelude
import Control.Monad.Eff.Console (log)
import Data.Array
import Prelude ((*), zero, (/=), mod, (==), ($), (+), bind, show, (<), (&&), compare, flip, const, (<<<), map, negate, unit, Unit)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (log, CONSOLE)
import Data.Array (range, foldM, unzip, zip, zipWithA, zipWith, intersectBy, intersect, (\\), deleteBy, delete, unionBy, union, nubBy, nub, groupBy, group', group, span, dropWhile, drop, takeWhile, take, sortBy, sort, catMaybes, mapMaybe, filterM, filter, concat, concatMap, reverse, alterAt, modifyAt, updateAt, deleteAt, insertAt, findLastIndex, findIndex, elemLastIndex, elemIndex, (!!), uncons, init, tail, last, head, insertBy, insert, snoc, (:), length, null, replicate, replicateM, singleton)
import Data.Maybe (Maybe(..), isNothing)
import Data.Maybe.Unsafe (fromJust)
import Data.Tuple (Tuple(..))
import Test.Assert (assert)

import Test.Assert (assert, ASSERT)

testArray :: forall t.
Eff
( console :: CONSOLE
, assert :: ASSERT
| t
)
Unit
testArray = do

log "singleton should construct an array with a single value"
Expand Down Expand Up @@ -121,12 +129,12 @@ testArray = do
assert $ (elemLastIndex 4 [1, 2, 1]) == Nothing

log "findIndex should return the index of an item that a predicate returns true for in an array"
assert $ (findIndex (/= 1) [1, 2, 1]) == Just 1
assert $ (findIndex (== 3) [1, 2, 1]) == Nothing
assert $ (findIndex (_ /= 1) [1, 2, 1]) == Just 1
assert $ (findIndex (_ == 3) [1, 2, 1]) == Nothing

log "findLastIndex should return the last index of an item in an array"
assert $ (findLastIndex (/= 1) [2, 1, 2]) == Just 2
assert $ (findLastIndex (== 3) [2, 1, 2]) == Nothing
assert $ (findLastIndex (_ /= 1) [2, 1, 2]) == Just 2
assert $ (findLastIndex (_ == 3) [2, 1, 2]) == Nothing

log "insertAt should add an item at the specified index"
assert $ (insertAt 0 1 [2, 3]) == Just [1, 2, 3]
Expand All @@ -151,11 +159,11 @@ testArray = do
assert $ (updateAt 1 9 nil) == Nothing

log "modifyAt should update an item at the specified index"
assert $ (modifyAt 0 (+ 1) [1, 2, 3]) == Just [2, 2, 3]
assert $ (modifyAt 1 (+ 1) [1, 2, 3]) == Just [1, 3, 3]
assert $ (modifyAt 0 (_ + 1) [1, 2, 3]) == Just [2, 2, 3]
assert $ (modifyAt 1 (_ + 1) [1, 2, 3]) == Just [1, 3, 3]

log "modifyAt should return Nothing if the index is out of range"
assert $ (modifyAt 1 (+ 1) nil) == Nothing
assert $ (modifyAt 1 (_ + 1) nil) == Nothing

log "alterAt should update an item at the specified index when the function returns Just"
assert $ (alterAt 0 (Just <<< (+ 1)) [1, 2, 3]) == Just [2, 2, 3]
Expand Down Expand Up @@ -205,22 +213,22 @@ testArray = do
assert $ (take 1 nil) == nil

log "takeWhile should keep all values that match a predicate from the front of an array"
assert $ (takeWhile (/= 2) [1, 2, 3]) == [1]
assert $ (takeWhile (/= 3) [1, 2, 3]) == [1, 2]
assert $ (takeWhile (/= 1) nil) == nil
assert $ (takeWhile (_ /= 2) [1, 2, 3]) == [1]
assert $ (takeWhile (_ /= 3) [1, 2, 3]) == [1, 2]
assert $ (takeWhile (_ /= 1) nil) == nil

log "drop should remove the specified number of items from the front of an array"
assert $ (drop 1 [1, 2, 3]) == [2, 3]
assert $ (drop 2 [1, 2, 3]) == [3]
assert $ (drop 1 nil) == nil

log "dropWhile should remove all values that match a predicate from the front of an array"
assert $ (dropWhile (/= 1) [1, 2, 3]) == [1, 2, 3]
assert $ (dropWhile (/= 2) [1, 2, 3]) == [2, 3]
assert $ (dropWhile (/= 1) nil) == nil
assert $ (dropWhile (_ /= 1) [1, 2, 3]) == [1, 2, 3]
assert $ (dropWhile (_ /= 2) [1, 2, 3]) == [2, 3]
assert $ (dropWhile (_ /= 1) nil) == nil

log "span should split an array in two based on a predicate"
let spanResult = span (< 4) [1, 2, 3, 4, 5, 6, 7]
let spanResult = span (_ < 4) [1, 2, 3, 4, 5, 6, 7]
assert $ spanResult.init == [1, 2, 3]
assert $ spanResult.rest == [4, 5, 6, 7]

Expand Down
20 changes: 13 additions & 7 deletions test/Test/Data/Array/ST.purs
Original file line number Diff line number Diff line change
@@ -1,15 +1,21 @@
module Test.Data.Array.ST (testArrayST) where

import Prelude
import Control.Monad.Eff.Console (log, print)
import Control.Monad.Eff (runPure)
import Prelude (bind, (+), (*), (==), ($), return, negate, not, Unit)
import Control.Monad.Eff.Console (log, CONSOLE)
import Control.Monad.Eff (runPure, Eff)
import Control.Monad.ST (runST)
import Data.Array ()
import Data.Array.ST
import Data.Array.ST (toAssocArray, thaw, spliceSTArray, runSTArray, pokeSTArray, emptySTArray, peekSTArray, pushAllSTArray, pushSTArray, freeze)
import Data.Foldable (all)
import Data.Maybe (Maybe(..), isNothing)
import Test.Assert (assert)

import Test.Assert (assert, ASSERT)

testArrayST :: forall t.
Eff
( console :: CONSOLE
, assert :: ASSERT
| t
)
Unit
testArrayST = do

log "emptySTArray should produce an empty array"
Expand Down
16 changes: 12 additions & 4 deletions test/Test/Data/Array/Unsafe.purs
Original file line number Diff line number Diff line change
@@ -1,10 +1,18 @@
module Test.Data.Array.Unsafe (testArrayUnsafe) where

import Prelude
import Control.Monad.Eff.Console (log)
import Data.Array.Unsafe
import Test.Assert (assert)
import Prelude ((==), ($), bind, Unit)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (log, CONSOLE)
import Data.Array.Unsafe (init, last, tail, head)
import Test.Assert (assert, ASSERT)

testArrayUnsafe :: forall t.
Eff
( console :: CONSOLE
, assert :: ASSERT
| t
)
Unit
testArrayUnsafe = do

log "head should return the first item in an array"
Expand Down
18 changes: 14 additions & 4 deletions test/Test/Main.purs
Original file line number Diff line number Diff line change
@@ -1,10 +1,20 @@
module Test.Main where

import Prelude
import Test.Data.Array
import Test.Data.Array.ST
import Test.Data.Array.Unsafe
import Prelude (bind, Unit)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE)
import Test.Assert (ASSERT)
import Test.Data.Array (testArray)
import Test.Data.Array.ST (testArrayST)
import Test.Data.Array.Unsafe (testArrayUnsafe)

main :: forall t.
Eff
( console :: CONSOLE
, assert :: ASSERT
| t
)
Unit
main = do
testArray
testArrayST
Expand Down