{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Foreign.Nix.Shellout
(
parseNixExpr, ParseError(..)
, instantiate, InstantiateError(..)
, eval
, realize, RealizeError(..)
, addToStore
, parseInstRealize
, NixError(..)
, StorePath(..), Derivation, Realized
, NixExpr
, runNixAction, NixAction(..), NixActionError(..)
) where
import Control.Error ( throwE, tryLast )
import Data.Text (stripPrefix, lines, isPrefixOf, Text)
import qualified Foreign.Nix.Shellout.Helpers as Helpers
import Foreign.Nix.Shellout.Types
( Realized,
Derivation,
StorePath(..),
NixActionError(..),
NixAction(..),
runNixAction )
import qualified Data.Text as Text
import System.Exit (ExitCode(ExitFailure, ExitSuccess))
import Data.Bifunctor (bimap, Bifunctor (first))
import Control.Monad ((>=>))
import qualified System.FilePath as FilePath
import Data.Function ((&))
import qualified Data.List as List
newtype NixExpr = NixExpr Text deriving (Int -> NixExpr -> ShowS
[NixExpr] -> ShowS
NixExpr -> String
(Int -> NixExpr -> ShowS)
-> (NixExpr -> String) -> ([NixExpr] -> ShowS) -> Show NixExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NixExpr] -> ShowS
$cshowList :: [NixExpr] -> ShowS
show :: NixExpr -> String
$cshow :: NixExpr -> String
showsPrec :: Int -> NixExpr -> ShowS
$cshowsPrec :: Int -> NixExpr -> ShowS
Show)
data ParseError
= SyntaxError Text
| UnknownParseError
deriving (Int -> ParseError -> ShowS
[ParseError] -> ShowS
ParseError -> String
(Int -> ParseError -> ShowS)
-> (ParseError -> String)
-> ([ParseError] -> ShowS)
-> Show ParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseError] -> ShowS
$cshowList :: [ParseError] -> ShowS
show :: ParseError -> String
$cshow :: ParseError -> String
showsPrec :: Int -> ParseError -> ShowS
$cshowsPrec :: Int -> ParseError -> ShowS
Show, ParseError -> ParseError -> Bool
(ParseError -> ParseError -> Bool)
-> (ParseError -> ParseError -> Bool) -> Eq ParseError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseError -> ParseError -> Bool
$c/= :: ParseError -> ParseError -> Bool
== :: ParseError -> ParseError -> Bool
$c== :: ParseError -> ParseError -> Bool
Eq)
parseNixExpr :: Text -> NixAction ParseError NixExpr
parseNixExpr :: Text -> NixAction ParseError NixExpr
parseNixExpr Text
e =
(Text -> ParseError)
-> (Text -> NixExpr)
-> NixAction Text Text
-> NixAction ParseError NixExpr
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> ParseError
parseParseError Text -> NixExpr
NixExpr
(NixAction Text Text -> NixAction ParseError NixExpr)
-> NixAction Text Text -> NixAction ParseError NixExpr
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> NixAction Text Text
evalNixOutput Text
"nix-instantiate" [ Text
"--parse", Text
"-E", Text
e ]
parseParseError :: Text -> ParseError
parseParseError :: Text -> ParseError
parseParseError
(Text -> Text -> Maybe Text
stripPrefix Text
"error: syntax error, "
-> Just Text
mes) = Text -> ParseError
SyntaxError (Text -> ParseError) -> Text -> ParseError
forall a b. (a -> b) -> a -> b
$ Text
mes
parseParseError Text
_ = ParseError
UnknownParseError
data InstantiateError
= NotADerivation
| UnknownInstantiateError
deriving (Int -> InstantiateError -> ShowS
[InstantiateError] -> ShowS
InstantiateError -> String
(Int -> InstantiateError -> ShowS)
-> (InstantiateError -> String)
-> ([InstantiateError] -> ShowS)
-> Show InstantiateError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstantiateError] -> ShowS
$cshowList :: [InstantiateError] -> ShowS
show :: InstantiateError -> String
$cshow :: InstantiateError -> String
showsPrec :: Int -> InstantiateError -> ShowS
$cshowsPrec :: Int -> InstantiateError -> ShowS
Show, InstantiateError -> InstantiateError -> Bool
(InstantiateError -> InstantiateError -> Bool)
-> (InstantiateError -> InstantiateError -> Bool)
-> Eq InstantiateError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstantiateError -> InstantiateError -> Bool
$c/= :: InstantiateError -> InstantiateError -> Bool
== :: InstantiateError -> InstantiateError -> Bool
$c== :: InstantiateError -> InstantiateError -> Bool
Eq)
instantiate :: NixExpr -> NixAction InstantiateError (StorePath Derivation)
instantiate :: NixExpr -> NixAction InstantiateError (StorePath Derivation)
instantiate (NixExpr Text
e) =
(Text -> InstantiateError)
-> NixAction Text (StorePath Derivation)
-> NixAction InstantiateError (StorePath Derivation)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> InstantiateError
parseInstantiateError
(NixAction Text (StorePath Derivation)
-> NixAction InstantiateError (StorePath Derivation))
-> NixAction Text (StorePath Derivation)
-> NixAction InstantiateError (StorePath Derivation)
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> NixAction Text Text
evalNixOutput Text
"nix-instantiate" [ Text
"-E", Text
e ]
NixAction Text Text
-> (Text -> NixAction Text (StorePath Derivation))
-> NixAction Text (StorePath Derivation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> StorePath Derivation)
-> Text -> NixAction Text (StorePath Derivation)
forall a. (String -> a) -> Text -> NixAction Text a
toNixFilePath String -> StorePath Derivation
forall a. String -> StorePath a
StorePath
eval :: NixExpr -> NixAction InstantiateError ()
eval :: NixExpr -> NixAction InstantiateError ()
eval (NixExpr Text
e) = do
Text
_instantiateOutput <- (Text -> InstantiateError)
-> NixAction Text Text -> NixAction InstantiateError Text
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> InstantiateError
parseInstantiateError
(NixAction Text Text -> NixAction InstantiateError Text)
-> NixAction Text Text -> NixAction InstantiateError Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> NixAction Text Text
evalNixOutput Text
"nix-instantiate" [ Text
"--eval", Text
"-E", Text
e ]
() -> NixAction InstantiateError ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
parseInstantiateError :: Text -> InstantiateError
parseInstantiateError :: Text -> InstantiateError
parseInstantiateError
(Text -> Text -> Maybe Text
stripPrefix Text
"error: expression does not evaluate to a derivation"
-> Just Text
_) = InstantiateError
NotADerivation
parseInstantiateError Text
_ = InstantiateError
UnknownInstantiateError
data RealizeError = UnknownRealizeError deriving (Int -> RealizeError -> ShowS
[RealizeError] -> ShowS
RealizeError -> String
(Int -> RealizeError -> ShowS)
-> (RealizeError -> String)
-> ([RealizeError] -> ShowS)
-> Show RealizeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RealizeError] -> ShowS
$cshowList :: [RealizeError] -> ShowS
show :: RealizeError -> String
$cshow :: RealizeError -> String
showsPrec :: Int -> RealizeError -> ShowS
$cshowsPrec :: Int -> RealizeError -> ShowS
Show, RealizeError -> RealizeError -> Bool
(RealizeError -> RealizeError -> Bool)
-> (RealizeError -> RealizeError -> Bool) -> Eq RealizeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RealizeError -> RealizeError -> Bool
$c/= :: RealizeError -> RealizeError -> Bool
== :: RealizeError -> RealizeError -> Bool
$c== :: RealizeError -> RealizeError -> Bool
Eq)
realize :: StorePath Derivation -> NixAction RealizeError (StorePath Realized)
realize :: StorePath Derivation -> NixAction RealizeError (StorePath Realized)
realize (StorePath String
d) =
[Text] -> NixAction RealizeError (StorePath Realized)
storeOp [ Text
"-r", String -> Text
Text.pack String
d ]
addToStore :: FilePath -> NixAction RealizeError (StorePath Realized)
addToStore :: String -> NixAction RealizeError (StorePath Realized)
addToStore String
fp = [Text] -> NixAction RealizeError (StorePath Realized)
storeOp [ Text
"--add", String -> Text
Text.pack String
fp ]
storeOp :: [Text] -> NixAction RealizeError (StorePath Realized)
storeOp :: [Text] -> NixAction RealizeError (StorePath Realized)
storeOp [Text]
op =
(Text -> RealizeError)
-> NixAction Text (StorePath Realized)
-> NixAction RealizeError (StorePath Realized)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (RealizeError -> Text -> RealizeError
forall a b. a -> b -> a
const RealizeError
UnknownRealizeError)
(NixAction Text (StorePath Realized)
-> NixAction RealizeError (StorePath Realized))
-> NixAction Text (StorePath Realized)
-> NixAction RealizeError (StorePath Realized)
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> NixAction Text Text
evalNixOutput Text
"nix-store" [Text]
op
NixAction Text Text
-> (Text -> NixAction Text (StorePath Realized))
-> NixAction Text (StorePath Realized)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (String -> StorePath Realized)
-> Text -> NixAction Text (StorePath Realized)
forall a. (String -> a) -> Text -> NixAction Text a
toNixFilePath String -> StorePath Realized
forall a. String -> StorePath a
StorePath
data NixError
= ParseError ParseError
| InstantiateError InstantiateError
| RealizeError RealizeError deriving (Int -> NixError -> ShowS
[NixError] -> ShowS
NixError -> String
(Int -> NixError -> ShowS)
-> (NixError -> String) -> ([NixError] -> ShowS) -> Show NixError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NixError] -> ShowS
$cshowList :: [NixError] -> ShowS
show :: NixError -> String
$cshow :: NixError -> String
showsPrec :: Int -> NixError -> ShowS
$cshowsPrec :: Int -> NixError -> ShowS
Show, NixError -> NixError -> Bool
(NixError -> NixError -> Bool)
-> (NixError -> NixError -> Bool) -> Eq NixError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NixError -> NixError -> Bool
$c/= :: NixError -> NixError -> Bool
== :: NixError -> NixError -> Bool
$c== :: NixError -> NixError -> Bool
Eq)
parseInstRealize :: Text -> NixAction NixError (StorePath Realized)
parseInstRealize :: Text -> NixAction NixError (StorePath Realized)
parseInstRealize = (ParseError -> NixError)
-> NixAction ParseError NixExpr -> NixAction NixError NixExpr
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ParseError -> NixError
ParseError (NixAction ParseError NixExpr -> NixAction NixError NixExpr)
-> (Text -> NixAction ParseError NixExpr)
-> Text
-> NixAction NixError NixExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> NixAction ParseError NixExpr
parseNixExpr
(Text -> NixAction NixError NixExpr)
-> (NixExpr -> NixAction NixError (StorePath Realized))
-> Text
-> NixAction NixError (StorePath Realized)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (InstantiateError -> NixError)
-> NixAction InstantiateError (StorePath Derivation)
-> NixAction NixError (StorePath Derivation)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first InstantiateError -> NixError
InstantiateError (NixAction InstantiateError (StorePath Derivation)
-> NixAction NixError (StorePath Derivation))
-> (NixExpr -> NixAction InstantiateError (StorePath Derivation))
-> NixExpr
-> NixAction NixError (StorePath Derivation)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NixExpr -> NixAction InstantiateError (StorePath Derivation)
instantiate
(NixExpr -> NixAction NixError (StorePath Derivation))
-> (StorePath Derivation
-> NixAction NixError (StorePath Realized))
-> NixExpr
-> NixAction NixError (StorePath Realized)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (RealizeError -> NixError)
-> NixAction RealizeError (StorePath Realized)
-> NixAction NixError (StorePath Realized)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first RealizeError -> NixError
RealizeError (NixAction RealizeError (StorePath Realized)
-> NixAction NixError (StorePath Realized))
-> (StorePath Derivation
-> NixAction RealizeError (StorePath Realized))
-> StorePath Derivation
-> NixAction NixError (StorePath Realized)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorePath Derivation -> NixAction RealizeError (StorePath Realized)
realize
evalNixOutput :: Text
-> [Text]
-> NixAction Text Text
evalNixOutput :: Text -> [Text] -> NixAction Text Text
evalNixOutput = ((Text, Text) -> ExitCode -> ExceptT Text IO Text)
-> Text -> [Text] -> NixAction Text Text
forall e a.
((Text, Text) -> ExitCode -> ExceptT e IO a)
-> Text -> [Text] -> NixAction e a
Helpers.readProcess (\(Text
out, Text
err) -> \case
ExitFailure Int
_ -> Text -> ExceptT Text IO Text
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (Text -> ExceptT Text IO Text) -> Text -> ExceptT Text IO Text
forall a b. (a -> b) -> a -> b
$
case
Text
err
Text -> (Text -> [Text]) -> [Text]
forall a b. a -> (a -> b) -> b
& Text -> [Text]
Text.lines
[Text] -> ([Text] -> [Text]) -> [Text]
forall a b. a -> (a -> b) -> b
& (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Bool
isPrefixOf Text
"error: ")
[Text] -> ([Text] -> [Text]) -> [Text]
forall a b. a -> (a -> b) -> b
& Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
List.intersperse Text
"\n"
[Text] -> ([Text] -> Text) -> Text
forall a b. a -> (a -> b) -> b
& [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat of
Text
"" -> Text
"nix didn’t output any error message"
Text
s -> Text
s
ExitCode
ExitSuccess -> Text -> [Text] -> ExceptT Text IO Text
forall (m :: * -> *) e a. Monad m => e -> [a] -> ExceptT e m a
tryLast
Text
"nix didn’t output a store path" (Text -> [Text]
Data.Text.lines Text
out))
toNixFilePath :: (String -> a) -> Text -> NixAction Text a
toNixFilePath :: (String -> a) -> Text -> NixAction Text a
toNixFilePath String -> a
a Text
p = ExceptT (NixActionError Text) IO a -> NixAction Text a
forall e a. ExceptT (NixActionError e) IO a -> NixAction e a
NixAction (ExceptT (NixActionError Text) IO a -> NixAction Text a)
-> ExceptT (NixActionError Text) IO a -> NixAction Text a
forall a b. (a -> b) -> a -> b
$
if String -> Bool
FilePath.isValid (Text -> String
Text.unpack Text
p) then a -> ExceptT (NixActionError Text) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> ExceptT (NixActionError Text) IO a)
-> a -> ExceptT (NixActionError Text) IO a
forall a b. (a -> b) -> a -> b
$ String -> a
a (Text -> String
Text.unpack Text
p)
else NixActionError Text -> ExceptT (NixActionError Text) IO a
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (NixActionError Text -> ExceptT (NixActionError Text) IO a)
-> NixActionError Text -> ExceptT (NixActionError Text) IO a
forall a b. (a -> b) -> a -> b
$ NixActionError :: forall e. Text -> e -> NixActionError e
NixActionError
{ actionStderr :: Text
actionStderr = Text
nostderr
, actionError :: Text
actionError = Text
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a filepath!" }
where nostderr :: Text
nostderr = Text
forall a. Monoid a => a
mempty