@@ -9,9 +9,6 @@ module Data.Array
9
9
( singleton
10
10
, (..), range
11
11
, replicate
12
- , replicateM
13
- , some
14
- , many
15
12
16
13
, null
17
14
, length
@@ -39,7 +36,6 @@ module Data.Array
39
36
, concat
40
37
, concatMap
41
38
, filter
42
- , filterM
43
39
, mapMaybe
44
40
, catMaybes
45
41
@@ -69,10 +65,10 @@ module Data.Array
69
65
, zipWithA
70
66
, zip
71
67
, unzip
72
-
73
- , foldM
74
68
) where
75
69
70
+ import Prelude
71
+
76
72
import Control.Alt (Alt , (<|>))
77
73
import Control.Alternative (Alternative )
78
74
import Control.Lazy (Lazy , defer )
@@ -105,28 +101,6 @@ infix 8 ..
105
101
-- | Create an array with repeated instances of a value.
106
102
foreign import replicate :: forall a . Int -> a -> Array a
107
103
108
- -- | Perform a monadic action `n` times collecting all of the results.
109
- replicateM :: forall m a . (Monad m ) => Int -> m a -> m (Array a )
110
- replicateM n m | n < 1 = return []
111
- | otherwise = do a <- m
112
- as <- replicateM (n - 1 ) m
113
- return (a : as)
114
-
115
- -- | Attempt a computation multiple times, requiring at least one success.
116
- -- |
117
- -- | The `Lazy` constraint is used to generate the result lazily, to ensure
118
- -- | termination.
119
- some :: forall f a . (Alternative f , Lazy (f (Array a ))) => f a -> f (Array a )
120
- some v = (:) <$> v <*> defer (\_ -> many v)
121
-
122
- -- | Attempt a computation multiple times, returning as many successful results
123
- -- | as possible (possibly zero).
124
- -- |
125
- -- | The `Lazy` constraint is used to generate the result lazily, to ensure
126
- -- | termination.
127
- many :: forall f a . (Alternative f , Lazy (f (Array a ))) => f a -> f (Array a )
128
- many v = some v <|> pure []
129
-
130
104
-- ------------------------------------------------------------------------------
131
105
-- Array size ------------------------------------------------------------------
132
106
-- ------------------------------------------------------------------------------
@@ -281,20 +255,6 @@ concatMap = flip bind
281
255
-- | creating a new array.
282
256
foreign import filter :: forall a . (a -> Boolean ) -> Array a -> Array a
283
257
284
- -- | Filter where the predicate returns a monadic `Boolean`.
285
- -- |
286
- -- | ```purescript
287
- -- | powerSet :: forall a. [a] -> [[a]]
288
- -- | powerSet = filterM (const [true, false])
289
- -- | ```
290
- filterM :: forall a m . (Monad m ) => (a -> m Boolean ) -> Array a -> m (Array a )
291
- filterM p = uncons' (\_ -> pure [] ) \x xs -> do
292
- b <- p x
293
- xs' <- filterM p xs
294
- return if b
295
- then x : xs'
296
- else xs'
297
-
298
258
-- | Apply a function to each element in an array, keeping only the results
299
259
-- | which contain a value, creating a new array.
300
260
mapMaybe :: forall a b . (a -> Maybe b ) -> Array a -> Array b
@@ -470,18 +430,6 @@ unzip :: forall a b. Array (Tuple a b) -> Tuple (Array a) (Array b)
470
430
unzip = uncons' (\_ -> Tuple [] [] ) \(Tuple a b) ts -> case unzip ts of
471
431
Tuple as bs -> Tuple (a : as) (b : bs)
472
432
473
- -- ------------------------------------------------------------------------------
474
- -- Folding ---------------------------------------------------------------------
475
- -- ------------------------------------------------------------------------------
476
-
477
- -- | Perform a fold using a monadic step function.
478
- foldM :: forall m a b . (Monad m ) => (a -> b -> m a ) -> a -> Array b -> m a
479
- foldM f a = uncons' (\_ -> return a) (\b bs -> f a b >>= \a' -> foldM f a' bs)
480
-
481
- foreign import foldrArray :: forall a b . (a -> b -> b ) -> b -> Array a -> b
482
-
483
- foreign import foldlArray :: forall a b . (b -> a -> b ) -> b -> Array a -> b
484
-
485
433
-- ------------------------------------------------------------------------------
486
434
-- Non-Prelude instances -------------------------------------------------------
487
435
-- ------------------------------------------------------------------------------
@@ -496,14 +444,5 @@ instance alternativeArray :: Alternative Array
496
444
497
445
instance monadPlusArray :: MonadPlus Array
498
446
499
- instance foldableArray :: Foldable Array where
500
- foldr f z xs = foldrArray f z xs
501
- foldl f z xs = foldlArray f z xs
502
- foldMap f xs = foldr (\x acc -> f x <> acc) mempty xs
503
-
504
- instance traversableArray :: Traversable Array where
505
- traverse f = uncons' (\_ -> pure [] ) (\x xs -> (:) <$> (f x) <*> traverse f xs)
506
- sequence = uncons' (\_ -> pure [] ) (\x xs -> (:) <$> x <*> sequence xs)
507
-
508
447
instance invariantArray :: Invariant Array where
509
448
imap = imapF
0 commit comments