Skip to content

Commit feaeff7

Browse files
committed
Merge branch 'compiler/0.12' into with-index-result
2 parents e836652 + d7a3fa2 commit feaeff7

File tree

12 files changed

+199
-79
lines changed

12 files changed

+199
-79
lines changed

bower.json

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,14 @@
1717
"package.json"
1818
],
1919
"dependencies": {
20-
"purescript-bifunctors": "^3.0.0",
21-
"purescript-maybe": "^3.0.0"
20+
"purescript-bifunctors": "#compiler/0.12",
21+
"purescript-maybe": "#compiler/0.12",
22+
"purescript-orders": "#compiler/0.12"
2223
},
2324
"devDependencies": {
24-
"purescript-assert": "^3.0.0",
25-
"purescript-console": "^3.0.0",
26-
"purescript-integers": "^3.0.0",
27-
"purescript-math": "^2.0.0"
25+
"purescript-assert": "#compiler/0.12",
26+
"purescript-console": "#compiler/0.12",
27+
"purescript-integers": "#compiler/0.12",
28+
"purescript-math": "#compiler/0.12"
2829
}
2930
}

package.json

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,8 @@
77
},
88
"devDependencies": {
99
"eslint": "^3.17.1",
10-
"pulp": "^10.0.4",
11-
"purescript-psa": "^0.5.0-rc.1",
10+
"pulp": "^11.0.0",
11+
"purescript-psa": "^0.5.1",
1212
"rimraf": "^2.6.1"
1313
}
1414
}

src/Data/Bifoldable.purs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,6 @@ module Data.Bifoldable where
33
import Prelude
44

55
import Control.Apply (applySecond)
6-
7-
import Data.Monoid (class Monoid, mempty)
86
import Data.Monoid.Conj (Conj(..))
97
import Data.Monoid.Disj (Disj(..))
108
import Data.Monoid.Dual (Dual(..))
@@ -127,7 +125,7 @@ bifoldMapDefaultL f g = bifoldl (\m a -> m <> f a) (\m b -> m <> g b) mempty
127125

128126
-- | Fold a data structure, accumulating values in a monoidal type.
129127
bifold :: forall t m. Bifoldable t => Monoid m => t m m -> m
130-
bifold = bifoldMap id id
128+
bifold = bifoldMap identity identity
131129

132130
-- | Traverse a data structure, accumulating effects using an `Applicative` functor,
133131
-- | ignoring the final result.
@@ -160,7 +158,7 @@ bisequence_
160158
=> Applicative f
161159
=> t (f a) (f b)
162160
-> f Unit
163-
bisequence_ = bitraverse_ id id
161+
bisequence_ = bitraverse_ identity identity
164162

165163
-- | Test whether a predicate holds at any position in a data structure.
166164
biany

src/Data/Bitraversable.purs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ bisequenceDefault
9292
=> Applicative f
9393
=> t (f a) (f b)
9494
-> f (t a b)
95-
bisequenceDefault = bitraverse id id
95+
bisequenceDefault = bitraverse identity identity
9696

9797
-- | Traverse a data structure, accumulating effects and results using an `Applicative` functor.
9898
bifor

src/Data/Foldable.purs

Lines changed: 38 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module Data.Foldable
77
, for_
88
, sequence_
99
, oneOf
10+
, oneOfMap
1011
, intercalate
1112
, surroundMap
1213
, surround
@@ -18,6 +19,8 @@ module Data.Foldable
1819
, product
1920
, elem
2021
, notElem
22+
, indexl
23+
, indexr
2124
, find
2225
, findMap
2326
, maximum
@@ -31,11 +34,9 @@ module Data.Foldable
3134
import Prelude
3235

3336
import Control.Plus (class Plus, alt, empty)
34-
3537
import Data.Maybe (Maybe(..))
3638
import Data.Maybe.First (First(..))
3739
import Data.Maybe.Last (Last(..))
38-
import Data.Monoid (class Monoid, mempty)
3940
import Data.Monoid.Additive (Additive(..))
4041
import Data.Monoid.Conj (Conj(..))
4142
import Data.Monoid.Disj (Disj(..))
@@ -170,11 +171,11 @@ instance foldableMultiplicative :: Foldable Multiplicative where
170171

171172
-- | Fold a data structure, accumulating values in some `Monoid`.
172173
fold :: forall f m. Foldable f => Monoid m => f m -> m
173-
fold = foldMap id
174+
fold = foldMap identity
174175

175-
-- | Similar to 'foldl', but the result is encapsulated in a monad.
176+
-- | Similar to 'foldl', but the result is encapsulated in a monad.
176177
-- |
177-
-- | Note: this function is not generally stack-safe, e.g., for monads which
178+
-- | Note: this function is not generally stack-safe, e.g., for monads which
178179
-- | build up thunks a la `Eff`.
179180
foldM :: forall f m a b. Foldable f => Monad m => (a -> b -> m a) -> a -> f b -> m a
180181
foldM f a0 = foldl (\ma b -> ma >>= flip f b) (pure a0)
@@ -227,12 +228,16 @@ for_ = flip traverse_
227228
-- | sequence_ [ trace "Hello, ", trace " world!" ]
228229
-- | ```
229230
sequence_ :: forall a f m. Applicative m => Foldable f => f (m a) -> m Unit
230-
sequence_ = traverse_ id
231+
sequence_ = traverse_ identity
231232

232233
-- | Combines a collection of elements using the `Alt` operation.
233234
oneOf :: forall f g a. Foldable f => Plus g => f (g a) -> g a
234235
oneOf = foldr alt empty
235236

237+
-- | Folds a structure into some `Plus`.
238+
oneOfMap :: forall f g a b. Foldable f => Plus g => (a -> g b) -> f a -> g b
239+
oneOfMap f = foldr (alt <<< f) empty
240+
236241
-- | Fold a data structure, accumulating values in some `Monoid`,
237242
-- | combining adjacent elements using the specified separator.
238243
intercalate :: forall f m. Foldable f => Monoid m => m -> f m -> m
@@ -280,19 +285,19 @@ surroundMap d t f = unwrap (foldMap joined f) d
280285
-- | = "*1*2*3*"
281286
-- | ```
282287
surround :: forall f m. Foldable f => Semigroup m => m -> f m -> m
283-
surround d = surroundMap d id
288+
surround d = surroundMap d identity
284289

285290
-- | The conjunction of all the values in a data structure. When specialized
286291
-- | to `Boolean`, this function will test whether all of the values in a data
287292
-- | structure are `true`.
288293
and :: forall a f. Foldable f => HeytingAlgebra a => f a -> a
289-
and = all id
294+
and = all identity
290295

291296
-- | The disjunction of all the values in a data structure. When specialized
292297
-- | to `Boolean`, this function will test whether any of the values in a data
293298
-- | structure is `true`.
294299
or :: forall a f. Foldable f => HeytingAlgebra a => f a -> a
295-
or = any id
300+
or = any identity
296301

297302
-- | `all f` is the same as `and <<< map f`; map a function over the structure,
298303
-- | and then get the conjunction of the results.
@@ -320,6 +325,30 @@ elem = any <<< (==)
320325
notElem :: forall a f. Foldable f => Eq a => a -> f a -> Boolean
321326
notElem x = not <<< elem x
322327

328+
-- | Try to get nth element from the left in a data structure
329+
indexl :: forall a f. Foldable f => Int -> f a -> Maybe a
330+
indexl idx = _.elem <<< foldl go { elem: Nothing, pos: 0 }
331+
where
332+
go cursor a =
333+
case cursor.elem of
334+
Just _ -> cursor
335+
_ ->
336+
if cursor.pos == idx
337+
then { elem: Just a, pos: cursor.pos }
338+
else { pos: cursor.pos + 1, elem: cursor.elem }
339+
340+
-- | Try to get nth element from the right in a data structure
341+
indexr :: forall a f. Foldable f => Int -> f a -> Maybe a
342+
indexr idx = _.elem <<< foldr go { elem: Nothing, pos: 0 }
343+
where
344+
go a cursor =
345+
case cursor.elem of
346+
Just _ -> cursor
347+
_ ->
348+
if cursor.pos == idx
349+
then { elem: Just a, pos: cursor.pos }
350+
else { pos: cursor.pos + 1, elem: cursor.elem }
351+
323352
-- | Try to find an element in a data structure which satisfies a predicate.
324353
find :: forall a f. Foldable f => (a -> Boolean) -> f a -> Maybe a
325354
find p = foldl go Nothing

src/Data/FoldableWithIndex.purs

Lines changed: 36 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,9 @@ module Data.FoldableWithIndex
1111
, allWithIndex
1212
, anyWithIndex
1313
, findWithIndex
14+
, foldrDefault
15+
, foldlDefault
16+
, foldMapDefault
1417
) where
1518

1619
import Prelude
@@ -20,7 +23,6 @@ import Data.FunctorWithIndex (mapWithIndex)
2023
import Data.Maybe (Maybe(..))
2124
import Data.Maybe.First (First)
2225
import Data.Maybe.Last (Last)
23-
import Data.Monoid (class Monoid, mempty)
2426
import Data.Monoid.Additive (Additive)
2527
import Data.Monoid.Conj (Conj(..))
2628
import Data.Monoid.Disj (Disj(..))
@@ -29,15 +31,15 @@ import Data.Monoid.Endo (Endo(..))
2931
import Data.Monoid.Multiplicative (Multiplicative)
3032
import Data.Newtype (unwrap)
3133

32-
-- | A `Foldable` with an additional index.
34+
-- | A `Foldable` with an additional index.
3335
-- | A `FoldableWithIndex` instance must be compatible with its `Foldable`
3436
-- | instance
3537
-- | ```purescript
3638
-- | foldr f = foldrWithIndex (const f)
3739
-- | foldl f = foldlWithIndex (const f)
3840
-- | foldMap f = foldMapWithIndex (const f)
3941
-- | ```
40-
-- |
42+
-- |
4143
-- | Default implementations are provided by the following functions:
4244
-- |
4345
-- | - `foldrWithIndexDefault`
@@ -153,9 +155,9 @@ instance foldableWithIndexMultiplicative :: FoldableWithIndex Unit Multiplicativ
153155
foldMapWithIndex f = foldMap $ f unit
154156

155157

156-
-- | Similar to 'foldlWithIndex', but the result is encapsulated in a monad.
158+
-- | Similar to 'foldlWithIndex', but the result is encapsulated in a monad.
157159
-- |
158-
-- | Note: this function is not generally stack-safe, e.g., for monads which
160+
-- | Note: this function is not generally stack-safe, e.g., for monads which
159161
-- | build up thunks a la `Eff`.
160162
foldWithIndexM
161163
:: forall i f m a b
@@ -269,10 +271,32 @@ findWithIndex
269271
-> Maybe { index :: i, value :: a }
270272
findWithIndex p = foldlWithIndex go Nothing
271273
where
272-
go
273-
:: i
274-
-> Maybe { index :: i, value :: a }
275-
-> a
276-
-> Maybe { index :: i, value :: a }
277-
go i Nothing x | p i x = Just { index: i, value: x }
278-
go _ r _ = r
274+
go
275+
:: i
276+
-> Maybe { index :: i, value :: a }
277+
-> a
278+
-> Maybe { index :: i, value :: a }
279+
go i Nothing x | p i x = Just { index: i, value: x }
280+
go _ r _ = r
281+
282+
-- | A default implementation of `foldr` using `foldrWithIndex`
283+
foldrDefault
284+
:: forall i f a b
285+
. FoldableWithIndex i f
286+
=> (a -> b -> b) -> b -> f a -> b
287+
foldrDefault f = foldrWithIndex (const f)
288+
289+
-- | A default implementation of `foldl` using `foldlWithIndex`
290+
foldlDefault
291+
:: forall i f a b
292+
. FoldableWithIndex i f
293+
=> (b -> a -> b) -> b -> f a -> b
294+
foldlDefault f = foldlWithIndex (const f)
295+
296+
-- | A default implementation of `foldMap` using `foldMapWithIndex`
297+
foldMapDefault
298+
:: forall i f a m
299+
. FoldableWithIndex i f
300+
=> Monoid m
301+
=> (a -> m) -> f a -> m
302+
foldMapDefault f = foldMapWithIndex (const f)

src/Data/FunctorWithIndex.purs

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module Data.FunctorWithIndex
2-
( class FunctorWithIndex, mapWithIndex
2+
( class FunctorWithIndex, mapWithIndex, mapDefault
33
) where
44

55
import Prelude
@@ -13,11 +13,10 @@ import Data.Monoid.Disj (Disj)
1313
import Data.Monoid.Dual (Dual)
1414
import Data.Monoid.Multiplicative (Multiplicative)
1515

16-
17-
-- | A `Functor` with an additional index.
16+
-- | A `Functor` with an additional index.
1817
-- | Instances must satisfy a modified form of the `Functor` laws
1918
-- | ```purescript
20-
-- | mapWithIndex (\_ a -> a) = id
19+
-- | mapWithIndex (\_ a -> a) = identity
2120
-- | mapWithIndex f . mapWithIndex g = mapWithIndex (\i -> f i <<< g i)
2221
-- | ```
2322
-- | and be compatible with the `Functor` instance
@@ -55,3 +54,7 @@ instance functorWithIndexDisj :: FunctorWithIndex Unit Disj where
5554

5655
instance functorWithIndexMultiplicative :: FunctorWithIndex Unit Multiplicative where
5756
mapWithIndex f = map $ f unit
57+
58+
-- | A default implementation of Functor's `map` in terms of `mapWithIndex`
59+
mapDefault :: forall i f a b. FunctorWithIndex i f => (a -> b) -> f a -> f b
60+
mapDefault f = mapWithIndex (const f)

src/Data/Semigroup/Foldable.purs

Lines changed: 38 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,12 +7,18 @@ module Data.Semigroup.Foldable
77
, sequence1_
88
, foldMap1Default
99
, fold1Default
10+
, intercalate
11+
, intercalateMap
1012
) where
1113

1214
import Prelude
15+
1316
import Data.Foldable (class Foldable)
1417
import Data.Monoid.Dual (Dual(..))
1518
import Data.Monoid.Multiplicative (Multiplicative(..))
19+
import Data.Newtype (ala)
20+
import Data.Ord.Max (Max(..))
21+
import Data.Ord.Min (Min(..))
1622

1723
-- | `Foldable1` represents data structures with a minimum of one element that can be _folded_.
1824
-- |
@@ -33,7 +39,7 @@ class Foldable t <= Foldable1 t where
3339

3440
-- | A default implementation of `fold1` using `foldMap1`.
3541
fold1Default :: forall t m. Foldable1 t => Semigroup m => t m -> m
36-
fold1Default = foldMap1 id
42+
fold1Default = foldMap1 identity
3743

3844
-- | A default implementation of `foldMap1` using `fold1`.
3945
foldMap1Default :: forall t m a. Foldable1 t => Functor t => Semigroup m => (a -> m) -> t a -> m
@@ -70,4 +76,34 @@ for1_ = flip traverse1_
7076
-- | Perform all of the effects in some data structure in the order
7177
-- | given by the `Foldable1` instance, ignoring the final result.
7278
sequence1_ :: forall t f a. Foldable1 t => Apply f => t (f a) -> f Unit
73-
sequence1_ = traverse1_ id
79+
sequence1_ = traverse1_ identity
80+
81+
maximum :: forall f a. Ord a => Foldable1 f => f a -> a
82+
maximum = ala Max foldMap1
83+
84+
minimum :: forall f a. Ord a => Foldable1 f => f a -> a
85+
minimum = ala Min foldMap1
86+
87+
-- | Internal. Used by intercalation functions.
88+
newtype JoinWith a = JoinWith (a -> a)
89+
90+
joinee :: forall a. JoinWith a -> a -> a
91+
joinee (JoinWith x) = x
92+
93+
instance semigroupJoinWith :: Semigroup a => Semigroup (JoinWith a) where
94+
append (JoinWith a) (JoinWith b) = JoinWith $ \j -> a j <> j <> b j
95+
96+
-- | Fold a data structure using a `Semigroup` instance,
97+
-- | combining adjacent elements using the specified separator.
98+
intercalate :: forall f m. Foldable1 f => Semigroup m => m -> f m -> m
99+
intercalate = flip intercalateMap identity
100+
101+
-- | Fold a data structure, accumulating values in some `Semigroup`,
102+
-- | combining adjacent elements using the specified separator.
103+
intercalateMap
104+
:: forall f m a
105+
. Foldable1 f
106+
=> Semigroup m
107+
=> m -> (a -> m) -> f a -> m
108+
intercalateMap j f foldable =
109+
joinee (foldMap1 (JoinWith <<< const <<< f) foldable) j

0 commit comments

Comments
 (0)