{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -Wno-missing-signatures #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}

module Nix.Effects.Basic where

import           Control.Monad
import           Control.Monad.State.Strict
import           Data.HashMap.Lazy              ( HashMap )
import qualified Data.HashMap.Lazy             as M
import           Data.List
import           Data.List.Split
import           Data.Maybe                     ( maybeToList )
import           Data.Text                      ( Text )
import qualified Data.Text                     as Text
import           Data.Text.Prettyprint.Doc
import           Nix.Atoms
import           Nix.Convert
import           Nix.Effects
import           Nix.Exec                       ( MonadNix
                                                , callFunc
                                                , evalExprLoc
                                                , nixInstantiateExpr
                                                )
import           Nix.Expr
import           Nix.Frames
import           Nix.Normal
import           Nix.Parser
import           Nix.Pretty
import           Nix.Render
import           Nix.Scope
import           Nix.String
import           Nix.String.Coerce
import           Nix.Utils
import           Nix.Value
import           Nix.Value.Monad
import           System.FilePath

#ifdef MIN_VERSION_ghc_datasize
#if MIN_VERSION_ghc_datasize(0,2,0)
import           GHC.DataSize
#endif
#endif

defaultMakeAbsolutePath :: MonadNix e t f m => FilePath -> m FilePath
defaultMakeAbsolutePath :: FilePath -> m FilePath
defaultMakeAbsolutePath origPath :: FilePath
origPath = do
  FilePath
origPathExpanded <- FilePath -> m FilePath
forall (m :: * -> *). MonadFile m => FilePath -> m FilePath
expandHomePath FilePath
origPath
  FilePath
absPath          <- if FilePath -> Bool
isAbsolute FilePath
origPathExpanded
    then FilePath -> m FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
origPathExpanded
    else do
      FilePath
cwd <- do
        Maybe (Free (NValue' t f m) t)
mres <- Text -> m (Maybe (Free (NValue' t f m) t))
forall a (m :: * -> *). Scoped a m => Text -> m (Maybe a)
lookupVar "__cur_file"
        case Maybe (Free (NValue' t f m) t)
mres of
          Nothing -> m FilePath
forall (m :: * -> *). MonadFile m => m FilePath
getCurrentDirectory
          Just v :: Free (NValue' t f m) t
v  -> Free (NValue' t f m) t
-> (Free (NValue' t f m) t -> m FilePath) -> m FilePath
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand Free (NValue' t f m) t
v ((Free (NValue' t f m) t -> m FilePath) -> m FilePath)
-> (Free (NValue' t f m) t -> m FilePath) -> m FilePath
forall a b. (a -> b) -> a -> b
$ \case
            NVPath s :: FilePath
s -> FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> m FilePath) -> FilePath -> m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDirectory FilePath
s
            v :: Free (NValue' t f m) t
v ->
              ErrorCall -> m FilePath
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError
                (ErrorCall -> m FilePath) -> ErrorCall -> m FilePath
forall a b. (a -> b) -> a -> b
$  FilePath -> ErrorCall
ErrorCall
                (FilePath -> ErrorCall) -> FilePath -> ErrorCall
forall a b. (a -> b) -> a -> b
$  "when resolving relative path,"
                FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ " __cur_file is in scope,"
                FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ " but is not a path; it is: "
                FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Free (NValue' t f m) t -> FilePath
forall a. Show a => a -> FilePath
show Free (NValue' t f m) t
v
      pure $ FilePath
cwd FilePath -> FilePath -> FilePath
<///> FilePath
origPathExpanded
  FilePath -> FilePath
removeDotDotIndirections (FilePath -> FilePath) -> m FilePath -> m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m FilePath
forall (m :: * -> *). MonadFile m => FilePath -> m FilePath
canonicalizePath FilePath
absPath

expandHomePath :: MonadFile m => FilePath -> m FilePath
expandHomePath :: FilePath -> m FilePath
expandHomePath ('~' : xs :: FilePath
xs) = (FilePath -> FilePath -> FilePath)
-> FilePath -> FilePath -> FilePath
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
(++) FilePath
xs (FilePath -> FilePath) -> m FilePath -> m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m FilePath
forall (m :: * -> *). MonadFile m => m FilePath
getHomeDirectory
expandHomePath p :: FilePath
p          = FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
p

-- | Incorrectly normalize paths by rewriting patterns like @a/b/..@ to @a@.
--   This is incorrect on POSIX systems, because if @b@ is a symlink, its
--   parent may be a different directory from @a@. See the discussion at
--   https://hackage.haskell.org/package/directory-1.3.1.5/docs/System-Directory.html#v:canonicalizePath
removeDotDotIndirections :: FilePath -> FilePath
removeDotDotIndirections :: FilePath -> FilePath
removeDotDotIndirections = FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate "/" ([FilePath] -> FilePath)
-> (FilePath -> [FilePath]) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath] -> [FilePath]
forall a. (Eq a, IsString a) => [a] -> [a] -> [a]
go [] ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> [FilePath]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn "/"
 where
  go :: [a] -> [a] -> [a]
go s :: [a]
s       []            = [a] -> [a]
forall a. [a] -> [a]
reverse [a]
s
  go (_ : s :: [a]
s) (".." : rest :: [a]
rest) = [a] -> [a] -> [a]
go [a]
s [a]
rest
  go s :: [a]
s       (this :: a
this : rest :: [a]
rest) = [a] -> [a] -> [a]
go (a
this a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
s) [a]
rest

infixr 9 <///>
(<///>) :: FilePath -> FilePath -> FilePath
x :: FilePath
x <///> :: FilePath -> FilePath -> FilePath
<///> y :: FilePath
y | FilePath -> Bool
isAbsolute FilePath
y Bool -> Bool -> Bool
|| "." FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
y = FilePath
x FilePath -> FilePath -> FilePath
</> FilePath
y
          | Bool
otherwise                          = FilePath -> FilePath -> FilePath
joinByLargestOverlap FilePath
x FilePath
y
 where
  joinByLargestOverlap :: FilePath -> FilePath -> FilePath
joinByLargestOverlap (FilePath -> [FilePath]
splitDirectories -> [FilePath]
xs) (FilePath -> [FilePath]
splitDirectories -> [FilePath]
ys) =
    [FilePath] -> FilePath
joinPath ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ [[FilePath]] -> [FilePath]
forall a. [a] -> a
head
      [ [FilePath]
xs [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ Int -> [FilePath] -> [FilePath]
forall a. Int -> [a] -> [a]
drop ([FilePath] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FilePath]
tx) [FilePath]
ys | [FilePath]
tx <- [FilePath] -> [[FilePath]]
forall a. [a] -> [[a]]
tails [FilePath]
xs, [FilePath]
tx [FilePath] -> [[FilePath]] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath] -> [[FilePath]]
forall a. [a] -> [[a]]
inits [FilePath]
ys ]

defaultFindEnvPath :: MonadNix e t f m => String -> m FilePath
defaultFindEnvPath :: FilePath -> m FilePath
defaultFindEnvPath = FilePath -> m FilePath
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
FilePath -> m FilePath
findEnvPathM

findEnvPathM :: forall e t f m . MonadNix e t f m => FilePath -> m FilePath
findEnvPathM :: FilePath -> m FilePath
findEnvPathM name :: FilePath
name = do
  Maybe (NValue t f m)
mres <- Text -> m (Maybe (NValue t f m))
forall a (m :: * -> *). Scoped a m => Text -> m (Maybe a)
lookupVar "__nixPath"
  case Maybe (NValue t f m)
mres of
    Nothing -> FilePath -> m FilePath
forall a. HasCallStack => FilePath -> a
error "impossible"
    Just x :: NValue t f m
x  -> NValue t f m -> (NValue t f m -> m FilePath) -> m FilePath
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
x ((NValue t f m -> m FilePath) -> m FilePath)
-> (NValue t f m -> m FilePath) -> m FilePath
forall a b. (a -> b) -> a -> b
$ NValue t f m -> m [NValue t f m]
forall a (m :: * -> *) v. FromValue a m v => v -> m a
fromValue (NValue t f m -> m [NValue t f m])
-> ([NValue t f m] -> m FilePath) -> NValue t f m -> m FilePath
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \([NValue t f m]
l :: [NValue t f m]) ->
      (FilePath -> m (Maybe FilePath))
-> [NValue t f m] -> FilePath -> m FilePath
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
(FilePath -> m (Maybe FilePath))
-> [NValue t f m] -> FilePath -> m FilePath
findPathBy FilePath -> m (Maybe FilePath)
MonadEffects t f m => FilePath -> m (Maybe FilePath)
nixFilePath [NValue t f m]
l FilePath
name
 where
  nixFilePath :: MonadEffects t f m => FilePath -> m (Maybe FilePath)
  nixFilePath :: FilePath -> m (Maybe FilePath)
nixFilePath path :: FilePath
path = do
    FilePath
path   <- FilePath -> m FilePath
forall t (f :: * -> *) (m :: * -> *).
MonadEffects t f m =>
FilePath -> m FilePath
makeAbsolutePath @t @f FilePath
path
    Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). MonadFile m => FilePath -> m Bool
doesDirectoryExist FilePath
path
    FilePath
path'  <- if Bool
exists
      then forall t (f :: * -> *) (m :: * -> *).
MonadEffects t f m =>
FilePath -> m FilePath
forall (m :: * -> *). MonadEffects t f m => FilePath -> m FilePath
makeAbsolutePath @t @f (FilePath -> m FilePath) -> FilePath -> m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
path FilePath -> FilePath -> FilePath
</> "default.nix"
      else FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
path
    Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). MonadFile m => FilePath -> m Bool
doesFileExist FilePath
path'
    return $ if Bool
exists then FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path' else Maybe FilePath
forall a. Maybe a
Nothing

findPathBy
  :: forall e t f m
   . MonadNix e t f m
  => (FilePath -> m (Maybe FilePath))
  -> [NValue t f m]
  -> FilePath
  -> m FilePath
findPathBy :: (FilePath -> m (Maybe FilePath))
-> [NValue t f m] -> FilePath -> m FilePath
findPathBy finder :: FilePath -> m (Maybe FilePath)
finder l :: [NValue t f m]
l name :: FilePath
name = do
  Maybe FilePath
mpath <- (Maybe FilePath -> NValue t f m -> m (Maybe FilePath))
-> Maybe FilePath -> [NValue t f m] -> m (Maybe FilePath)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM Maybe FilePath -> NValue t f m -> m (Maybe FilePath)
go Maybe FilePath
forall a. Maybe a
Nothing [NValue t f m]
l
  case Maybe FilePath
mpath of
    Nothing ->
      ErrorCall -> m FilePath
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError
        (ErrorCall -> m FilePath) -> ErrorCall -> m FilePath
forall a b. (a -> b) -> a -> b
$  FilePath -> ErrorCall
ErrorCall
        (FilePath -> ErrorCall) -> FilePath -> ErrorCall
forall a b. (a -> b) -> a -> b
$  "file '"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ "' was not found in the Nix search path"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ " (add it's using $NIX_PATH or -I)"
    Just path :: FilePath
path -> FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
path
 where
  go :: Maybe FilePath -> NValue t f m -> m (Maybe FilePath)
  go :: Maybe FilePath -> NValue t f m -> m (Maybe FilePath)
go p :: Maybe FilePath
p@(Just _) _ = Maybe FilePath -> m (Maybe FilePath)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FilePath
p
  go Nothing l :: NValue t f m
l =
    NValue t f m
-> (NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
l ((NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath))
-> (NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ NValue t f m -> m (HashMap Text (NValue t f m))
forall a (m :: * -> *) v. FromValue a m v => v -> m a
fromValue (NValue t f m -> m (HashMap Text (NValue t f m)))
-> (HashMap Text (NValue t f m) -> m (Maybe FilePath))
-> NValue t f m
-> m (Maybe FilePath)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \(HashMap Text (NValue t f m)
s :: HashMap Text (NValue t f m)) -> do
      NValue t f m
p <- HashMap Text (NValue t f m) -> m (NValue t f m)
forall e (m :: * -> *) t (f :: * -> *) k.
(MonadReader e m, HasCitations1 m (NValue t f m) f,
 HasCitations m (NValue t f m) t, Traversable f, Comonad f,
 MonadThunk t m (NValue t f m), MonadEffects t f m, Alternative m,
 MonadCatch m, MonadFix m, Scoped (NValue t f m) m,
 MonadValue (NValue t f m) m, IsString k, Hashable k, Has e Frames,
 Has e SrcSpan, Has e Options, Applicative f, Eq k, Show t, Show k,
 Typeable f, Typeable m, Typeable t) =>
HashMap k (NValue t f m) -> m (NValue t f m)
resolvePath HashMap Text (NValue t f m)
s
      NValue t f m
-> (NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
p ((NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath))
-> (NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ NValue t f m -> m Path
forall a (m :: * -> *) v. FromValue a m v => v -> m a
fromValue (NValue t f m -> m Path)
-> (Path -> m (Maybe FilePath))
-> NValue t f m
-> m (Maybe FilePath)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \(Path path :: FilePath
path) -> case Text -> HashMap Text (NValue t f m) -> Maybe (NValue t f m)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup "prefix" HashMap Text (NValue t f m)
s of
        Nothing -> FilePath -> Maybe FilePath -> m (Maybe FilePath)
tryPath FilePath
path Maybe FilePath
forall a. Maybe a
Nothing
        Just pf :: NValue t f m
pf -> NValue t f m
-> (NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
pf ((NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath))
-> (NValue t f m -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ NValue t f m -> m (Maybe NixString)
forall a (m :: * -> *) v. FromValue a m v => v -> m (Maybe a)
fromValueMay (NValue t f m -> m (Maybe NixString))
-> (Maybe NixString -> m (Maybe FilePath))
-> NValue t f m
-> m (Maybe FilePath)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \case
          Just (NixString
nsPfx :: NixString) ->
            let pfx :: Text
pfx = NixString -> Text
hackyStringIgnoreContext NixString
nsPfx
            in  if Bool -> Bool
not (Text -> Bool
Text.null Text
pfx)
                  then FilePath -> Maybe FilePath -> m (Maybe FilePath)
tryPath FilePath
path (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (Text -> FilePath
Text.unpack Text
pfx))
                  else FilePath -> Maybe FilePath -> m (Maybe FilePath)
tryPath FilePath
path Maybe FilePath
forall a. Maybe a
Nothing
          _ -> FilePath -> Maybe FilePath -> m (Maybe FilePath)
tryPath FilePath
path Maybe FilePath
forall a. Maybe a
Nothing

  tryPath :: FilePath -> Maybe FilePath -> m (Maybe FilePath)
tryPath p :: FilePath
p (Just n :: FilePath
n) | n' :: FilePath
n' : ns :: [FilePath]
ns <- FilePath -> [FilePath]
splitDirectories FilePath
name, FilePath
n FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
n' =
    FilePath -> m (Maybe FilePath)
finder (FilePath -> m (Maybe FilePath)) -> FilePath -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath
p FilePath -> FilePath -> FilePath
<///> [FilePath] -> FilePath
joinPath [FilePath]
ns
  tryPath p :: FilePath
p _ = FilePath -> m (Maybe FilePath)
finder (FilePath -> m (Maybe FilePath)) -> FilePath -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath
p FilePath -> FilePath -> FilePath
<///> FilePath
name

  resolvePath :: HashMap k (NValue t f m) -> m (NValue t f m)
resolvePath s :: HashMap k (NValue t f m)
s = case k -> HashMap k (NValue t f m) -> Maybe (NValue t f m)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup "path" HashMap k (NValue t f m)
s of
    Just t :: NValue t f m
t  -> NValue t f m -> m (NValue t f m)
forall (m :: * -> *) a. Monad m => a -> m a
return NValue t f m
t
    Nothing -> case k -> HashMap k (NValue t f m) -> Maybe (NValue t f m)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup "uri" HashMap k (NValue t f m)
s of
      Just ut :: NValue t f m
ut -> m (NValue t f m) -> m (NValue t f m)
forall v (m :: * -> *). MonadValue v m => m v -> m v
defer (m (NValue t f m) -> m (NValue t f m))
-> m (NValue t f m) -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ NValue t f m -> m (NValue t f m)
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
NValue t f m -> m (NValue t f m)
fetchTarball NValue t f m
ut
      Nothing ->
        ErrorCall -> m (NValue t f m)
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError
          (ErrorCall -> m (NValue t f m)) -> ErrorCall -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$  FilePath -> ErrorCall
ErrorCall
          (FilePath -> ErrorCall) -> FilePath -> ErrorCall
forall a b. (a -> b) -> a -> b
$  "__nixPath must be a list of attr sets"
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ " with 'path' elements, but received: "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ HashMap k (NValue t f m) -> FilePath
forall a. Show a => a -> FilePath
show HashMap k (NValue t f m)
s

fetchTarball
  :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)
fetchTarball :: NValue t f m -> m (NValue t f m)
fetchTarball = (NValue t f m
 -> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m))
-> (NValue t f m -> m (NValue t f m))
-> NValue t f m
-> m (NValue t f m)
forall a b c. (a -> b -> c) -> b -> a -> c
flip NValue t f m
-> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand ((NValue t f m -> m (NValue t f m))
 -> NValue t f m -> m (NValue t f m))
-> (NValue t f m -> m (NValue t f m))
-> NValue t f m
-> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ \case
  NVSet s :: AttrSet (NValue t f m)
s _ -> case Text -> AttrSet (NValue t f m) -> Maybe (NValue t f m)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup "url" AttrSet (NValue t f m)
s of
    Nothing ->
      ErrorCall -> m (NValue t f m)
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError (ErrorCall -> m (NValue t f m)) -> ErrorCall -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ FilePath -> ErrorCall
ErrorCall "builtins.fetchTarball: Missing url attribute"
    Just url :: NValue t f m
url -> NValue t f m
-> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
url ((NValue t f m -> m (NValue t f m)) -> m (NValue t f m))
-> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ Maybe (NValue t f m) -> NValue t f m -> m (NValue t f m)
go (Text -> AttrSet (NValue t f m) -> Maybe (NValue t f m)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup "sha256" AttrSet (NValue t f m)
s)
  v :: NValue t f m
v@NVStr{} -> Maybe (NValue t f m) -> NValue t f m -> m (NValue t f m)
go Maybe (NValue t f m)
forall a. Maybe a
Nothing NValue t f m
v
  v :: NValue t f m
v ->
    ErrorCall -> m (NValue t f m)
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError
      (ErrorCall -> m (NValue t f m)) -> ErrorCall -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$  FilePath -> ErrorCall
ErrorCall
      (FilePath -> ErrorCall) -> FilePath -> ErrorCall
forall a b. (a -> b) -> a -> b
$  "builtins.fetchTarball: Expected URI or set, got "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ NValue t f m -> FilePath
forall a. Show a => a -> FilePath
show NValue t f m
v
 where
  go :: Maybe (NValue t f m) -> NValue t f m -> m (NValue t f m)
  go :: Maybe (NValue t f m) -> NValue t f m -> m (NValue t f m)
go msha :: Maybe (NValue t f m)
msha = \case
    NVStr ns :: NixString
ns -> Text -> Maybe (NValue t f m) -> m (NValue t f m)
fetch (NixString -> Text
hackyStringIgnoreContext NixString
ns) Maybe (NValue t f m)
msha
    v :: NValue t f m
v ->
      ErrorCall -> m (NValue t f m)
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError
        (ErrorCall -> m (NValue t f m)) -> ErrorCall -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$  FilePath -> ErrorCall
ErrorCall
        (FilePath -> ErrorCall) -> FilePath -> ErrorCall
forall a b. (a -> b) -> a -> b
$  "builtins.fetchTarball: Expected URI or string, got "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ NValue t f m -> FilePath
forall a. Show a => a -> FilePath
show NValue t f m
v

{- jww (2018-04-11): This should be written using pipes in another module
    fetch :: Text -> Maybe (NThunk m) -> m (NValue t f m)
    fetch uri msha = case takeExtension (Text.unpack uri) of
        ".tgz" -> undefined
        ".gz"  -> undefined
        ".bz2" -> undefined
        ".xz"  -> undefined
        ".tar" -> undefined
        ext -> throwError $ ErrorCall $ "builtins.fetchTarball: Unsupported extension '"
                  ++ ext ++ "'"
-}

  fetch :: Text -> Maybe (NValue t f m) -> m (NValue t f m)
  fetch :: Text -> Maybe (NValue t f m) -> m (NValue t f m)
fetch uri :: Text
uri Nothing =
    FilePath -> m (NValue t f m)
forall e t (f :: * -> *) (m :: * -> *).
(MonadNix e t f m, MonadInstantiate m) =>
FilePath -> m (NValue t f m)
nixInstantiateExpr (FilePath -> m (NValue t f m)) -> FilePath -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ "builtins.fetchTarball \"" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Text -> FilePath
Text.unpack Text
uri FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ "\""
  fetch url :: Text
url (Just t :: NValue t f m
t) = NValue t f m
-> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
t ((NValue t f m -> m (NValue t f m)) -> m (NValue t f m))
-> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ NValue t f m -> m NixString
forall a (m :: * -> *) v. FromValue a m v => v -> m a
fromValue (NValue t f m -> m NixString)
-> (NixString -> m (NValue t f m))
-> NValue t f m
-> m (NValue t f m)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \nsSha :: NixString
nsSha ->
    let sha :: Text
sha = NixString -> Text
hackyStringIgnoreContext NixString
nsSha
    in  FilePath -> m (NValue t f m)
forall e t (f :: * -> *) (m :: * -> *).
(MonadNix e t f m, MonadInstantiate m) =>
FilePath -> m (NValue t f m)
nixInstantiateExpr
          (FilePath -> m (NValue t f m)) -> FilePath -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$  "builtins.fetchTarball { "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ "url    = \""
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Text -> FilePath
Text.unpack Text
url
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ "\"; "
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ "sha256 = \""
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Text -> FilePath
Text.unpack Text
sha
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ "\"; }"

defaultFindPath :: MonadNix e t f m => [NValue t f m] -> FilePath -> m FilePath
defaultFindPath :: [NValue t f m] -> FilePath -> m FilePath
defaultFindPath = [NValue t f m] -> FilePath -> m FilePath
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
[NValue t f m] -> FilePath -> m FilePath
findPathM

findPathM
  :: forall e t f m
   . MonadNix e t f m
  => [NValue t f m]
  -> FilePath
  -> m FilePath
findPathM :: [NValue t f m] -> FilePath -> m FilePath
findPathM = (FilePath -> m (Maybe FilePath))
-> [NValue t f m] -> FilePath -> m FilePath
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
(FilePath -> m (Maybe FilePath))
-> [NValue t f m] -> FilePath -> m FilePath
findPathBy FilePath -> m (Maybe FilePath)
MonadEffects t f m => FilePath -> m (Maybe FilePath)
path
 where
  path :: MonadEffects t f m => FilePath -> m (Maybe FilePath)
  path :: FilePath -> m (Maybe FilePath)
path path :: FilePath
path = do
    FilePath
path   <- FilePath -> m FilePath
forall t (f :: * -> *) (m :: * -> *).
MonadEffects t f m =>
FilePath -> m FilePath
makeAbsolutePath @t @f FilePath
path
    Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). MonadFile m => FilePath -> m Bool
doesPathExist FilePath
path
    return $ if Bool
exists then FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path else Maybe FilePath
forall a. Maybe a
Nothing

defaultImportPath
  :: (MonadNix e t f m, MonadState (HashMap FilePath NExprLoc) m)
  => FilePath
  -> m (NValue t f m)
defaultImportPath :: FilePath -> m (NValue t f m)
defaultImportPath path :: FilePath
path = do
  FilePath -> m ()
forall (m :: * -> *). Monad m => FilePath -> m ()
traceM (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ "Importing file " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
path
  NixLevel -> ErrorCall -> m (NValue t f m) -> m (NValue t f m)
forall s e (m :: * -> *) a.
(Framed e m, Exception s) =>
NixLevel -> s -> m a -> m a
withFrame NixLevel
Info (FilePath -> ErrorCall
ErrorCall (FilePath -> ErrorCall) -> FilePath -> ErrorCall
forall a b. (a -> b) -> a -> b
$ "While importing file " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
path) (m (NValue t f m) -> m (NValue t f m))
-> m (NValue t f m) -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ do
    HashMap FilePath NExprLoc
imports <- m (HashMap FilePath NExprLoc)
forall s (m :: * -> *). MonadState s m => m s
get
    NExprLoc -> m (NValue t f m)
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
NExprLoc -> m (NValue t f m)
evalExprLoc (NExprLoc -> m (NValue t f m)) -> m NExprLoc -> m (NValue t f m)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< case FilePath -> HashMap FilePath NExprLoc -> Maybe NExprLoc
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup FilePath
path HashMap FilePath NExprLoc
imports of
      Just expr :: NExprLoc
expr -> NExprLoc -> m NExprLoc
forall (f :: * -> *) a. Applicative f => a -> f a
pure NExprLoc
expr
      Nothing   -> do
        Result NExprLoc
eres <- FilePath -> m (Result NExprLoc)
forall (m :: * -> *).
MonadFile m =>
FilePath -> m (Result NExprLoc)
parseNixFileLoc FilePath
path
        case Result NExprLoc
eres of
          Failure err :: Doc Void
err ->
            ErrorCall -> m NExprLoc
forall s e (m :: * -> *) a.
(Framed e m, Exception s, MonadThrow m) =>
s -> m a
throwError
              (ErrorCall -> m NExprLoc) -> ErrorCall -> m NExprLoc
forall a b. (a -> b) -> a -> b
$ FilePath -> ErrorCall
ErrorCall
              (FilePath -> ErrorCall)
-> (Doc Void -> FilePath) -> Doc Void -> ErrorCall
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Void -> FilePath
forall a. Show a => a -> FilePath
show (Doc Void -> ErrorCall) -> Doc Void -> ErrorCall
forall a b. (a -> b) -> a -> b
$ [Doc Void] -> Doc Void
forall ann. [Doc ann] -> Doc ann
fillSep ["Parse during import failed:", Doc Void
err]
          Success expr :: NExprLoc
expr -> do
            (HashMap FilePath NExprLoc -> HashMap FilePath NExprLoc) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (FilePath
-> NExprLoc
-> HashMap FilePath NExprLoc
-> HashMap FilePath NExprLoc
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
M.insert FilePath
path NExprLoc
expr)
            pure NExprLoc
expr

defaultPathToDefaultNix :: MonadNix e t f m => FilePath -> m FilePath
defaultPathToDefaultNix :: FilePath -> m FilePath
defaultPathToDefaultNix = FilePath -> m FilePath
forall (m :: * -> *). MonadFile m => FilePath -> m FilePath
pathToDefaultNixFile

-- Given a path, determine the nix file to load
pathToDefaultNixFile :: MonadFile m => FilePath -> m FilePath
pathToDefaultNixFile :: FilePath -> m FilePath
pathToDefaultNixFile p :: FilePath
p = do
  Bool
isDir <- FilePath -> m Bool
forall (m :: * -> *). MonadFile m => FilePath -> m Bool
doesDirectoryExist FilePath
p
  pure $ if Bool
isDir then FilePath
p FilePath -> FilePath -> FilePath
</> "default.nix" else FilePath
p

defaultDerivationStrict
  :: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)
defaultDerivationStrict :: NValue t f m -> m (NValue t f m)
defaultDerivationStrict = forall a (m :: * -> *) v. FromValue a m v => v -> m a
forall (m :: * -> *) v.
FromValue (AttrSet (NValue t f m)) m v =>
v -> m (AttrSet (NValue t f m))
fromValue @(AttrSet (NValue t f m)) (NValue t f m -> m (AttrSet (NValue t f m)))
-> (AttrSet (NValue t f m) -> m (NValue t f m))
-> NValue t f m
-> m (NValue t f m)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \s :: AttrSet (NValue t f m)
s -> do
  Bool
nn <- m Bool
-> (NValue t f m -> m Bool) -> Maybe (NValue t f m) -> m Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False) (NValue t f m -> (NValue t f m -> m Bool) -> m Bool
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand (NValue t f m -> (NValue t f m -> m Bool) -> m Bool)
-> (NValue t f m -> m Bool) -> NValue t f m -> m Bool
forall (f :: * -> *) a b. Functor f => f (a -> b) -> a -> f b
?? NValue t f m -> m Bool
forall a (m :: * -> *) v. FromValue a m v => v -> m a
fromValue) (Text -> AttrSet (NValue t f m) -> Maybe (NValue t f m)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
M.lookup "__ignoreNulls" AttrSet (NValue t f m)
s)
  AttrSet (NValue t f m)
s' <- [(Text, NValue t f m)] -> AttrSet (NValue t f m)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
M.fromList ([(Text, NValue t f m)] -> AttrSet (NValue t f m))
-> m [(Text, NValue t f m)] -> m (AttrSet (NValue t f m))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text, NValue t f m) -> m (Maybe (Text, NValue t f m)))
-> [(Text, NValue t f m)] -> m [(Text, NValue t f m)]
forall a b. (a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM (Bool -> (Text, NValue t f m) -> m (Maybe (Text, NValue t f m))
handleEntry Bool
nn) (AttrSet (NValue t f m) -> [(Text, NValue t f m)]
forall k v. HashMap k v -> [(k, v)]
M.toList AttrSet (NValue t f m)
s)
  NValue t f m
v' <- NValue t f m -> m (NValue t f m)
forall e (m :: * -> *) t (f :: * -> *).
(Framed e m, MonadThunk t m (NValue t f m),
 MonadDataErrorContext t f m, HasCitations m (NValue t f m) t,
 HasCitations1 m (NValue t f m) f, Ord (ThunkId m)) =>
NValue t f m -> m (NValue t f m)
normalForm (NValue t f m -> m (NValue t f m))
-> m (NValue t f m) -> m (NValue t f m)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< AttrSet (NValue t f m) -> m (NValue t f m)
forall a (m :: * -> *) v. ToValue a m v => a -> m v
toValue @(AttrSet (NValue t f m)) @_ @(NValue t f m) AttrSet (NValue t f m)
s'
  FilePath -> m (NValue t f m)
forall e t (f :: * -> *) (m :: * -> *).
(MonadNix e t f m, MonadInstantiate m) =>
FilePath -> m (NValue t f m)
nixInstantiateExpr (FilePath -> m (NValue t f m)) -> FilePath -> m (NValue t f m)
forall a b. (a -> b) -> a -> b
$ "derivationStrict " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Doc Any -> FilePath
forall a. Show a => a -> FilePath
show (NValue t f m -> Doc Any
forall t (f :: * -> *) (m :: * -> *) ann.
MonadDataContext f m =>
NValue t f m -> Doc ann
prettyNValue NValue t f m
v')
 where
  mapMaybeM :: (a -> m (Maybe b)) -> [a] -> m [b]
  mapMaybeM :: (a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM op :: a -> m (Maybe b)
op = (a -> m [b] -> m [b]) -> m [b] -> [a] -> m [b]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> m [b] -> m [b]
f ([b] -> m [b]
forall (m :: * -> *) a. Monad m => a -> m a
return [])
    where f :: a -> m [b] -> m [b]
f x :: a
x xs :: m [b]
xs = a -> m (Maybe b)
op a
x m (Maybe b) -> (Maybe b -> m [b]) -> m [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (([b] -> [b]) -> m [b] -> m [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m [b]
xs) (([b] -> [b]) -> m [b])
-> (Maybe b -> [b] -> [b]) -> Maybe b -> m [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [b] -> [b] -> [b]
forall a. [a] -> [a] -> [a]
(++) ([b] -> [b] -> [b]) -> (Maybe b -> [b]) -> Maybe b -> [b] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe b -> [b]
forall a. Maybe a -> [a]
maybeToList

  handleEntry :: Bool -> (Text, NValue t f m) -> m (Maybe (Text, NValue t f m))
  handleEntry :: Bool -> (Text, NValue t f m) -> m (Maybe (Text, NValue t f m))
handleEntry ignoreNulls :: Bool
ignoreNulls (k :: Text
k, v :: NValue t f m
v) = (NValue t f m -> (Text, NValue t f m))
-> Maybe (NValue t f m) -> Maybe (Text, NValue t f m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text
k, ) (Maybe (NValue t f m) -> Maybe (Text, NValue t f m))
-> m (Maybe (NValue t f m)) -> m (Maybe (Text, NValue t f m))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case Text
k of
      -- The `args' attribute is special: it supplies the command-line
      -- arguments to the builder.
      -- TODO This use of coerceToString is probably not right and may
      -- not have the right arguments.
    "args"          -> NValue t f m
-> (NValue t f m -> m (Maybe (NValue t f m)))
-> m (Maybe (NValue t f m))
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
v ((NValue t f m -> m (Maybe (NValue t f m)))
 -> m (Maybe (NValue t f m)))
-> (NValue t f m -> m (Maybe (NValue t f m)))
-> m (Maybe (NValue t f m))
forall a b. (a -> b) -> a -> b
$ (NValue t f m -> Maybe (NValue t f m))
-> m (NValue t f m) -> m (Maybe (NValue t f m))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NValue t f m -> Maybe (NValue t f m)
forall a. a -> Maybe a
Just (m (NValue t f m) -> m (Maybe (NValue t f m)))
-> (NValue t f m -> m (NValue t f m))
-> NValue t f m
-> m (Maybe (NValue t f m))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NValue t f m -> m (NValue t f m)
coerceNixList
    "__ignoreNulls" -> Maybe (NValue t f m) -> m (Maybe (NValue t f m))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (NValue t f m)
forall a. Maybe a
Nothing
    _               -> NValue t f m
-> (NValue t f m -> m (Maybe (NValue t f m)))
-> m (Maybe (NValue t f m))
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
demand NValue t f m
v ((NValue t f m -> m (Maybe (NValue t f m)))
 -> m (Maybe (NValue t f m)))
-> (NValue t f m -> m (Maybe (NValue t f m)))
-> m (Maybe (NValue t f m))
forall a b. (a -> b) -> a -> b
$ \case
      NVConstant NNull | Bool
ignoreNulls -> Maybe (NValue t f m) -> m (Maybe (NValue t f m))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (NValue t f m)
forall a. Maybe a
Nothing
      v' :: NValue t f m
v'                             -> NValue t f m -> Maybe (NValue t f m)
forall a. a -> Maybe a
Just (NValue t f m -> Maybe (NValue t f m))
-> m (NValue t f m) -> m (Maybe (NValue t f m))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NValue t f m -> m (NValue t f m)
coerceNix NValue t f m
v'
   where
    coerceNix :: NValue t f m -> m (NValue t f m)
    coerceNix :: NValue t f m -> m (NValue t f m)
coerceNix = NixString -> m (NValue t f m)
forall a (m :: * -> *) v. ToValue a m v => a -> m v
toValue (NixString -> m (NValue t f m))
-> (NValue t f m -> m NixString)
-> NValue t f m
-> m (NValue t f m)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (NValue t f m -> NValue t f m -> m (NValue t f m))
-> CopyToStoreMode -> CoercionLevel -> NValue t f m -> m NixString
forall e (m :: * -> *) t (f :: * -> *).
(Framed e m, MonadStore m, MonadThrow m,
 MonadDataErrorContext t f m, MonadValue (NValue t f m) m) =>
(NValue t f m -> NValue t f m -> m (NValue t f m))
-> CopyToStoreMode -> CoercionLevel -> NValue t f m -> m NixString
coerceToString NValue t f m -> NValue t f m -> m (NValue t f m)
forall e t (f :: * -> *) (m :: * -> *).
MonadNix e t f m =>
NValue t f m -> NValue t f m -> m (NValue t f m)
callFunc CopyToStoreMode
CopyToStore CoercionLevel
CoerceAny

    coerceNixList :: NValue t f m -> m (NValue t f m)
    coerceNixList :: NValue t f m -> m (NValue t f m)
coerceNixList v :: NValue t f m
v = do
      [NValue t f m]
xs <- NValue t f m -> m [NValue t f m]
forall a (m :: * -> *) v. FromValue a m v => v -> m a
fromValue @[NValue t f m] NValue t f m
v
      [NValue t f m]
ys <- (NValue t f m -> m (NValue t f m))
-> [NValue t f m] -> m [NValue t f m]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (NValue t f m
-> (NValue t f m -> m (NValue t f m)) -> m (NValue t f m)
forall v (m :: * -> *) r. MonadValue v m => v -> (v -> m r) -> m r
`demand` NValue t f m -> m (NValue t f m)
coerceNix) [NValue t f m]
xs
      [NValue t f m] -> m (NValue t f m)
forall a (m :: * -> *) v. ToValue a m v => a -> m v
toValue @[NValue t f m] [NValue t f m]
ys

defaultTraceEffect :: MonadPutStr m => String -> m ()
defaultTraceEffect :: FilePath -> m ()
defaultTraceEffect = FilePath -> m ()
forall (m :: * -> *). MonadPutStr m => FilePath -> m ()
Nix.Effects.putStrLn