Skip to content

Commit

Permalink
Upgraded to PureScript 0.12 (#4)
Browse files Browse the repository at this point in the history
* upgraded to purescript 0.12

* made purescript-console a dev dependency and hid a couple of instance of 'identiy' from Prelude

* set purescript-psa back to 0.5.0 due to a bug I'm encountering with it - reported in that repo

* upgraded purescript-psa to 0.7.3
  • Loading branch information
dwhitney authored and natefaubion committed Aug 24, 2018
1 parent 1eb765d commit ff42f05
Show file tree
Hide file tree
Showing 7 changed files with 31 additions and 28 deletions.
12 changes: 6 additions & 6 deletions bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -25,13 +25,13 @@
"test"
],
"dependencies": {
"purescript-prelude": "^3.0.0",
"purescript-console": "^3.0.0",
"purescript-run": "^1.0.0"
"purescript-prelude": "^4.1.0",
"purescript-run": "^2.0.0"
},
"devDependencies": {
"purescript-psci-support": "^3.0.0",
"purescript-assert": "^3.0.0",
"purescript-debug": "^3.0.0"
"purescript-psci-support": "^4.0.0",
"purescript-assert": "^4.0.0",
"purescript-console": "^4.1.0",
"purescript-debug": "^4.0.0"
}
}
6 changes: 3 additions & 3 deletions package.json
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
},
"devDependencies": {
"bower": "^1.8.2",
"pulp": "^11.0.2",
"purescript": "^0.11.6",
"purescript-psa": "^0.5.0"
"pulp": "^12.3.0",
"purescript": "^0.12.0",
"purescript-psa": "^0.7.3"
}
}
8 changes: 5 additions & 3 deletions src/Run/Streaming.purs
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,10 @@ module Run.Streaming
) where

import Prelude

import Data.Profunctor (class Profunctor, dimap)
import Data.Symbol (class IsSymbol)
import Prim.Row (class Cons)
import Run (Run, SProxy(..), FProxy)
import Run as Run

Expand Down Expand Up @@ -63,11 +65,11 @@ liftAwait = Run.lift _await

-- | Yields a response and waits for a request.
respond req res r. res Run (Server req res r) req
respond res = liftYield (Step res id)
respond res = liftYield (Step res identity)

-- | Issues a request and awaits a response.
request req res r. req Run (Client req res r) res
request req = liftAwait (Step req id)
request req = liftAwait (Step req identity)

-- | Yields a value to be consumed downstream.
yield o r. o Run (Producer o r) Unit
Expand Down Expand Up @@ -111,7 +113,7 @@ instance profunctorResume ∷ Profunctor (Resume r a) where

runStep
sym i o r1 r2 a
. RowCons sym (FProxy (Step i o)) r1 r2
. Cons sym (FProxy (Step i o)) r1 r2
IsSymbol sym
SProxy sym
Run r2 a
Expand Down
14 changes: 7 additions & 7 deletions src/Run/Streaming/Prelude.purs
Original file line number Diff line number Diff line change
Expand Up @@ -205,11 +205,11 @@ any f = P.map not <<< null <<< Pull.feed (filter f)

-- | Checks if all yielded values are true.
and r. Run (Producer Boolean (Producer Boolean r)) Unit Run r Boolean
and = all id
and = all identity

-- | Checks if any yielded values are true.
or r. Run (Producer Boolean (Producer Boolean r)) Unit Run r Boolean
or = any id
or = any identity

-- | Checks if a value occurs in the stream.
elem r x. Eq x x Run (Producer x (Producer x r)) Unit Run r Boolean
Expand Down Expand Up @@ -294,27 +294,27 @@ foldM' step init done ra = do

-- | Returns the number of values yielded by a Producer.
length r x. Run (Producer x r) Unit Run r Int
length = fold (const <<< add 1) 0 id
length = fold (const <<< add 1) 0 identity

-- | Returns the sum of values yielded by a Producer.
sum r x. Semiring x Run (Producer x r) Unit Run r x
sum = fold (+) zero id
sum = fold (+) zero identity

-- | Returns the product of values yielded by a Producer.
product r x. Semiring x Run (Producer x r) Unit Run r x
product = fold (*) one id
product = fold (*) one identity

-- | Returns the minimum value yielded by a Producer.
minimum r x. Ord x Run (Producer x r) Unit Run r (Maybe x)
minimum = fold go Nothing id
minimum = fold go Nothing identity
where
go x y = Just case x of
Nothing → y
Just x' → min x' y

-- | Returns the maximum value yielded by a Producer.
maximum r x. Ord x Run (Producer x r) Unit Run r (Maybe x)
maximum = fold go Nothing id
maximum = fold go Nothing identity
where
go x y = Just case x of
Nothing → y
Expand Down
2 changes: 1 addition & 1 deletion src/Run/Streaming/Pull.purs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module Run.Streaming.Pull
, consume
) where

import Prelude hiding (compose)
import Prelude hiding (compose, identity)
import Run (Run)
import Run.Streaming as RS

Expand Down
2 changes: 1 addition & 1 deletion src/Run/Streaming/Push.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module Run.Streaming.Push
, produce
) where

import Prelude hiding (compose)
import Prelude hiding (compose, identity)
import Run (Run)
import Run.Streaming as RS

Expand Down
15 changes: 8 additions & 7 deletions test/Main.purs
Original file line number Diff line number Diff line change
@@ -1,24 +1,25 @@
module Test.Main where

import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Prelude hiding (map)

import Data.Array as A
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Prelude hiding (map)
import Effect (Effect)
import Effect.Console (log)
import Run (Run, extract)
import Run.Streaming.Prelude as S
import Run.Streaming.Pull as Pull
import Run.Streaming.Push as Push
import Test.Assert (ASSERT, assert')
import Test.Assert (assert')

assert eff. String Boolean Eff (assert ASSERT, console CONSOLE | eff) Unit
assert String Boolean Effect Unit
assert label ok
| ok = log ("[OK] " <> label)
| otherwise = log ("[xx] " <> label) *> assert' label ok

toArray x. Run (S.Producer x ()) Unit Array x
toArray = extract <<< S.fold A.snoc [] id
toArray = extract <<< S.fold A.snoc [] identity

-- Push based take
take' x r. Int x Run (S.Transformer x x r) Unit
Expand All @@ -28,7 +29,7 @@ take' n x = S.yield x >>= S.request >>= take' (n - 1)
data Req = A Int | B Int
type Rep = String

main Eff (assert ASSERT, console CONSOLE) Unit
main Effect Unit
main = do
assert "pull/take"
let
Expand Down

0 comments on commit ff42f05

Please sign in to comment.