@@ -36,9 +36,8 @@ module Node.Stream
3636
3737import Prelude
3838
39- import Control.Monad.Eff (Eff , kind Effect )
40- import Control.Monad.Eff.Exception (throw , EXCEPTION (), Error ())
41- import Control.Monad.Eff.Unsafe (unsafeCoerceEff )
39+ import Effect (Effect )
40+ import Effect.Exception (throw , Error ())
4241import Data.Either (Either (..))
4342import Data.Maybe (Maybe (..), fromMaybe )
4443import Node.Buffer (Buffer ())
@@ -51,7 +50,7 @@ import Node.Encoding (Encoding)
5150-- |
5251-- | - Whether reading and/or writing from/to the stream are allowed.
5352-- | - Effects associated with reading/writing from/to this stream.
54- foreign import data Stream :: # Type -> # Effect -> Type
53+ foreign import data Stream :: # Type -> Type
5554
5655-- | A phantom type associated with _readable streams_.
5756data Read
@@ -84,10 +83,10 @@ readChunk = readChunkImpl Left Right
8483-- | Listen for `data` events, returning data in a Buffer. Note that this will fail
8584-- | if `setEncoding` has been called on the stream.
8685onData
87- :: forall w eff
88- . Readable w ( exception :: EXCEPTION | eff )
89- -> (Buffer -> Eff ( exception :: EXCEPTION | eff ) Unit )
90- -> Eff ( exception :: EXCEPTION | eff ) Unit
86+ :: forall w
87+ . Readable w
88+ -> (Buffer -> Effect Unit )
89+ -> Effect Unit
9190onData r cb =
9291 onDataEither r (cb <=< fromEither)
9392 where
@@ -99,10 +98,10 @@ onData r cb =
9998 pure buf
10099
101100read
102- :: forall w eff
103- . Readable w ( exception :: EXCEPTION | eff )
101+ :: forall w
102+ . Readable w
104103 -> Maybe Int
105- -> Eff ( exception :: EXCEPTION | eff ) (Maybe Buffer )
104+ -> Effect (Maybe Buffer )
106105read r size = do
107106 v <- readEither r size
108107 case v of
@@ -111,67 +110,67 @@ read r size = do
111110 Just (Right b) -> pure (Just b)
112111
113112readString
114- :: forall w eff
115- . Readable w ( exception :: EXCEPTION | eff )
113+ :: forall w
114+ . Readable w
116115 -> Maybe Int
117116 -> Encoding
118- -> Eff ( exception :: EXCEPTION | eff ) (Maybe String )
117+ -> Effect (Maybe String )
119118readString r size enc = do
120119 v <- readEither r size
121120 case v of
122121 Nothing -> pure Nothing
123122 Just (Left _) -> throw " Stream encoding should not be set"
124- Just (Right buf) -> Just <$> (unsafeCoerceEff $ Buffer .toString enc buf)
123+ Just (Right buf) -> Just <$> Buffer .toString enc buf
125124
126125readEither
127- :: forall w eff
128- . Readable w eff
126+ :: forall w
127+ . Readable w
129128 -> Maybe Int
130- -> Eff eff (Maybe (Either String Buffer ))
129+ -> Effect (Maybe (Either String Buffer ))
131130readEither r size = readImpl readChunk Nothing Just r (fromMaybe undefined size)
132131
133132foreign import readImpl
134- :: forall r eff
133+ :: forall r
135134 . (Chunk -> Either String Buffer )
136135 -> (forall a . Maybe a )
137136 -> (forall a . a -> Maybe a )
138- -> Readable r eff
137+ -> Readable r
139138 -> Int
140- -> Eff eff (Maybe (Either String Buffer ))
139+ -> Effect (Maybe (Either String Buffer ))
141140
142141-- | Listen for `data` events, returning data in a String, which will be
143142-- | decoded using the given encoding. Note that this will fail if `setEncoding`
144143-- | has been called on the stream.
145144onDataString
146- :: forall w eff
147- . Readable w ( exception :: EXCEPTION | eff )
145+ :: forall w
146+ . Readable w
148147 -> Encoding
149- -> (String -> Eff ( exception :: EXCEPTION | eff ) Unit )
150- -> Eff ( exception :: EXCEPTION | eff ) Unit
151- onDataString r enc cb = onData r (cb <=< unsafeCoerceEff <<< Buffer .toString enc)
148+ -> (String -> Effect Unit )
149+ -> Effect Unit
150+ onDataString r enc cb = onData r (cb <=< Buffer .toString enc)
152151
153152-- | Listen for `data` events, returning data in an `Either String Buffer`. This
154153-- | function is provided for the (hopefully rare) case that `setEncoding` has
155154-- | been called on the stream.
156155onDataEither
157- :: forall r eff
158- . Readable r ( exception :: EXCEPTION | eff )
159- -> (Either String Buffer -> Eff ( exception :: EXCEPTION | eff ) Unit )
160- -> Eff ( exception :: EXCEPTION | eff ) Unit
156+ :: forall r
157+ . Readable r
158+ -> (Either String Buffer -> Effect Unit )
159+ -> Effect Unit
161160onDataEither r cb = onDataEitherImpl readChunk r cb
162161
163162foreign import onDataEitherImpl
164- :: forall r eff
163+ :: forall r
165164 . (Chunk -> Either String Buffer )
166- -> Readable r eff
167- -> (Either String Buffer -> Eff eff Unit )
168- -> Eff eff Unit
165+ -> Readable r
166+ -> (Either String Buffer -> Effect Unit )
167+ -> Effect Unit
169168
170169foreign import setEncodingImpl
171- :: forall w eff
172- . Readable w eff
170+ :: forall w
171+ . Readable w
173172 -> String
174- -> Eff eff Unit
173+ -> Effect Unit
175174
176175-- | Set the encoding used to read chunks as strings from the stream. This
177176-- | function may be useful when you are passing a readable stream to some other
@@ -180,146 +179,146 @@ foreign import setEncodingImpl
180179-- | Where possible, you should try to use `onDataString` instead of this
181180-- | function.
182181setEncoding
183- :: forall w eff
184- . Readable w eff
182+ :: forall w
183+ . Readable w
185184 -> Encoding
186- -> Eff eff Unit
185+ -> Effect Unit
187186setEncoding r enc = setEncodingImpl r (show enc)
188187
189188-- | Listen for `readable` events.
190189foreign import onReadable
191- :: forall w eff
192- . Readable w eff
193- -> Eff eff Unit
194- -> Eff eff Unit
190+ :: forall w
191+ . Readable w
192+ -> Effect Unit
193+ -> Effect Unit
195194
196195-- | Listen for `end` events.
197196foreign import onEnd
198- :: forall w eff
199- . Readable w eff
200- -> Eff eff Unit
201- -> Eff eff Unit
197+ :: forall w
198+ . Readable w
199+ -> Effect Unit
200+ -> Effect Unit
202201
203202-- | Listen for `finish` events.
204203foreign import onFinish
205- :: forall w eff
206- . Writable w eff
207- -> Eff eff Unit
208- -> Eff eff Unit
204+ :: forall w
205+ . Writable w
206+ -> Effect Unit
207+ -> Effect Unit
209208
210209-- | Listen for `close` events.
211210foreign import onClose
212- :: forall w eff
213- . Stream w eff
214- -> Eff eff Unit
215- -> Eff eff Unit
211+ :: forall w
212+ . Stream w
213+ -> Effect Unit
214+ -> Effect Unit
216215
217216-- | Listen for `error` events.
218217foreign import onError
219- :: forall w eff
220- . Stream w eff
221- -> (Error -> Eff eff Unit )
222- -> Eff eff Unit
218+ :: forall w
219+ . Stream w
220+ -> (Error -> Effect Unit )
221+ -> Effect Unit
223222
224223-- | Resume reading from the stream.
225- foreign import resume :: forall w eff . Readable w eff -> Eff eff Unit
224+ foreign import resume :: forall w . Readable w -> Effect Unit
226225
227226-- | Pause reading from the stream.
228- foreign import pause :: forall w eff . Readable w eff -> Eff eff Unit
227+ foreign import pause :: forall w . Readable w -> Effect Unit
229228
230229-- | Check whether or not a stream is paused for reading.
231- foreign import isPaused :: forall w eff . Readable w eff -> Eff eff Boolean
230+ foreign import isPaused :: forall w . Readable w -> Effect Boolean
232231
233232-- | Read chunks from a readable stream and write them to a writable stream.
234233foreign import pipe
235- :: forall r w eff
236- . Readable w eff
237- -> Writable r eff
238- -> Eff eff (Writable r eff )
234+ :: forall r w
235+ . Readable w
236+ -> Writable r
237+ -> Effect (Writable r )
239238
240239-- | Detach a Writable stream previously attached using `pipe`.
241240foreign import unpipe
242- :: forall r w eff
243- . Readable w eff
244- -> Writable r eff
245- -> Eff eff Unit
241+ :: forall r w
242+ . Readable w
243+ -> Writable r
244+ -> Effect Unit
246245
247246-- | Detach all Writable streams previously attached using `pipe`.
248247foreign import unpipeAll
249- :: forall w eff
250- . Readable w eff
251- -> Eff eff Unit
248+ :: forall w
249+ . Readable w
250+ -> Effect Unit
252251
253252-- | Write a Buffer to a writable stream.
254253foreign import write
255- :: forall r eff
256- . Writable r eff
254+ :: forall r
255+ . Writable r
257256 -> Buffer
258- -> Eff eff Unit
259- -> Eff eff Boolean
257+ -> Effect Unit
258+ -> Effect Boolean
260259
261260foreign import writeStringImpl
262- :: forall r eff
263- . Writable r eff
261+ :: forall r
262+ . Writable r
264263 -> String
265264 -> String
266- -> Eff eff Unit
267- -> Eff eff Boolean
265+ -> Effect Unit
266+ -> Effect Boolean
268267
269268-- | Write a string in the specified encoding to a writable stream.
270269writeString
271- :: forall r eff
272- . Writable r eff
270+ :: forall r
271+ . Writable r
273272 -> Encoding
274273 -> String
275- -> Eff eff Unit
276- -> Eff eff Boolean
274+ -> Effect Unit
275+ -> Effect Boolean
277276writeString w enc = writeStringImpl w (show enc)
278277
279278-- | Force buffering of writes.
280- foreign import cork :: forall r eff . Writable r eff -> Eff eff Unit
279+ foreign import cork :: forall r . Writable r -> Effect Unit
281280
282281-- | Flush buffered data.
283- foreign import uncork :: forall r eff . Writable r eff -> Eff eff Unit
282+ foreign import uncork :: forall r . Writable r -> Effect Unit
284283
285284foreign import setDefaultEncodingImpl
286- :: forall r eff
287- . Writable r eff
285+ :: forall r
286+ . Writable r
288287 -> String
289- -> Eff eff Unit
288+ -> Effect Unit
290289
291290-- | Set the default encoding used to write strings to the stream. This function
292291-- | is useful when you are passing a writable stream to some other JavaScript
293292-- | library, which already expects a default encoding to be set. It has no
294293-- | effect on the behaviour of the `writeString` function (because that
295294-- | function ensures that the encoding is always supplied explicitly).
296295setDefaultEncoding
297- :: forall r eff
298- . Writable r eff
296+ :: forall r
297+ . Writable r
299298 -> Encoding
300- -> Eff eff Unit
299+ -> Effect Unit
301300setDefaultEncoding r enc = setDefaultEncodingImpl r (show enc)
302301
303302-- | End writing data to the stream.
304303foreign import end
305- :: forall r eff
306- . Writable r eff
307- -> Eff eff Unit
308- -> Eff eff Unit
304+ :: forall r
305+ . Writable r
306+ -> Effect Unit
307+ -> Effect Unit
309308
310309-- | Destroy the stream. It will release any internal resources.
311310--
312311-- Added in node 8.0.
313312foreign import destroy
314- :: forall r eff
315- . Stream r eff
316- -> Eff eff Unit
313+ :: forall r
314+ . Stream r
315+ -> Effect Unit
317316
318317-- | Destroy the stream and emit 'error'.
319318--
320319-- Added in node 8.0.
321320foreign import destroyWithError
322- :: forall r eff
323- . Stream r eff
321+ :: forall r
322+ . Stream r
324323 -> Error
325- -> Eff eff Unit
324+ -> Effect Unit
0 commit comments