hnix-store-core-0.4.2.0: Core effects for interacting with the Nix store.
Safe HaskellNone
LanguageHaskell2010

System.Nix.Internal.Nar.Parser

Description

A streaming parser for the NAR format

Synopsis

Documentation

newtype NarParser m a Source #

NarParser is a monad for parsing a Nar file as a byte stream and reconstructing the file system objects inside See the definitions of NarEffects for a description of the actions the parser can take, and ParserState for the internals of the parser

Instances

Instances details
MonadTrans NarParser Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

lift :: Monad m => m a -> NarParser m a #

Monad m => MonadState ParserState (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Monad m => MonadError String (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

throwError :: String -> NarParser m a #

catchError :: NarParser m a -> (String -> NarParser m a) -> NarParser m a #

Monad m => Monad (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

(>>=) :: NarParser m a -> (a -> NarParser m b) -> NarParser m b #

(>>) :: NarParser m a -> NarParser m b -> NarParser m b #

return :: a -> NarParser m a #

Functor m => Functor (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

fmap :: (a -> b) -> NarParser m a -> NarParser m b #

(<$) :: a -> NarParser m b -> NarParser m a #

MonadFail m => MonadFail (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

fail :: String -> NarParser m a #

Monad m => Applicative (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

pure :: a -> NarParser m a #

(<*>) :: NarParser m (a -> b) -> NarParser m a -> NarParser m b #

liftA2 :: (a -> b -> c) -> NarParser m a -> NarParser m b -> NarParser m c #

(*>) :: NarParser m a -> NarParser m b -> NarParser m b #

(<*) :: NarParser m a -> NarParser m b -> NarParser m a #

MonadIO m => MonadIO (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

liftIO :: IO a -> NarParser m a #

Monad m => MonadReader (NarEffects m) (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Methods

ask :: NarParser m (NarEffects m) #

local :: (NarEffects m -> NarEffects m) -> NarParser m a -> NarParser m a #

reader :: (NarEffects m -> a) -> NarParser m a #

runParser Source #

Arguments

:: forall m a. (MonadIO m, MonadBaseControl IO m) 
=> NarEffects m

Provide the effects set, usually narEffectsIO

-> NarParser m a

A parser to run, such as parseNar

-> Handle

A handle the stream containg the NAR. It should already be open and in IO.ReadMode

-> 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

data ParserState Source #

Constructors

ParserState 

Fields

  • tokenStack :: ![Text]

    The parser can push tokens (words or punctuation) onto this stack. We use this for a very limited backtracking where the Nar format requires it

  • directoryStack :: ![String]

    The parser knows the name of the current FSO it's targeting, and the relative directory path leading there

  • handle :: Handle

    Handle of the input byte stream

  • links :: [LinkInfo]

    Unlike with files and directories, we collect symlinks from the NAR on

Instances

Instances details
Monad m => MonadState ParserState (NarParser m) Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

Parsers for NAR components

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 ()

parseSymlink :: (MonadIO m, MonadFail m) => NarParser m () Source #

Parse a symlink from a NAR, storing the link details in the parser state We remember links rather than immediately creating file system objects from them, because we might encounter a link in the NAR before we encountered its target, and in this case, creating the link will fail The final step of creating links is handle by createLinks

data LinkInfo Source #

Internal data type representing symlinks encountered in the NAR

Constructors

LinkInfo 

Fields

  • linkTarget :: String

    path to the symlink target, relative to the root of the unpacking NAR

  • linkFile :: String

    file name of the link being created

  • linkPWD :: String

    directory in which to create the link (relative to unpacking root)

Instances

Instances details
Show LinkInfo Source # 
Instance details

Defined in System.Nix.Internal.Nar.Parser

parseFile :: forall m. (MonadIO m, MonadFail m) => NarParser m () Source #

When the NAR includes a file, we read from the NAR handle in chunks and write the target in chunks. This lets us avoid reading the full contents of the encoded file into memory

parseDirectory :: (MonadIO m, MonadFail m) => NarParser m () Source #

Parse a NAR encoded directory, being careful not to hold onto file handles for target files longer than needed

Utility parsers

parseStr :: (MonadIO m, MonadFail m) => NarParser m Text Source #

Short strings guiding the NAR parsing are prefixed with their length, then encoded in ASCII, and padded to 8 bytes. parseStr captures this logic

parseLength :: (MonadIO m, MonadFail m) => NarParser m Int64 Source #

Get an Int64 describing the length of the upcoming string, according to NAR's encoding of ints

expectStr :: (MonadIO m, MonadFail m) => Text -> NarParser m () Source #

Consume a NAR string and assert that it matches an expectation

expectRawString :: (MonadIO m, MonadFail m) => ByteString -> NarParser m () Source #

Consume a raw string and assert that it equals some expectation. This is usually used when consuming padding 0's

matchStr Source #

Arguments

:: (MonadIO m, MonadFail m) 
=> [(Text, NarParser m a)]

List of expected possible strings and the parsers they should run

-> NarParser m a 

Consume a NAR string, and dispatch to a parser depending on which string matched

parens :: (MonadIO m, MonadFail m) => NarParser m a -> NarParser m a Source #

Wrap any parser in NAR formatted parentheses (a parenthesis is a NAR string, so it needs length encoding and padding)

createLinks :: MonadIO m => NarParser m () Source #

Sort links in the symlink stack according to their connectivity (Targets must be created before the links that target them)

State manipulation

consume :: (MonadIO m, MonadFail m) => Int -> NarParser m ByteString Source #

Pull n bytes from the underlying handle, failing if fewer bytes are available

popStr :: Monad m => NarParser m (Maybe Text) Source #

Pop a string off the token stack

pushStr :: Monad m => Text -> NarParser m () Source #

Push a string onto the token stack

pushFileName :: Monad m => FilePath -> NarParser m () Source #

Push a level onto the directory stack

popFileName :: Monad m => NarParser m () Source #

Go to the parent level in the directory stack

currentFile :: Monad m => NarParser m FilePath Source #

Convert the current directory stack into a filepath by interspersing the path components with "/"

pushLink :: Monad m => LinkInfo -> NarParser m () Source #

Add a link to the collection of encountered symlinks

Utilities

padLen :: Int -> Int Source #

Distance to the next multiple of 8