Skip to content

Commit e84d02e

Browse files
committed
Bump deps for compiler/0.12
1 parent 2bb1c95 commit e84d02e

File tree

14 files changed

+45
-51
lines changed

14 files changed

+45
-51
lines changed

bower.json

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -20,17 +20,17 @@
2020
"package.json"
2121
],
2222
"dependencies": {
23-
"purescript-lazy": "^3.0.0",
24-
"purescript-nonempty": "^4.0.0",
25-
"purescript-tailrec": "^3.3.0",
26-
"purescript-unfoldable": "^3.0.0",
27-
"purescript-partial": "^1.0.0",
28-
"purescript-foldable-traversable": "^3.4.0"
23+
"purescript-lazy": "#compiler/0.12",
24+
"purescript-nonempty": "#compiler/0.12",
25+
"purescript-tailrec": "#compiler/0.12",
26+
"purescript-unfoldable": "#compiler/0.12",
27+
"purescript-partial": "#compiler/0.12",
28+
"purescript-foldable-traversable": "#compiler/0.12"
2929
},
3030
"devDependencies": {
31-
"purescript-arrays": "^4.0.0",
32-
"purescript-assert": "^3.0.0",
33-
"purescript-console": "^3.0.0",
34-
"purescript-math": "^2.0.0"
31+
"purescript-arrays": "#compiler/0.12",
32+
"purescript-assert": "#compiler/0.12",
33+
"purescript-console": "#compiler/0.12",
34+
"purescript-math": "#compiler/0.12"
3535
}
3636
}

package.json

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,11 @@
33
"scripts": {
44
"clean": "rimraf output && rimraf .pulp-cache",
55
"build": "pulp build -- --censor-lib --strict",
6-
"test": "pulp test"
6+
"test": "pulp test --check-main-type Effect.Effect"
77
},
88
"devDependencies": {
99
"pulp": "^12.0.1",
1010
"purescript-psa": "^0.6.0",
11-
"rimraf": "^2.6.1"
11+
"rimraf": "^2.6.2"
1212
}
1313
}

src/Data/List.purs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -372,7 +372,7 @@ reverse = go Nil
372372
-- |
373373
-- | Running time: `O(n)`, where `n` is the total number of elements.
374374
concat :: forall a. List (List a) -> List a
375-
concat = (_ >>= id)
375+
concat = (_ >>= identity)
376376

377377
-- | Apply a function to each element in a list, and flatten the results
378378
-- | into a single, new list.
@@ -423,7 +423,7 @@ mapMaybe f = go Nil
423423
-- | Filter a list of optional values, keeping only the elements which contain
424424
-- | a value.
425425
catMaybes :: forall a. List (Maybe a) -> List a
426-
catMaybes = mapMaybe id
426+
catMaybes = mapMaybe identity
427427

428428

429429
-- | Apply a function to each element and its index in a list starting at 0.

src/Data/List/Lazy.purs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -409,7 +409,7 @@ reverse xs = Z.defer \_ -> foldl (flip cons) nil xs
409409
-- |
410410
-- | Running time: `O(n)`, where `n` is the total number of elements.
411411
concat :: forall a. List (List a) -> List a
412-
concat = (_ >>= id)
412+
concat = (_ >>= identity)
413413

414414
-- | Apply a function to each element in a list, and flatten the results
415415
-- | into a single, new list.
@@ -463,7 +463,7 @@ mapMaybe f = List <<< map go <<< unwrap
463463
-- | Filter a list of optional values, keeping only the elements which contain
464464
-- | a value.
465465
catMaybes :: forall a. List (Maybe a) -> List a
466-
catMaybes = mapMaybe id
466+
catMaybes = mapMaybe identity
467467

468468
--------------------------------------------------------------------------------
469469
-- Sorting ---------------------------------------------------------------------

src/Data/List/Lazy/Types.purs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@ import Data.FoldableWithIndex (class FoldableWithIndex, foldlWithIndex, foldrWit
1616
import Data.FunctorWithIndex (class FunctorWithIndex)
1717
import Data.Lazy (Lazy, defer, force)
1818
import Data.Maybe (Maybe(..))
19-
import Data.Monoid (class Monoid, mempty)
2019
import Data.Newtype (class Newtype, unwrap)
2120
import Data.NonEmpty (NonEmpty, (:|))
2221
import Data.NonEmpty as NE
@@ -151,7 +150,7 @@ instance traversableList :: Traversable List where
151150
traverse f =
152151
foldr (\a b -> cons <$> f a <*> b) (pure nil)
153152

154-
sequence = traverse id
153+
sequence = traverse identity
155154

156155
instance traversableWithIndexList :: TraversableWithIndex Int List where
157156
traverseWithIndex f =

src/Data/List/NonEmpty.purs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -210,7 +210,7 @@ catMaybes :: forall a. NonEmptyList (Maybe a) -> L.List a
210210
catMaybes = lift L.catMaybes
211211

212212
concat :: forall a. NonEmptyList (NonEmptyList a) -> NonEmptyList a
213-
concat = (_ >>= id)
213+
concat = (_ >>= identity)
214214

215215
concatMap :: forall a b. (a -> NonEmptyList b) -> NonEmptyList a -> NonEmptyList b
216216
concatMap = flip bind

src/Data/List/Types.purs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@ import Data.Foldable (class Foldable, foldl, foldr, intercalate)
1515
import Data.FoldableWithIndex (class FoldableWithIndex, foldlWithIndex, foldrWithIndex)
1616
import Data.FunctorWithIndex (class FunctorWithIndex)
1717
import Data.Maybe (Maybe(..))
18-
import Data.Monoid (class Monoid, mempty)
1918
import Data.Newtype (class Newtype)
2019
import Data.NonEmpty (NonEmpty, (:|))
2120
import Data.NonEmpty as NE
@@ -108,7 +107,7 @@ instance unfoldableList :: Unfoldable List where
108107

109108
instance traversableList :: Traversable List where
110109
traverse f = map (foldl (flip (:)) Nil) <<< foldl (\acc -> lift2 (flip (:)) acc <<< f) (pure Nil)
111-
sequence = traverse id
110+
sequence = traverse identity
112111

113112
instance traversableWithIndexList :: TraversableWithIndex Int List where
114113
traverseWithIndex f =
@@ -214,4 +213,4 @@ instance traversable1NonEmptyList :: Traversable1 NonEmptyList where
214213
traverse1 f (NonEmptyList (a :| as)) =
215214
foldl (\acc -> lift2 (flip nelCons) acc <<< f) (pure <$> f a) as
216215
<#> case _ of NonEmptyList (x :| xs) → foldl (flip nelCons) (pure x) xs
217-
sequence1 = traverse1 id
216+
sequence1 = traverse1 identity

src/Data/List/ZipList.purs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@ import Control.Alternative (class Alternative)
1212
import Control.Plus (class Plus)
1313
import Data.Foldable (class Foldable)
1414
import Data.List.Lazy (List, repeat, zipWith)
15-
import Data.Monoid (class Monoid, mempty)
1615
import Data.Newtype (class Newtype)
1716
import Data.Traversable (class Traversable)
1817
import Partial.Unsafe (unsafeCrashWith)

test/Test/Data/List.purs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,8 @@ module Test.Data.List (testList) where
22

33
import Prelude
44

5-
import Control.Monad.Eff (Eff)
6-
import Control.Monad.Eff.Console (CONSOLE, log)
5+
import Effect (Effect)
6+
import Effect.Console (log)
77
import Data.Foldable (foldMap, foldl)
88
import Data.FoldableWithIndex (foldMapWithIndex, foldlWithIndex, foldrWithIndex)
99
import Data.List (List(..), (..), stripPrefix, Pattern(..), length, range, foldM, unzip, zip, zipWithA, zipWith, intersectBy, intersect, (\\), deleteBy, delete, unionBy, union, nubBy, nub, groupBy, group', group, partition, span, dropWhile, drop, dropEnd, takeWhile, take, takeEnd, sortBy, sort, catMaybes, mapMaybe, filterM, filter, concat, concatMap, reverse, alterAt, modifyAt, updateAt, deleteAt, insertAt, findLastIndex, findIndex, elemLastIndex, elemIndex, (!!), uncons, unsnoc, init, tail, last, head, insertBy, insert, snoc, null, singleton, fromFoldable, transpose, mapWithIndex, (:))
@@ -16,9 +16,9 @@ import Data.TraversableWithIndex (traverseWithIndex)
1616
import Data.Tuple (Tuple(..))
1717
import Data.Unfoldable (replicate, replicateA, unfoldr)
1818
import Partial.Unsafe (unsafePartial)
19-
import Test.Assert (ASSERT, assert)
19+
import Test.Assert (assert)
2020

21-
testList :: forall eff. Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
21+
testList :: Effect Unit
2222
testList = do
2323
let l = fromFoldable
2424

@@ -358,7 +358,7 @@ testList = do
358358
assert $ (1..5) == unfoldr step 1
359359

360360
log "map should maintain order"
361-
assert $ (1..5) == map id (1..5)
361+
assert $ (1..5) == map identity (1..5)
362362

363363
log "transpose"
364364
assert $ transpose (l [l [1,2,3], l[4,5,6], l [7,8,9]]) ==

test/Test/Data/List/Lazy.purs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,8 @@ module Test.Data.List.Lazy (testListLazy) where
33
import Prelude
44

55
import Control.Lazy (defer)
6-
import Control.Monad.Eff (Eff)
7-
import Control.Monad.Eff.Console (CONSOLE, log)
6+
import Effect (Effect)
7+
import Effect.Console (log)
88
import Data.FoldableWithIndex (foldMapWithIndex, foldlWithIndex, foldrWithIndex)
99
import Data.FunctorWithIndex (mapWithIndex)
1010
import Data.Lazy as Z
@@ -17,9 +17,9 @@ import Data.Traversable (traverse)
1717
import Data.TraversableWithIndex (traverseWithIndex)
1818
import Data.Tuple (Tuple(..))
1919
import Partial.Unsafe (unsafePartial)
20-
import Test.Assert (ASSERT, assert)
20+
import Test.Assert (assert)
2121

22-
testListLazy :: forall eff. Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
22+
testListLazy :: Effect Unit
2323
testListLazy = do
2424
let
2525
l = fromFoldable

test/Test/Data/List/NonEmpty.purs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2,19 +2,18 @@ module Test.Data.List.NonEmpty (testNonEmptyList) where
22

33
import Prelude
44

5-
import Control.Monad.Eff (Eff)
6-
import Control.Monad.Eff.Console (CONSOLE, log)
5+
import Effect (Effect)
6+
import Effect.Console (log)
77
import Data.Foldable (class Foldable, foldM, foldMap, foldl, length)
88
import Data.List as L
99
import Data.List.NonEmpty as NEL
1010
import Data.Maybe (Maybe(..))
1111
import Data.Monoid.Additive (Additive(..))
1212
import Data.NonEmpty ((:|))
1313
import Data.Tuple (Tuple(..))
14-
import Test.Assert (ASSERT, assert)
14+
import Test.Assert (assert)
1515

16-
testNonEmptyList ::
17-
forall eff. Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
16+
testNonEmptyList :: Effect Unit
1817
testNonEmptyList = do
1918
let
2019
nel :: f a. Foldable f => a -> f a -> NEL.NonEmptyList a
@@ -223,7 +222,7 @@ testNonEmptyList = do
223222
assert $ foldMap show (nel 1 (L.range 2 5)) == "12345"
224223

225224
log "map should maintain order"
226-
assert $ nel 0 (L.range 1 5) == map id (nel 0 (L.range 1 5))
225+
assert $ nel 0 (L.range 1 5) == map identity (nel 0 (L.range 1 5))
227226

228227
log "traverse1 should be stack-safe"
229228
let xs = nel 0 (L.range 1 100000)

test/Test/Data/List/Partial.purs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,17 +2,17 @@ module Test.Data.List.Partial (testListPartial) where
22

33
import Prelude
44

5-
import Control.Monad.Eff (Eff)
6-
import Control.Monad.Eff.Console (CONSOLE, log)
5+
import Effect (Effect)
6+
import Effect.Console (log)
77

88
import Data.List (List(..), fromFoldable)
99
import Data.List.Partial (init, tail, last, head)
1010

1111
import Partial.Unsafe (unsafePartial)
1212

13-
import Test.Assert (ASSERT, assert, assertThrows)
13+
import Test.Assert (assert, assertThrows)
1414

15-
testListPartial :: forall eff. Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
15+
testListPartial :: Effect Unit
1616
testListPartial = do
1717
let l = fromFoldable
1818

test/Test/Data/List/ZipList.purs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,23 +2,23 @@ module Test.Data.List.ZipList (testZipList) where
22

33
import Prelude
44

5-
import Control.Monad.Eff (Eff)
6-
import Control.Monad.Eff.Console (CONSOLE, log)
5+
import Effect (Effect)
6+
import Effect.Console (log)
77

88
import Data.Array as Array
99
import Data.List.Lazy as LazyList
1010
import Data.List.ZipList (ZipList(..))
1111

12-
import Test.Assert (ASSERT, assert)
12+
import Test.Assert (assert)
1313

14-
testZipList :: forall eff. Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
14+
testZipList :: Effect Unit
1515
testZipList = do
1616
log "ZipList Applicative instance should be zippy"
1717
testZipWith (+) [1,2,3] [4,5,6]
1818
testZipWith (*) [1,2,3] [4,5,6]
1919
testZipWith const [1,2,3] [4,5,6]
2020

21-
testZipWith :: forall a b c eff. Eq c => (a -> b -> c) -> Array a -> Array b -> Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
21+
testZipWith :: forall a b c. Eq c => (a -> b -> c) -> Array a -> Array b -> Effect Unit
2222
testZipWith f xs ys =
2323
assert $ (f <$> l xs <*> l ys) == l (Array.zipWith f xs ys)
2424

test/Test/Main.purs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,17 +2,15 @@ module Test.Main where
22

33
import Prelude
44

5-
import Control.Monad.Eff (Eff)
6-
import Control.Monad.Eff.Console (CONSOLE)
5+
import Effect (Effect)
76

8-
import Test.Assert (ASSERT)
97
import Test.Data.List (testList)
108
import Test.Data.List.Lazy (testListLazy)
119
import Test.Data.List.Partial (testListPartial)
1210
import Test.Data.List.ZipList (testZipList)
1311
import Test.Data.List.NonEmpty (testNonEmptyList)
1412

15-
main :: forall eff. Eff (assert :: ASSERT, console :: CONSOLE | eff) Unit
13+
main :: Effect Unit
1614
main = do
1715
testList
1816
testListLazy

0 commit comments

Comments
 (0)