Skip to content

Commit

Permalink
Update to v0.14.0-rc3 (#122)
Browse files Browse the repository at this point in the history
* Update packages.dhall to prepare-0.14 bootstrap

* Update CI to use v0.14.0-rc3 PS release

* Add compiler's suggested kind annotations

* Replace usages of SProxy with Proxy or proxy

* Fix hash

* Fix module name for Proxy

* Specify all kinds to Type except for Forget and Tagged

This reverts a prior change

* Remove SHA hash from packages.dhall file
  • Loading branch information
JordanMartinez authored Dec 4, 2020
1 parent e7037b8 commit cddc073
Show file tree
Hide file tree
Showing 10 changed files with 25 additions and 8 deletions.
2 changes: 2 additions & 0 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,8 @@ jobs:

- name: Set up a PureScript toolchain
uses: purescript-contrib/setup-purescript@main
with:
purescript: "0.14.0-rc3"

- name: Cache PureScript dependencies
uses: actions/cache@v2
Expand Down
2 changes: 1 addition & 1 deletion packages.dhall
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.13.8-20201007/packages.dhall sha256:35633f6f591b94d216392c9e0500207bb1fec42dd355f4fecdfd186956567b6b
https://raw.githubusercontent.com/purescript/package-sets/prepare-0.14/src/packages.dhall

in upstream
1 change: 1 addition & 0 deletions src/Data/Lens/Internal/Bazaar.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Data.Traversable (traverse)
import Data.Tuple (Tuple(..))

-- | This is used to characterize a Traversal.
newtype Bazaar :: (Type -> Type -> Type) -> Type -> Type -> Type -> Type -> Type
newtype Bazaar p a b s t = Bazaar (forall f. Applicative f => p a (f b) -> s -> f t)

runBazaar :: forall p a b s t. Bazaar p a b s t -> (forall f. Applicative f => p a (f b) -> s -> f t)
Expand Down
1 change: 1 addition & 0 deletions src/Data/Lens/Internal/Forget.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ import Data.Tuple (fst, snd)
-- |
-- | `Forget r` is isomorphic to `Star (Const r)`, but can be given a `Cochoice`
-- | instance.
newtype Forget :: forall k. Type -> Type -> k -> Type
newtype Forget r a b = Forget (a -> r)

derive instance newtypeForget :: Newtype (Forget r a b) _
Expand Down
1 change: 1 addition & 0 deletions src/Data/Lens/Internal/Indexed.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import Data.Profunctor.Strong (class Strong, first, second)
import Data.Tuple (Tuple(..))

-- | Profunctor used for `IndexedOptic`s.
newtype Indexed :: (Type -> Type -> Type) -> Type -> Type -> Type -> Type
newtype Indexed p i s t = Indexed (p (Tuple i s) t)

derive instance newtypeIndexed :: Newtype (Indexed p i s t) _
Expand Down
1 change: 1 addition & 0 deletions src/Data/Lens/Internal/Re.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ import Data.Profunctor.Cochoice (class Cochoice, unleft, unright)
import Data.Profunctor.Costrong (class Costrong, unfirst, unsecond)
import Data.Profunctor.Strong (class Strong, first, second)

newtype Re :: (Type -> Type -> Type) -> Type -> Type -> Type -> Type -> Type
newtype Re p s t a b = Re (p b a -> p t s)

derive instance newtypeRe :: Newtype (Re p s t a b) _
Expand Down
1 change: 1 addition & 0 deletions src/Data/Lens/Internal/Tagged.purs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import Data.Profunctor.Costrong (class Costrong)
import Data.Traversable (class Traversable)
import Data.Tuple (Tuple(..))

newtype Tagged :: forall k. k -> Type -> Type
newtype Tagged a b = Tagged b

derive instance newtypeTagged :: Newtype (Tagged a b) _
Expand Down
8 changes: 4 additions & 4 deletions src/Data/Lens/Record.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Data.Lens.Record (prop) where
import Prelude

import Data.Lens (Lens, lens)
import Data.Symbol (class IsSymbol, SProxy)
import Data.Symbol (class IsSymbol)
import Prim.Row as Row
import Record (get, set)

Expand All @@ -15,14 +15,14 @@ import Record (get, set)
-- | For example:
-- |
-- | ```purescript
-- | prop (SProxy :: SProxy "foo")
-- | prop (Proxy :: Proxy "foo")
-- | :: forall a b r. Lens { foo :: a | r } { foo :: b | r } a b
-- | ```
prop
:: forall l r1 r2 r a b
:: forall l r1 r2 r a b proxy
. IsSymbol l
=> Row.Cons l a r r1
=> Row.Cons l b r r2
=> SProxy l
=> proxy l
-> Lens (Record r1) (Record r2) a b
prop l = lens (get l) (flip (set l))
10 changes: 10 additions & 0 deletions src/Data/Lens/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,10 @@ type ATraversal s t a b = Optic (Bazaar (->) a b) s t a b
type ATraversal' s a = ATraversal s s a a

-- | A general-purpose Data.Lens.
type Optic :: (Type -> Type -> Type) -> Type -> Type -> Type -> Type -> Type
type Optic p s t a b = p a b -> p s t

type Optic' :: (Type -> Type -> Type) -> Type -> Type -> Type
type Optic' p s a = Optic p s s a a

type AnIso s t a b = Optic (Exchange a b) s t a b
Expand Down Expand Up @@ -130,9 +133,11 @@ type AGrate s t a b = Optic (Grating a b) s t a b
type AGrate' s a = AGrate s s a a

-- | A getter.
type Getter :: Type -> Type -> Type -> Type -> Type
type Getter s t a b = forall r. Fold r s t a b
type Getter' s a = Getter s s a a

type AGetter :: Type -> Type -> Type -> Type -> Type
type AGetter s t a b = Fold a s t a b
type AGetter' s a = AGetter s s a a

Expand All @@ -141,14 +146,17 @@ type Setter s t a b = Optic Function s t a b
type Setter' s a = Setter s s a a

-- | A review.
type Review :: Type -> Type -> Type -> Type -> Type
type Review s t a b = Optic Tagged s t a b
type Review' s a = Review s s a a

-- | A fold.
type Fold :: Type -> Type -> Type -> Type -> Type -> Type
type Fold r s t a b = Optic (Forget r) s t a b
type Fold' r s a = Fold r s s a a

-- | An indexed optic.
type IndexedOptic :: (Type -> Type -> Type) -> Type -> Type -> Type -> Type -> Type -> Type
type IndexedOptic p i s t a b = Indexed p i a b -> p s t
type IndexedOptic' p i s a = IndexedOptic p i s s a a

Expand All @@ -157,10 +165,12 @@ type IndexedTraversal i s t a b = forall p. Wander p => IndexedOptic p i s t a b
type IndexedTraversal' i s a = IndexedTraversal i s s a a

-- | An indexed fold.
type IndexedFold :: Type -> Type -> Type -> Type -> Type -> Type -> Type
type IndexedFold r i s t a b = IndexedOptic (Forget r) i s t a b
type IndexedFold' r i s a = IndexedFold r i s s a a

-- | An indexed getter.
type IndexedGetter :: Type -> Type -> Type -> Type -> Type -> Type
type IndexedGetter i s t a b = IndexedFold a i s t a b
type IndexedGetter' i s a = IndexedGetter i s s a a

Expand Down
6 changes: 3 additions & 3 deletions test/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,18 +17,18 @@ import Data.Lens.Setter (iover)
import Data.Lens.Traversal (cloneTraversal)
import Data.Lens.Zoom (ATraversal', IndexedTraversal', Traversal, Traversal', Lens, Lens', zoom)
import Data.Maybe (Maybe(..))
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..), fst, snd)
import Effect (Effect)
import Effect.Console (logShow)
import Partial.Unsafe (unsafePartial)
import Type.Proxy (Proxy(..))

-- Traversing an array nested within a record
foo :: forall a b r. Lens { foo :: a | r } { foo :: b | r } a b
foo = prop (SProxy :: SProxy "foo")
foo = prop (Proxy :: Proxy "foo")

bar :: forall a b r. Lens { bar :: a | r } { bar :: b | r } a b
bar = prop (SProxy :: SProxy "bar")
bar = prop (Proxy :: Proxy "bar")

barAndFoo :: forall a b r. Getter' { bar :: a, foo :: b | r } (Tuple a b)
barAndFoo = takeBoth bar foo
Expand Down

0 comments on commit cddc073

Please sign in to comment.