Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- buildNarIO :: NarEffects IO -> FilePath -> Handle -> IO ()
- unpackNarIO :: NarEffects IO -> Handle -> FilePath -> IO (Either String ())
- parseNar :: (MonadIO m, MonadFail m) => NarParser m ()
- testParser :: m ~ IO => NarParser m a -> ByteString -> m (Either String a)
- testParser' :: m ~ IO => FilePath -> IO (Either String ())
- data NarEffects (m :: Type -> Type) = NarEffects {
- narReadFile :: FilePath -> m ByteString
- narWriteFile :: FilePath -> ByteString -> m ()
- narStreamFile :: FilePath -> m (Maybe ByteString) -> m ()
- narListDir :: FilePath -> m [FilePath]
- narCreateDir :: FilePath -> m ()
- narCreateLink :: FilePath -> FilePath -> m ()
- narGetPerms :: FilePath -> m Permissions
- narSetPerms :: FilePath -> Permissions -> m ()
- narIsDir :: FilePath -> m Bool
- narIsSymLink :: FilePath -> m Bool
- narFileSize :: FilePath -> m Int64
- narReadLink :: FilePath -> m FilePath
- narDeleteDir :: FilePath -> m ()
- narDeleteFile :: FilePath -> m ()
- narEffectsIO :: (MonadIO m, MonadFail m, MonadBaseControl IO m) => NarEffects m
- data NarOptions = NarOptions {}
- defaultNarOptions :: NarOptions
- streamNarIO :: forall m. MonadIO m => NarEffects IO -> FilePath -> NarSource m
- streamNarIOWithOptions :: forall m. MonadIO m => NarOptions -> NarEffects IO -> FilePath -> NarSource m
- runParser :: forall m a. (MonadIO m, MonadBaseControl IO m) => NarEffects m -> NarParser m a -> Handle -> FilePath -> m (Either String a)
- runParserWithOptions :: forall m a. (MonadIO m, MonadBaseControl IO m) => NarOptions -> NarEffects m -> NarParser m a -> Handle -> FilePath -> m (Either String a)
- dumpString :: forall m. MonadIO m => ByteString -> NarSource m
- dumpPath :: forall m. MonadIO m => FilePath -> NarSource m
- type NarSource m = (ByteString -> m ()) -> m ()
Encoding and Decoding NAR archives
buildNarIO :: NarEffects IO -> FilePath -> Handle -> IO () Source #
Pack the filesystem object at FilePath
into a NAR and stream it into the
IO.Handle
The handle should aleady be open and in WriteMode
.
unpackNarIO :: NarEffects IO -> Handle -> FilePath -> IO (Either String ()) Source #
Read NAR formatted bytes from the IO.Handle
and unpack them into
file system object(s) at the supplied FilePath
Experimental
parseNar :: (MonadIO m, MonadFail m) => NarParser m () Source #
Parse a NAR byte string, producing ()
.
Parsing a NAR is mostly used for its side-effect: producing
the file system objects packed in the NAR. That's why we pure ()
testParser :: m ~ IO => NarParser m a -> ByteString -> m (Either String a) Source #
Filesystem capabilities used by NAR encoder/decoder
data NarEffects (m :: Type -> Type) Source #
NarEffects | |
|
narEffectsIO :: (MonadIO m, MonadFail m, MonadBaseControl IO m) => NarEffects m Source #
A particular NarEffects
that uses regular POSIX for file manipulation
You would replace this with your own NarEffects
if you wanted a
different backend
data NarOptions Source #
Options for configuring how NAR files are encoded and decoded.
NarOptions | |
|
Internal
streamNarIO :: forall m. MonadIO m => NarEffects IO -> FilePath -> NarSource m Source #
This implementation of Nar encoding takes an arbitrary yield
function from any streaming library, and repeatedly calls
it while traversing the filesystem object to Nar encode
streamNarIOWithOptions :: forall m. MonadIO m => NarOptions -> NarEffects IO -> FilePath -> NarSource m Source #
:: forall m a. (MonadIO m, MonadBaseControl IO m) | |
=> NarEffects m | Provide the effects set, usually |
-> NarParser m a | A parser to run, such as |
-> Handle | A handle the stream containg the NAR. It should already be
open and in |
-> FilePath | The root file system object to be created by the NAR |
-> m (Either String a) |
Run a NarParser
over a byte stream
This is suitable for testing the top-level NAR parser, or any of the
smaller utilities parsers, if you have bytes appropriate for them
:: forall m a. (MonadIO m, MonadBaseControl IO m) | |
=> NarOptions | |
-> NarEffects m | Provide the effects set, usually |
-> NarParser m a | A parser to run, such as |
-> Handle | A handle the stream containg the NAR. It should already be
open and in |
-> FilePath | The root file system object to be created by the NAR |
-> m (Either String a) |
:: forall m. MonadIO m | |
=> ByteString | the string you want to dump |
-> NarSource m | The nar result in CPS style |
dumpString
dump a string to nar in CPS style. The function takes in a ByteString
,
and build a `NarSource m`.
:: forall m. MonadIO m | |
=> FilePath | path for the file you want to dump to nar |
-> NarSource m | the nar result in CPS style |
dumpPath shorthand build a Source that turn file path to nar using the default narEffectsIO.
Type
type NarSource m = (ByteString -> m ()) -> m () Source #
NarSource The source to provide nar to the handler `(ByteString -> m ())`. It is isomorphic to ByteString by Yoneda lemma if the result is meant to be m (). It is done in CPS style so IO can be chunks.