{-# LANGUAGE OverloadedStrings #-}

module System.Nix.Derivation
  ( parseDerivation
  , buildDerivation
  )
where

import           Data.Text                      ( Text )
import qualified Data.Text                     as Text
import qualified Data.Text.Lazy.Builder        as Text.Lazy
                                                ( Builder )
import qualified Data.Text.Lazy.Builder        as Text.Lazy.Builder
import qualified Data.Attoparsec.Text.Lazy     as Text.Lazy
                                                ( Parser )
import           Nix.Derivation                 ( Derivation )
import qualified Nix.Derivation                as Derivation
import           System.Nix.StorePath           ( StorePath )
import qualified System.Nix.StorePath          as StorePath



parseDerivation :: FilePath -> Text.Lazy.Parser (Derivation StorePath Text)
parseDerivation :: FilePath -> Parser (Derivation StorePath Text)
parseDerivation FilePath
expectedRoot =
  Parser StorePath
-> Parser Text -> Parser (Derivation StorePath Text)
forall fp txt.
(Ord fp, Ord txt) =>
Parser fp -> Parser txt -> Parser (Derivation fp txt)
Derivation.parseDerivationWith
    (Parser Text
"\"" Parser Text -> Parser StorePath -> Parser StorePath
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> FilePath -> Parser StorePath
StorePath.pathParser FilePath
expectedRoot Parser StorePath -> Parser Text -> Parser StorePath
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Text
"\"")
    Parser Text
Derivation.textParser

buildDerivation :: Derivation StorePath Text -> Text.Lazy.Builder
buildDerivation :: Derivation StorePath Text -> Builder
buildDerivation =
  (StorePath -> Builder)
-> (Text -> Builder) -> Derivation StorePath Text -> Builder
forall fp txt.
(fp -> Builder) -> (txt -> Builder) -> Derivation fp txt -> Builder
Derivation.buildDerivationWith
    (Text -> Builder
string (Text -> Builder) -> (StorePath -> Text) -> StorePath -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
Text.pack (FilePath -> Text) -> (StorePath -> FilePath) -> StorePath -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorePath -> FilePath
forall a. Show a => a -> FilePath
show)
    Text -> Builder
string
  where
    string :: Text -> Builder
string = Text -> Builder
Text.Lazy.Builder.fromText (Text -> Builder) -> (Text -> Text) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
Text.pack (FilePath -> Text) -> (Text -> FilePath) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
forall a. Show a => a -> FilePath
show