module System.Nix.Derivation
( parseDerivation
, buildDerivation
, Derivation(..)
, DerivationOutput(..)
) where
import Data.Attoparsec.Text.Lazy (Parser)
import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder)
import Nix.Derivation (Derivation(..), DerivationOutput(..))
import System.Nix.StorePath (StoreDir, StorePath)
import qualified Data.Attoparsec.Text.Lazy
import qualified Data.Text
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Builder
import qualified Nix.Derivation
import qualified System.Nix.StorePath
parseDerivation :: StoreDir -> Parser (Derivation StorePath Text)
parseDerivation :: StoreDir -> Parser (Derivation StorePath Text)
parseDerivation StoreDir
expectedRoot =
Parser StorePath
-> Parser Text -> Parser (Derivation StorePath Text)
forall fp txt.
(Ord fp, Ord txt) =>
Parser fp -> Parser txt -> Parser (Derivation fp txt)
Nix.Derivation.parseDerivationWith
Parser StorePath
pathParser
Parser Text
Nix.Derivation.textParser
where
pathParser :: Parser StorePath
pathParser = do
Text
text <- Parser Text
Nix.Derivation.textParser
case Parser StorePath -> Text -> Either String StorePath
forall a. Parser a -> Text -> Either String a
Data.Attoparsec.Text.Lazy.parseOnly
(StoreDir -> Parser StorePath
System.Nix.StorePath.pathParser StoreDir
expectedRoot)
(Text -> Text
Data.Text.Lazy.fromStrict Text
text)
of
Right StorePath
p -> StorePath -> Parser StorePath
forall a. a -> Parser Text a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StorePath
p
Left String
e -> String -> Parser StorePath
forall a. String -> Parser Text a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
e
buildDerivation :: StoreDir -> Derivation StorePath Text -> Builder
buildDerivation :: StoreDir -> Derivation StorePath Text -> Builder
buildDerivation StoreDir
storeDir =
(StorePath -> Builder)
-> (Text -> Builder) -> Derivation StorePath Text -> Builder
forall fp txt.
(fp -> Builder) -> (txt -> Builder) -> Derivation fp txt -> Builder
Nix.Derivation.buildDerivationWith
(Text -> Builder
string (Text -> Builder) -> (StorePath -> Text) -> StorePath -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StoreDir -> StorePath -> Text
System.Nix.StorePath.storePathToText StoreDir
storeDir)
Text -> Builder
string
where
string :: Text -> Builder
string = Text -> Builder
Data.Text.Lazy.Builder.fromText (Text -> Builder) -> (Text -> Text) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
forall a. Show a => a -> String
show