hnix/src/Nix/Fresh/Basic.hs
Guillaume Maudoux 4ded48a789 Add proper default 'nix' prefix to search paths
The search path of Nix contains by default the "nix" prefix that points
to $datadir/nix/corepkgs, where $datadir defaults to $prefix/lib at
installation time, but can be overriden by NIX_DATA_DIR.

We implemented it using `Paths.hnix.getDataDir` and `NIX_DATA_DIR` to
follow Nix behaviour as closely as possible.

A small discrepancy is that we do the lookup on each invocation, where
Nix caches the searchPath at context creation.
2019-11-26 14:32:29 -07:00

49 lines
1.6 KiB
Haskell

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Nix.Fresh.Basic where
import Control.Monad.Reader
import Nix.Effects
import Nix.Render
import Nix.Fresh
import Nix.Value
type StdIdT = FreshIdT Int
instance MonadFile m => MonadFile (StdIdT m)
instance MonadIntrospect m => MonadIntrospect (StdIdT m)
instance MonadStore m => MonadStore (StdIdT m) where
addPath' = lift . addPath'
toFile_' = (lift .) . toFile_'
instance MonadPutStr m => MonadPutStr (StdIdT m)
instance MonadHttp m => MonadHttp (StdIdT m)
instance MonadEnv m => MonadEnv (StdIdT m)
instance MonadPaths m => MonadPaths (StdIdT m)
instance MonadInstantiate m => MonadInstantiate (StdIdT m)
instance MonadExec m => MonadExec (StdIdT m)
instance (MonadEffects t f m, MonadDataContext f m)
=> MonadEffects t f (StdIdT m) where
makeAbsolutePath = lift . makeAbsolutePath @t @f @m
findEnvPath = lift . findEnvPath @t @f @m
findPath vs path = do
i <- FreshIdT ask
let vs' = map (unliftNValue (runFreshIdT i)) vs
lift $ findPath @t @f @m vs' path
importPath path = do
i <- FreshIdT ask
p <- lift $ importPath @t @f @m path
return $ liftNValue (runFreshIdT i) p
pathToDefaultNix = lift . pathToDefaultNix @t @f @m
derivationStrict v = do
i <- FreshIdT ask
p <- lift $ derivationStrict @t @f @m (unliftNValue (runFreshIdT i) v)
return $ liftNValue (runFreshIdT i) p
traceEffect = lift . traceEffect @t @f @m