purescript-node-stream-pipes/src/Pipes.Node.FS.purs

80 lines
2.7 KiB
Haskell
Raw Permalink Normal View History

module Pipes.Node.FS where
import Prelude
2024-05-12 03:08:02 +00:00
import Control.Monad.Error.Class (class MonadThrow)
import Data.Maybe (Maybe)
2024-05-12 03:08:02 +00:00
import Effect.Aff.Class (class MonadAff)
import Effect.Class (liftEffect)
2024-05-12 03:08:02 +00:00
import Effect.Exception (Error)
import Node.Buffer (Buffer)
2024-05-13 18:27:18 +00:00
import Node.FS.Stream (WriteStreamOptions, ReadStreamOptions)
import Node.FS.Stream as FS.Stream
import Node.Path (FilePath)
import Node.Stream.Object as O
import Pipes.Core (Consumer, Producer)
import Pipes.Node.Stream (fromReadable, fromWritable)
import Prim.Row (class Union)
-- | Creates a `fs.Writable` stream for the file
-- | at the given path.
-- |
-- | Writing `Nothing` to this pipe will close the stream.
-- |
-- | See `Pipes.Node.Stream.withEOS` for converting `Producer a`
-- | into `Producer (Maybe a)`, emitting `Nothing` before exiting.
2024-05-15 18:29:58 +00:00
write'
2024-05-12 03:08:02 +00:00
:: forall r trash m
. Union r trash WriteStreamOptions
2024-05-12 03:08:02 +00:00
=> MonadAff m
=> MonadThrow Error m
=> Record r
-> FilePath
2024-05-12 03:08:02 +00:00
-> Consumer (Maybe Buffer) m Unit
2024-05-15 18:29:58 +00:00
write' o p = do
w <- liftEffect $ FS.Stream.createWriteStream' p o
2024-05-15 18:29:58 +00:00
fromWritable $ O.unsafeCoerceWritable w
-- | Open a file in write mode, failing if the file already exists.
-- |
2024-05-15 18:29:58 +00:00
-- | `write' {flags: "wx"}`
2024-05-12 03:08:02 +00:00
create :: forall m. MonadAff m => MonadThrow Error m => FilePath -> Consumer (Maybe Buffer) m Unit
2024-05-15 18:29:58 +00:00
create = write' { flags: "wx" }
-- | Open a file in write mode, truncating it if the file already exists.
-- |
2024-05-15 18:29:58 +00:00
-- | `write' {flags: "w"}`
trunc :: forall m. MonadAff m => MonadThrow Error m => FilePath -> Consumer (Maybe Buffer) m Unit
trunc = write' { flags: "w" }
-- | Open a file in write mode, appending written contents if the file already exists.
-- |
2024-05-15 18:29:58 +00:00
-- | `write' {flags: "a"}`
2024-05-12 03:08:02 +00:00
append :: forall m. MonadAff m => MonadThrow Error m => FilePath -> Consumer (Maybe Buffer) m Unit
2024-05-15 18:29:58 +00:00
append = write' { flags: "a" }
-- | Creates a `fs.Readable` stream for the file at the given path.
-- |
-- | Emits `Nothing` before closing. To opt out of this behavior,
-- | use `Pipes.Node.Stream.withoutEOS` or `Pipes.Node.Stream.unEOS`.
2024-05-12 03:08:02 +00:00
read :: forall m. MonadAff m => MonadThrow Error m => FilePath -> Producer (Maybe Buffer) m Unit
read p = do
r <- liftEffect $ FS.Stream.createReadStream p
2024-05-15 18:29:58 +00:00
fromReadable $ O.unsafeCoerceReadable r
2024-05-13 18:27:18 +00:00
-- | Creates a `fs.Readable` stream for the file at the given path.
-- |
-- | Emits `Nothing` before closing. To opt out of this behavior,
-- | use `Pipes.Node.Stream.withoutEOS` or `Pipes.Node.Stream.unEOS`.
read'
:: forall r trash m
. Union r trash ReadStreamOptions
=> MonadAff m
=> MonadThrow Error m
=> Record r
-> FilePath
-> Producer (Maybe Buffer) m Unit
read' opts p = do
r <- liftEffect $ FS.Stream.createReadStream' p opts
2024-05-15 18:29:58 +00:00
fromReadable $ O.unsafeCoerceReadable r