hnix/src/Nix/Builtins.hs

961 lines
38 KiB
Haskell
Raw Normal View History

{-# LANGUAGE AllowAmbiguousTypes #-}
2018-04-07 21:02:50 +02:00
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PartialTypeSignatures #-}
2018-04-07 21:02:50 +02:00
{-# LANGUAGE ScopedTypeVariables #-}
2018-04-08 00:34:54 +02:00
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
2018-04-07 21:02:50 +02:00
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Nix.Builtins (builtins) where
2018-04-07 21:02:50 +02:00
import Control.Monad
2018-04-07 23:33:15 +02:00
import Control.Monad.Catch
2018-04-07 21:02:50 +02:00
import Control.Monad.ListM (sortByM)
2018-05-03 06:32:00 +02:00
import Control.Monad.Reader (asks)
2018-04-07 21:02:50 +02:00
import qualified Crypto.Hash.MD5 as MD5
import qualified Crypto.Hash.SHA1 as SHA1
import qualified Crypto.Hash.SHA256 as SHA256
import qualified Crypto.Hash.SHA512 as SHA512
import qualified Data.Aeson as A
import qualified Data.Aeson.Encoding as A
import Data.Align (alignWith)
import Data.Array
import Data.ByteString (ByteString)
2018-04-08 09:26:48 +02:00
import qualified Data.ByteString as B
2018-04-07 21:02:50 +02:00
import Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Lazy as LBS
import Data.Char (isDigit)
import Data.Coerce
import Data.Fix
import Data.Foldable (foldrM)
2018-04-07 21:02:50 +02:00
import qualified Data.HashMap.Lazy as M
import Data.List
import Data.Maybe
import Data.Semigroup
import Data.Set (Set)
import qualified Data.Set as S
2018-04-07 21:02:50 +02:00
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Text.Encoding
import qualified Data.Text.Lazy as LazyText
import qualified Data.Text.Lazy.Builder as Builder
import Data.These (fromThese)
2018-05-03 06:32:00 +02:00
import qualified Data.Time.Clock.POSIX as Time
2018-04-07 21:02:50 +02:00
import Data.Traversable (mapM)
2018-04-08 00:34:54 +02:00
import Language.Haskell.TH.Syntax (addDependentFile, runIO)
2018-04-07 21:02:50 +02:00
import Nix.Atoms
import Nix.Convert
import Nix.Effects
import qualified Nix.Eval as Eval
2018-04-09 09:52:10 +02:00
import Nix.Exec
2018-04-07 21:02:50 +02:00
import Nix.Expr.Types
import Nix.Expr.Types.Annotated
import Nix.Frames
import Nix.Normal
2018-05-03 06:32:00 +02:00
import Nix.Options
2018-04-08 00:34:54 +02:00
import Nix.Parser
import Nix.Render
2018-04-07 21:02:50 +02:00
import Nix.Scope
import Nix.Thunk
import Nix.Utils
import Nix.Value
import Nix.XML
import System.FilePath
import System.Posix.Files
import Text.Regex.TDFA
builtins :: (MonadNix e m, Scoped e (NThunk m) m)
=> m (Scopes m (NThunk m))
builtins = do
ref <- thunk $ flip nvSet M.empty <$> buildMap
lst <- ([("builtins", ref)] ++) <$> topLevelBuiltins
2018-04-07 21:02:50 +02:00
pushScope (M.fromList lst) currentScopes
where
2018-04-28 22:49:34 +02:00
buildMap = M.fromList . map mapping <$> builtinsList
topLevelBuiltins = map mapping <$> fullBuiltinsList
fullBuiltinsList = map go <$> builtinsList
where
go b@(Builtin TopLevel _) = b
go (Builtin Normal (name, builtin)) =
Builtin TopLevel ("__" <> name, builtin)
2018-04-07 21:02:50 +02:00
data BuiltinType = Normal | TopLevel
data Builtin m = Builtin
{ _kind :: BuiltinType
2018-04-07 21:02:50 +02:00
, mapping :: (Text, NThunk m)
}
valueThunk :: forall e m. MonadNix e m => NValue m -> NThunk m
2018-04-09 09:52:10 +02:00
valueThunk = value @_ @_ @m
force' :: forall e m. MonadNix e m => NThunk m -> m (NValue m)
force' = force ?? pure
builtinsList :: forall e m. MonadNix e m => m [ Builtin m ]
2018-04-07 21:02:50 +02:00
builtinsList = sequence [
do version <- toValue ("2.0" :: Text)
pure $ Builtin Normal ("nixVersion", version)
2018-04-07 21:02:50 +02:00
, do version <- toValue (5 :: Int)
pure $ Builtin Normal ("langVersion", version)
, add0 Normal "nixPath" nixPath
2018-04-07 21:02:50 +02:00
, add TopLevel "abort" throw_ -- for now
, add2 Normal "add" add_
2018-04-22 19:48:55 +02:00
, add2 Normal "all" all_
, add2 Normal "any" any_
, add Normal "attrNames" attrNames
, add Normal "attrValues" attrValues
2018-04-22 19:48:55 +02:00
, add TopLevel "baseNameOf" baseNameOf
2018-04-07 21:02:50 +02:00
, add2 Normal "catAttrs" catAttrs
2018-04-22 19:48:55 +02:00
, add2 Normal "compareVersions" compareVersions_
, add Normal "concatLists" concatLists
, add' Normal "concatStringsSep" (arity2 Text.intercalate)
2018-04-22 19:48:55 +02:00
, add0 Normal "currentSystem" currentSystem
2018-05-03 06:32:00 +02:00
, add0 Normal "currentTime" currentTime_
2018-04-07 21:02:50 +02:00
, add2 Normal "deepSeq" deepSeq
2018-04-22 19:48:55 +02:00
, add0 TopLevel "derivation" $(do
let f = "data/nix/corepkgs/derivation.nix"
addDependentFile f
Success expr <- runIO $ parseNixFile f
[| cata Eval.eval expr |]
)
, add TopLevel "derivationStrict" derivationStrict_
, add TopLevel "dirOf" dirOf
2018-04-29 00:01:12 +02:00
, add2 Normal "div" div_
2018-04-07 21:02:50 +02:00
, add2 Normal "elem" elem_
, add2 Normal "elemAt" elemAt_
2018-04-29 01:37:01 +02:00
, add Normal "exec" exec_
, add0 Normal "false" (return $ nvConstant $ NBool False)
2018-04-22 19:48:55 +02:00
, add Normal "fetchTarball" fetchTarball
Implement builtins.fetchurl Squashed commit of the following: commit 15b10d898e0457237f07cda9e5e9525bac0e95f6 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:33:30 2018 -0700 Update Exec.hs commit d4a886dccf2715f1c1790e01adc242c352e7f427 Merge: 02afb27 4caacc1 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:55 2018 -0700 Merge branch 'master' into http commit 02afb275f2078c1184a901da3ea0262630fefeea Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:42 2018 -0700 Update Exec.hs commit 3733ce5888adb7161d2f57a16204ab953e9c4d7d Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:07:08 2018 -0700 Update Builtins.hs commit 4402be6d04ac34156d50f8ee29f9af300de75ce5 Merge: 2c60097 13f3ebd Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 15:06:28 2018 -0700 Merge branch 'master' into http commit 2c600976bb3a5d9267a0f313487dd0ab1a6ce1f7 Merge: 4a9d1a5 555ce95 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:25:59 2018 -0700 Merge branch 'master' into http commit 4a9d1a56d463567ad155a58fc39f5b24e2636120 Merge: 4dd46f2 431006f Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:20:57 2018 -0700 Merge branch 'master' into http commit 4dd46f21e3f594c4f7ae5bee8412a7841e566d4c Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sun Apr 29 12:51:11 2018 -0700 generated hnix.cabal commit c87ae993fb7dbb1117f03133862799e1549c4259 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:55:11 2018 -0700 remove dep from hnix.cabal commit 0bb8856c8759ad3c67a0b4eb1d26b6195da82667 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:53:54 2018 -0700 remove http-client stuff from default.nix commit d298756a2ba4376f8cb3c54fb723a00697e0821d Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:49:59 2018 -0700 getURL is implemented for both http and https commit a3d66c07a097aedb03f30bcc636fcb3d5717e1fe Merge: c4cb48a a73eae5 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:14:32 2018 -0700 Merge branch 'builtin2' into http commit c4cb48a8a756e82fb7d389ff501b2a85001dba38 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:13:25 2018 -0700 add getURL function commit ff23fc18ed16075353a58725d7d08f41605a6070 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:06:40 2018 -0700 use http-client-* instead of HTTP commit fcbe40f3bea84607a9d7849a9f3d2fc3a6cb9bef Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:58:07 2018 -0700 add HTTP commit a73eae573a193dbb8361e03b584a6cd55e7c427a Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:36:24 2018 -0700 implement fetchurl (as a copy of fetchTarball)
2018-05-03 06:38:13 +02:00
, add Normal "fetchurl" fetchurl
2018-04-07 21:02:50 +02:00
, add2 Normal "filter" filter_
2018-04-22 19:48:55 +02:00
, add3 Normal "foldl'" foldl'_
, add Normal "fromJSON" fromJSON
, add Normal "functionArgs" functionArgs
, add2 Normal "genList" genList
, add Normal "genericClosure" genericClosure
2018-04-22 19:48:55 +02:00
, add2 Normal "getAttr" getAttr
, add Normal "getEnv" getEnv_
, add2 Normal "hasAttr" hasAttr
2018-04-29 07:18:46 +02:00
, add Normal "hasContext" hasContext
2018-04-22 19:48:55 +02:00
, add' Normal "hashString" hashString
, add Normal "head" head_
, add TopLevel "import" import_
, add2 Normal "intersectAttrs" intersectAttrs
2018-04-07 21:02:50 +02:00
, add Normal "isAttrs" isAttrs
2018-04-22 19:48:55 +02:00
, add Normal "isBool" isBool
, add Normal "isFloat" isFloat
2018-04-07 21:02:50 +02:00
, add Normal "isFunction" isFunction
, add Normal "isInt" isInt
2018-04-22 19:48:55 +02:00
, add Normal "isList" isList
, add TopLevel "isNull" isNull
, add Normal "isString" isString
, add Normal "length" length_
2018-04-07 21:02:50 +02:00
, add2 Normal "lessThan" lessThan
, add Normal "listToAttrs" listToAttrs
2018-04-22 19:48:55 +02:00
, add2 TopLevel "map" map_
, add2 Normal "match" match_
2018-04-29 20:43:06 +02:00
, add2 Normal "mul" mul_
, add0 Normal "null" (return $ nvConstant NNull)
2018-04-22 19:48:55 +02:00
, add Normal "parseDrvName" parseDrvName
2018-04-07 21:02:50 +02:00
, add2 Normal "partition" partition_
2018-04-22 19:48:55 +02:00
, add Normal "pathExists" pathExists_
, add TopLevel "placeholder" placeHolder
2018-04-22 19:48:55 +02:00
, add Normal "readDir" readDir_
, add Normal "readFile" readFile_
, add2 TopLevel "removeAttrs" removeAttrs
, add3 Normal "replaceStrings" replaceStrings
, add2 TopLevel "scopedImport" scopedImport
, add2 Normal "seq" seq_
, add2 Normal "sort" sort_
, add2 Normal "split" split_
, add Normal "splitVersion" splitVersion_
2018-04-29 00:28:57 +02:00
, add0 Normal "storeDir" (return $ nvPath "/nix/store")
2018-04-22 19:48:55 +02:00
, add' Normal "stringLength" (arity1 Text.length)
, add' Normal "sub" (arity2 ((-) @Integer))
, add' Normal "substring" substring
, add Normal "tail" tail_
, add0 Normal "true" (return $ nvConstant $ NBool True)
2018-04-22 19:48:55 +02:00
, add TopLevel "throw" throw_
2018-04-09 09:52:10 +02:00
, add' Normal "toJSON"
(arity1 $ decodeUtf8 . LBS.toStrict . A.encodingToLazyByteString
. toEncodingSorted)
2018-04-22 19:48:55 +02:00
, add Normal "toPath" toPath
, add TopLevel "toString" toString
, add Normal "toXML" toXML_
2018-04-29 01:37:01 +02:00
, add2 TopLevel "trace" trace_
2018-04-22 19:48:55 +02:00
, add Normal "tryEval" tryEval
, add Normal "typeOf" typeOf
, add Normal "unsafeDiscardStringContext" unsafeDiscardStringContext
, add2 Normal "unsafeGetAttrPos" unsafeGetAttrPos
2018-04-29 03:29:25 +02:00
, add Normal "valueSize" getRecursiveSize
2018-04-07 21:02:50 +02:00
]
where
wrap t n f = Builtin t (n, f)
arity1 f = Prim . pure . f
arity2 f = ((Prim . pure) .) . f
mkThunk n = thunk . withFrame Info
(ErrorCall $ "While calling builtin " ++ Text.unpack n ++ "\n")
add0 t n v = wrap t n <$> mkThunk n v
add t n v = wrap t n <$> mkThunk n (builtin (Text.unpack n) v)
add2 t n v = wrap t n <$> mkThunk n (builtin2 (Text.unpack n) v)
add3 t n v = wrap t n <$> mkThunk n (builtin3 (Text.unpack n) v)
2018-04-07 21:02:50 +02:00
add' :: ToBuiltin m a => BuiltinType -> Text -> a -> m (Builtin m)
add' t n v = wrap t n <$> mkThunk n (toBuiltin (Text.unpack n) v)
2018-04-07 21:02:50 +02:00
-- Primops
foldNixPath :: forall e m r. MonadNix e m
=> (FilePath -> Maybe String -> r -> m r) -> r -> m r
foldNixPath f z = do
mres <- lookupVar @_ @(NThunk m) "__includes"
dirs <- case mres of
Nothing -> return []
Just v -> fromNix @[Text] v
menv <- getEnvVar "NIX_PATH"
foldrM go z $ dirs ++ case menv of
Nothing -> []
Just str -> Text.splitOn ":" (Text.pack str)
where
go x rest = case Text.splitOn "=" x of
[p] -> f (Text.unpack p) Nothing rest
[n, p] -> f (Text.unpack p) (Just (Text.unpack n)) rest
_ -> throwError $ ErrorCall $ "Unexpected entry in NIX_PATH: " ++ show x
nixPath :: MonadNix e m => m (NValue m)
nixPath = fmap nvList $ flip foldNixPath [] $ \p mn rest ->
pure $ valueThunk
(flip nvSet mempty $ M.fromList
[ ("path", valueThunk $ nvPath p)
, ("prefix", valueThunk $
nvStr (Text.pack (fromMaybe "" mn)) mempty) ]) : rest
toString :: MonadNix e m => m (NValue m) -> m (NValue m)
2018-04-18 06:53:07 +02:00
toString str =
str >>= normalForm >>= valueText False >>= toNix @(Text, DList Text)
2018-04-07 21:02:50 +02:00
hasAttr :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
hasAttr x y =
fromValue @Text x >>= \key ->
fromValue @(AttrSet (NThunk m), AttrSet SourcePos) y >>= \(aset, _) ->
toNix $ M.member key aset
2018-04-07 21:02:50 +02:00
attrsetGet :: MonadNix e m => Text -> AttrSet t -> m t
attrsetGet k s = case M.lookup k s of
Just v -> pure v
Nothing ->
throwError $ ErrorCall $ "Attribute '" ++ Text.unpack k ++ "' required"
2018-04-29 07:18:46 +02:00
hasContext :: MonadNix e m => m (NValue m) -> m (NValue m)
hasContext =
toNix . not . null . (appEndo ?? []) . snd <=< fromValue @(Text, DList Text)
getAttr :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
getAttr x y = x >>= \x' -> y >>= \y' -> case (x', y') of
(NVStr key _, NVSet aset _) -> attrsetGet key aset >>= force'
(x, y) -> throwError $ ErrorCall $ "Invalid types for builtin.getAttr: "
++ show (x, y)
2018-04-07 21:02:50 +02:00
unsafeGetAttrPos :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
unsafeGetAttrPos x y = x >>= \x' -> y >>= \y' -> case (x', y') of
2018-04-07 21:02:50 +02:00
(NVStr key _, NVSet _ apos) -> case M.lookup key apos of
Nothing -> pure $ nvConstant NNull
Just delta -> toValue delta
(x, y) -> throwError $ ErrorCall $ "Invalid types for builtin.unsafeGetAttrPos: "
++ show (x, y)
2018-04-07 21:02:50 +02:00
-- This function is a bit special in that it doesn't care about the contents
-- of the list.
length_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
length_ = toValue . (length :: [NThunk m] -> Int) <=< fromValue
2018-04-07 21:02:50 +02:00
add_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
add_ x y = x >>= \x' -> y >>= \y' -> case (x', y') of
(NVConstant (NInt x), NVConstant (NInt y)) ->
toNix ( x + y :: Integer)
(NVConstant (NFloat x), NVConstant (NInt y)) -> toNix (x + fromInteger y)
(NVConstant (NInt x), NVConstant (NFloat y)) -> toNix (fromInteger x + y)
(NVConstant (NFloat x), NVConstant (NFloat y)) -> toNix (x + y)
(_, _) ->
throwError $ Addition x' y'
2018-04-29 20:43:06 +02:00
mul_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
mul_ x y = x >>= \x' -> y >>= \y' -> case (x', y') of
(NVConstant (NInt x), NVConstant (NInt y)) ->
toNix ( x * y :: Integer)
(NVConstant (NFloat x), NVConstant (NInt y)) -> toNix (x * fromInteger y)
(NVConstant (NInt x), NVConstant (NFloat y)) -> toNix (fromInteger x * y)
(NVConstant (NFloat x), NVConstant (NFloat y)) -> toNix (x * y)
(_, _) ->
throwError $ Multiplication x' y'
2018-04-29 00:01:12 +02:00
div_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
div_ x y = x >>= \x' -> y >>= \y' -> case (x', y') of
(NVConstant (NInt x), NVConstant (NInt y)) ->
toNix (floor (fromInteger x / fromInteger y :: Double) :: Integer)
(NVConstant (NFloat x), NVConstant (NInt y)) -> toNix (x / fromInteger y)
(NVConstant (NInt x), NVConstant (NFloat y)) -> toNix (fromInteger x / y)
(NVConstant (NFloat x), NVConstant (NFloat y)) -> toNix (x / y)
(_, _) ->
throwError $ Division x' y'
2018-04-07 21:02:50 +02:00
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
anyM _ [] = return False
anyM p (x:xs) = do
q <- p x
if q then return True
else anyM p xs
any_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
any_ fun xs = fun >>= \f ->
toNix <=< anyM fromValue <=< mapM ((f `callFunc`) . force')
<=< fromValue $ xs
2018-04-07 21:02:50 +02:00
allM :: Monad m => (a -> m Bool) -> [a] -> m Bool
allM _ [] = return True
allM p (x:xs) = do
q <- p x
if q then allM p xs
else return False
all_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
all_ fun xs = fun >>= \f ->
toNix <=< allM fromValue <=< mapM ((f `callFunc`) . force')
<=< fromValue $ xs
2018-04-07 21:02:50 +02:00
foldl'_ :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m) -> m (NValue m)
foldl'_ fun z xs =
fun >>= \f -> fromValue @[NThunk m] xs >>= foldl' (go f) z
where
2018-04-25 10:10:15 +02:00
go f b a = f `callFunc` b >>= (`callFunc` force' a)
2018-04-07 21:02:50 +02:00
head_ :: MonadNix e m => m (NValue m) -> m (NValue m)
head_ = fromValue >=> \case
[] -> throwError $ ErrorCall "builtins.head: empty list"
h:_ -> force' h
2018-04-07 21:02:50 +02:00
tail_ :: MonadNix e m => m (NValue m) -> m (NValue m)
tail_ = fromValue >=> \case
[] -> throwError $ ErrorCall "builtins.tail: empty list"
_:t -> return $ nvList t
2018-04-07 21:02:50 +02:00
data VersionComponent
= VersionComponent_Pre -- ^ The string "pre"
| VersionComponent_String Text -- ^ A string other than "pre"
| VersionComponent_Number Integer -- ^ A number
deriving (Show, Read, Eq, Ord)
versionComponentToString :: VersionComponent -> Text
versionComponentToString = \case
VersionComponent_Pre -> "pre"
VersionComponent_String s -> s
VersionComponent_Number n -> Text.pack $ show n
-- | Based on https://github.com/NixOS/nix/blob/4ee4fda521137fed6af0446948b3877e0c5db803/src/libexpr/names.cc#L44
versionComponentSeparators :: String
versionComponentSeparators = ".-"
splitVersion :: Text -> [VersionComponent]
splitVersion s = case Text.uncons s of
Nothing -> []
Just (h, t)
| h `elem` versionComponentSeparators -> splitVersion t
| isDigit h ->
let (digits, rest) = Text.span isDigit s
in VersionComponent_Number (read $ Text.unpack digits) : splitVersion rest
| otherwise ->
let (chars, rest) = Text.span (\c -> not $ isDigit c || c `elem` versionComponentSeparators) s
thisComponent = case chars of
"pre" -> VersionComponent_Pre
x -> VersionComponent_String x
in thisComponent : splitVersion rest
splitVersion_ :: MonadNix e m => m (NValue m) -> m (NValue m)
splitVersion_ = fromValue >=> \s -> do
let vals = flip map (splitVersion s) $ \c ->
valueThunk $ nvStr (versionComponentToString c) mempty
return $ nvList vals
2018-04-07 21:02:50 +02:00
compareVersions :: Text -> Text -> Ordering
compareVersions s1 s2 =
mconcat $ alignWith f (splitVersion s1) (splitVersion s2)
where
z = VersionComponent_String ""
f = uncurry compare . fromThese z z
compareVersions_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
compareVersions_ t1 t2 =
fromValue t1 >>= \s1 ->
fromValue t2 >>= \s2 ->
return $ nvConstant $ NInt $ case compareVersions s1 s2 of
2018-04-07 21:02:50 +02:00
LT -> -1
EQ -> 0
GT -> 1
splitDrvName :: Text -> (Text, Text)
splitDrvName s =
let sep = "-"
pieces = Text.splitOn sep s
isFirstVersionPiece p = case Text.uncons p of
Just (h, _) | isDigit h -> True
_ -> False
-- Like 'break', but always puts the first item into the first result
-- list
breakAfterFirstItem :: (a -> Bool) -> [a] -> ([a], [a])
breakAfterFirstItem f = \case
h : t ->
let (a, b) = break f t
in (h : a, b)
[] -> ([], [])
(namePieces, versionPieces) =
breakAfterFirstItem isFirstVersionPiece pieces
in (Text.intercalate sep namePieces, Text.intercalate sep versionPieces)
parseDrvName :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
parseDrvName = fromValue >=> \(s :: Text) -> do
let (name :: Text, version :: Text) = splitDrvName s
-- jww (2018-04-15): There should be an easier way to write this.
(toValue =<<) $ sequence $ M.fromList
[ ("name" :: Text, thunk (toValue @_ @_ @(NValue m) name))
, ("version", thunk (toValue version)) ]
2018-04-07 21:02:50 +02:00
match_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
match_ pat str =
fromValue pat >>= \p ->
fromValue str >>= \s -> do
let re = makeRegex (encodeUtf8 p) :: Regex
case matchOnceText re (encodeUtf8 s) of
Just ("", sarr, "") -> do
let s = map fst (elems sarr)
nvList <$> traverse (toValue . decodeUtf8)
(if length s > 1 then tail s else s)
_ -> pure $ nvConstant NNull
split_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
split_ pat str =
fromValue pat >>= \p ->
fromValue str >>= \s -> do
let re = makeRegex (encodeUtf8 p) :: Regex
haystack = encodeUtf8 s
return $ nvList $
splitMatches 0 (map elems $ matchAllText re haystack) haystack
2018-04-08 09:26:48 +02:00
splitMatches
:: forall e m. MonadNix e m
2018-04-08 09:26:48 +02:00
=> Int
-> [[(ByteString, (Int, Int))]]
-> ByteString
-> [NThunk m]
splitMatches _ [] haystack = [thunkStr haystack]
splitMatches _ ([]:_) _ = error "Error in splitMatches: this should never happen!"
splitMatches numDropped (((_,(start,len)):captures):mts) haystack =
2018-04-11 08:06:47 +02:00
thunkStr before : caps : splitMatches (numDropped + relStart + len) mts (B.drop len rest)
2018-04-08 09:26:48 +02:00
where
2018-04-11 08:06:47 +02:00
relStart = max 0 start - numDropped
(before,rest) = B.splitAt relStart haystack
caps = valueThunk $ nvList (map f captures)
f (a,(s,_)) = if s < 0 then valueThunk (nvConstant NNull) else thunkStr a
2018-04-08 09:26:48 +02:00
thunkStr s = valueThunk (nvStr (decodeUtf8 s) mempty)
2018-04-08 09:26:48 +02:00
substring :: MonadNix e m => Int -> Int -> Text -> Prim m Text
2018-04-07 23:33:15 +02:00
substring start len str = Prim $
2018-04-07 21:02:50 +02:00
if start < 0 --NOTE: negative values of 'len' are OK
then throwError $ ErrorCall $ "builtins.substring: negative start position: " ++ show start
2018-04-07 23:33:15 +02:00
else pure $ Text.take len $ Text.drop start str
2018-04-07 21:02:50 +02:00
attrNames :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
attrNames = fromValue @(ValueSet m) >=> toNix . sort . M.keys
2018-04-07 21:02:50 +02:00
attrValues :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
attrValues = fromValue @(ValueSet m) >=>
toValue . fmap snd . sortOn (fst @Text @(NThunk m)) . M.toList
2018-04-07 21:02:50 +02:00
map_ :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
map_ fun xs = fun >>= \f ->
toNix <=< traverse (thunk . withFrame Debug
(ErrorCall "While applying f in map:\n")
. (f `callFunc`) . force')
<=< fromValue @[NThunk m] $ xs
2018-04-07 21:02:50 +02:00
filter_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
filter_ fun xs = fun >>= \f ->
toNix <=< filterM (fromValue <=< callFunc f . force')
<=< fromValue @[NThunk m] $ xs
2018-04-07 21:02:50 +02:00
catAttrs :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
catAttrs attrName xs =
fromValue @Text attrName >>= \n ->
fromValue @[NThunk m] xs >>= \l ->
fmap (nvList . catMaybes) $
forM l $ fmap (M.lookup n) . fromValue
2018-04-07 21:02:50 +02:00
baseNameOf :: MonadNix e m => m (NValue m) -> m (NValue m)
baseNameOf x = x >>= \case
NVStr path ctx -> pure $ nvStr (Text.pack $ takeFileName $ Text.unpack path) ctx
NVPath path -> pure $ nvPath $ takeFileName path
v -> throwError $ ErrorCall $ "dirOf: expected string or path, got " ++ show v
2018-04-07 21:02:50 +02:00
dirOf :: MonadNix e m => m (NValue m) -> m (NValue m)
dirOf x = x >>= \case
NVStr path ctx -> pure $ nvStr (Text.pack $ takeDirectory $ Text.unpack path) ctx
NVPath path -> pure $ nvPath $ takeDirectory path
v -> throwError $ ErrorCall $ "dirOf: expected string or path, got " ++ show v
2018-04-07 21:02:50 +02:00
2018-04-28 22:49:22 +02:00
-- jww (2018-04-28): This should only be a string argument, and not coerced?
unsafeDiscardStringContext :: MonadNix e m => m (NValue m) -> m (NValue m)
unsafeDiscardStringContext = fromValue @Text >=> toNix
2018-04-07 21:02:50 +02:00
seq_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
seq_ a b = a >> b
2018-04-07 21:02:50 +02:00
deepSeq :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
2018-04-07 21:02:50 +02:00
deepSeq a b = do
-- We evaluate 'a' only for its effects, so data cycles are ignored.
_ <- normalFormBy (forceEffects . coerce . _baseThunk) 0 =<< a
2018-04-07 21:02:50 +02:00
-- Then we evaluate the other argument to deepseq, thus this function
-- should always produce a result (unlike applying 'deepseq' on infinitely
-- recursive data structures in Haskell).
b
2018-04-07 21:02:50 +02:00
elem_ :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
elem_ x xs = x >>= \x' ->
toValue <=< anyM (valueEq x' <=< force') <=< fromValue @[NThunk m] $ xs
elemAt :: [a] -> Int -> Maybe a
elemAt ls i = case drop i ls of
[] -> Nothing
a:_ -> Just a
2018-04-07 21:02:50 +02:00
elemAt_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
elemAt_ xs n = fromValue n >>= \n' -> fromValue xs >>= \xs' ->
case elemAt xs' n' of
Just a -> force' a
Nothing -> throwError $ ErrorCall $ "builtins.elem: Index " ++ show n'
++ " too large for list of length " ++ show (length xs')
2018-04-07 21:02:50 +02:00
genList :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
genList generator = fromValue @Integer >=> \n ->
if n >= 0
then generator >>= \f ->
toNix =<< forM [0 .. n - 1] (\i -> thunk $ f `callFunc` toNix i)
else throwError $ ErrorCall $ "builtins.genList: Expected a non-negative number, got "
++ show n
2018-04-07 21:02:50 +02:00
genericClosure :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
genericClosure = fromValue @(AttrSet (NThunk m)) >=> \s ->
case (M.lookup "startSet" s, M.lookup "operator" s) of
(Nothing, Nothing) ->
throwError $ ErrorCall $
"builtins.genericClosure: "
++ "Attributes 'startSet' and 'operator' required"
(Nothing, Just _) ->
throwError $ ErrorCall $
"builtins.genericClosure: Attribute 'startSet' required"
(Just _, Nothing) ->
throwError $ ErrorCall $
"builtins.genericClosure: Attribute 'operator' required"
(Just startSet, Just operator) ->
fromValue @[NThunk m] startSet >>= \ss ->
force operator $ \op ->
toValue @[NThunk m] =<< snd <$> go op ss S.empty
where
go :: NValue m -> [NThunk m] -> Set (NValue m)
-> m (Set (NValue m), [NThunk m])
go _ [] ks = pure (ks, [])
go op (t:ts) ks =
force t $ \v -> fromValue @(AttrSet (NThunk m)) t >>= \s ->
case M.lookup "key" s of
Nothing ->
throwError $ ErrorCall $
"builtins.genericClosure: Attribute 'key' required"
Just k -> force k $ \k' ->
if S.member k' ks
then go op ts ks
else do
ys <- fromValue @[NThunk m] =<< (op `callFunc` pure v)
case S.toList ks of
[] -> checkComparable k' k'
j:_ -> checkComparable k' j
fmap (t:) <$> go op (ts ++ ys) (S.insert k' ks)
replaceStrings :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m) -> m (NValue m)
replaceStrings tfrom tto ts =
fromNix tfrom >>= \(from :: [Text]) ->
fromNix tto >>= \(to :: [Text]) ->
fromValue ts >>= \(s :: Text) -> do
when (length from /= length to) $
throwError $ ErrorCall $
"'from' and 'to' arguments to 'replaceStrings'"
++ " have different lengths"
let lookupPrefix s = do
(prefix, replacement) <-
find ((`Text.isPrefixOf` s) . fst) $ zip from to
let rest = Text.drop (Text.length prefix) s
return (prefix, replacement, rest)
finish = LazyText.toStrict . Builder.toLazyText
go orig result = case lookupPrefix orig of
Nothing -> case Text.uncons orig of
Nothing -> finish result
Just (h, t) -> go t $ result <> Builder.singleton h
Just (prefix, replacement, rest) -> case prefix of
"" -> case Text.uncons rest of
Nothing -> finish $ result <> Builder.fromText replacement
Just (h, t) -> go t $ mconcat
[ result
, Builder.fromText replacement
, Builder.singleton h
]
_ -> go rest $ result <> Builder.fromText replacement
2018-04-16 07:01:01 +02:00
toNix $ go s mempty
2018-04-07 21:02:50 +02:00
removeAttrs :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
removeAttrs set = fromNix >=> \(toRemove :: [Text]) ->
fromValue @(AttrSet (NThunk m),
AttrSet SourcePos) set >>= \(m, p) ->
toNix (go m toRemove, go p toRemove)
2018-04-07 21:02:50 +02:00
where
go = foldl' (flip M.delete)
intersectAttrs :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
intersectAttrs set1 set2 =
fromValue @(AttrSet (NThunk m),
AttrSet SourcePos) set1 >>= \(s1, p1) ->
fromValue @(AttrSet (NThunk m),
AttrSet SourcePos) set2 >>= \(s2, p2) ->
return $ nvSet (s2 `M.intersection` s1) (p2 `M.intersection` p1)
functionArgs :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
functionArgs fun = fun >>= \case
NVClosure p _ -> toValue @(AttrSet (NThunk m)) $
valueThunk . nvConstant . NBool <$>
case p of
Param name -> M.singleton name False
ParamSet s _ _ -> isJust <$> M.fromList s
v -> throwError $ ErrorCall $
"builtins.functionArgs: expected function, got " ++ show v
2018-04-07 21:02:50 +02:00
toPath :: MonadNix e m => m (NValue m) -> m (NValue m)
toPath = fromValue @Path >=> toNix @Path
2018-04-07 21:02:50 +02:00
pathExists_ :: MonadNix e m => m (NValue m) -> m (NValue m)
pathExists_ path = path >>= \case
NVPath p -> toNix =<< pathExists p
NVStr s _ -> toNix =<< pathExists (Text.unpack s)
v -> throwError $ ErrorCall $
"builtins.pathExists: expected path, got " ++ show v
2018-04-07 21:02:50 +02:00
hasKind :: forall a e m. (MonadNix e m, FromValue a m (NValue m))
=> m (NValue m) -> m (NValue m)
hasKind = fromValueMay >=> toNix . \case Just (_ :: a) -> True; _ -> False
2018-04-07 21:02:50 +02:00
isAttrs :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isAttrs = hasKind @(ValueSet m)
2018-04-07 21:02:50 +02:00
isList :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isList = hasKind @[NThunk m]
2018-04-07 21:02:50 +02:00
isString :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isString = hasKind @Text
2018-04-07 21:02:50 +02:00
isInt :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isInt = hasKind @Int
2018-04-07 21:02:50 +02:00
isFloat :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isFloat = hasKind @Float
2018-04-07 21:02:50 +02:00
isBool :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isBool = hasKind @Bool
isNull :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
isNull = hasKind @()
2018-04-07 21:02:50 +02:00
isFunction :: MonadNix e m => m (NValue m) -> m (NValue m)
isFunction func = func >>= \case
NVClosure {} -> toValue True
_ -> toValue False
2018-04-07 21:02:50 +02:00
throw_ :: MonadNix e m => m (NValue m) -> m (NValue m)
throw_ = fromValue >=> throwError . ErrorCall . Text.unpack
2018-04-07 21:02:50 +02:00
import_ :: MonadNix e m => m (NValue m) -> m (NValue m)
import_ = fromValue >=> importPath M.empty . getPath
2018-04-07 21:02:50 +02:00
scopedImport :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
scopedImport aset path =
fromValue aset >>= \s ->
fromValue path >>= \p -> importPath @m s (getPath p)
2018-04-07 21:02:50 +02:00
getEnv_ :: MonadNix e m => m (NValue m) -> m (NValue m)
getEnv_ = fromValue >=> \s -> do
mres <- getEnvVar (Text.unpack s)
toNix $ case mres of
Nothing -> ""
Just v -> Text.pack v
2018-04-07 21:02:50 +02:00
sort_ :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
sort_ comparator xs = comparator >>= \comp ->
fromValue xs >>= sortByM (cmp comp) >>= toValue
where
cmp f a b = do
isLessThan <- f `callFunc` force' a >>= (`callFunc` force' b)
fromValue isLessThan >>= \case
True -> pure LT
False -> do
isGreaterThan <- f `callFunc` force' b >>= (`callFunc` force' a)
fromValue isGreaterThan <&> \case
True -> GT
False -> EQ
lessThan :: MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
lessThan ta tb = ta >>= \va -> tb >>= \vb -> do
let badType = throwError $ ErrorCall $
"builtins.lessThan: expected two numbers or two strings, "
++ "got " ++ show va ++ " and " ++ show vb
nvConstant . NBool <$> case (va, vb) of
2018-04-07 21:02:50 +02:00
(NVConstant ca, NVConstant cb) -> case (ca, cb) of
(NInt a, NInt b) -> pure $ a < b
(NFloat a, NInt b) -> pure $ a < fromInteger b
(NInt a, NFloat b) -> pure $ fromInteger a < b
(NFloat a, NFloat b) -> pure $ a < b
_ -> badType
(NVStr a _, NVStr b _) -> pure $ a < b
_ -> badType
concatLists :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
concatLists = fromValue @[NThunk m]
>=> mapM (fromValue @[NThunk m] >=> pure)
>=> toValue . concat
listToAttrs :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
listToAttrs = fromValue @[NThunk m] >=> \l ->
fmap (flip nvSet M.empty . M.fromList . reverse) $
forM l $ fromValue @(AttrSet (NThunk m)) >=> \s -> do
name <- attrsetGet "name" s
val <- attrsetGet "value" s
fromValue name <&> (, val)
2018-04-07 21:02:50 +02:00
hashString :: MonadNix e m => Text -> Text -> Prim m Text
2018-04-07 21:02:50 +02:00
hashString algo s = Prim $ do
hash <- case algo of
"md5" -> pure MD5.hash
"sha1" -> pure SHA1.hash
2018-04-07 21:02:50 +02:00
"sha256" -> pure SHA256.hash
"sha512" -> pure SHA512.hash
_ -> throwError $ ErrorCall $ "builtins.hashString: "
2018-04-07 21:02:50 +02:00
++ "expected \"md5\", \"sha1\", \"sha256\", or \"sha512\", got " ++ show algo
pure $ decodeUtf8 $ Base16.encode $ hash $ encodeUtf8 s
placeHolder :: MonadNix e m => m (NValue m) -> m (NValue m)
2018-04-29 07:18:46 +02:00
placeHolder = fromValue @Text >=> \_ -> do
h <- runPrim (hashString "sha256" "fdasdfas")
toNix h
2018-04-29 00:35:01 +02:00
absolutePathFromValue :: MonadNix e m => NValue m -> m FilePath
2018-04-07 21:02:50 +02:00
absolutePathFromValue = \case
NVStr pathText _ -> do
let path = Text.unpack pathText
unless (isAbsolute path) $
throwError $ ErrorCall $ "string " ++ show path ++ " doesn't represent an absolute path"
2018-04-07 21:02:50 +02:00
pure path
NVPath path -> pure path
v -> throwError $ ErrorCall $ "expected a path, got " ++ show v
2018-04-07 21:02:50 +02:00
readFile_ :: MonadNix e m => m (NValue m) -> m (NValue m)
readFile_ path =
path >>= absolutePathFromValue >>= Nix.Render.readFile >>= toNix
2018-04-07 21:02:50 +02:00
data FileType
= FileTypeRegular
| FileTypeDirectory
| FileTypeSymlink
| FileTypeUnknown
2018-04-07 21:02:50 +02:00
deriving (Show, Read, Eq, Ord)
instance Applicative m => ToNix FileType m (NValue m) where
2018-04-16 07:01:01 +02:00
toNix = toNix . \case
FileTypeRegular -> "regular" :: Text
FileTypeDirectory -> "directory"
FileTypeSymlink -> "symlink"
FileTypeUnknown -> "unknown"
2018-04-07 21:02:50 +02:00
readDir_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
2018-04-07 21:02:50 +02:00
readDir_ pathThunk = do
path <- absolutePathFromValue =<< pathThunk
2018-04-07 21:02:50 +02:00
items <- listDirectory path
itemsWithTypes <- forM items $ \item -> do
s <- Nix.Effects.getSymbolicLinkStatus $ path </> item
2018-04-07 21:02:50 +02:00
let t = if
| isRegularFile s -> FileTypeRegular
| isDirectory s -> FileTypeDirectory
| isSymbolicLink s -> FileTypeSymlink
| otherwise -> FileTypeUnknown
2018-04-07 21:02:50 +02:00
pure (Text.pack item, t)
2018-04-16 07:01:01 +02:00
toNix (M.fromList itemsWithTypes)
2018-04-07 21:02:50 +02:00
fromJSON :: MonadNix e m => m (NValue m) -> m (NValue m)
fromJSON = fromValue >=> \encoded ->
2018-04-07 21:02:50 +02:00
case A.eitherDecodeStrict' @A.Value $ encodeUtf8 encoded of
Left jsonError ->
throwError $ ErrorCall $ "builtins.fromJSON: " ++ jsonError
Right v -> toValue v
2018-04-07 21:02:50 +02:00
toXML_ :: MonadNix e m => m (NValue m) -> m (NValue m)
toXML_ v = v >>= normalForm >>= \x ->
pure $ nvStr (Text.pack (toXML x)) mempty
2018-04-07 21:02:50 +02:00
typeOf :: MonadNix e m => m (NValue m) -> m (NValue m)
typeOf v = v >>= toNix @Text . \case
2018-04-07 21:02:50 +02:00
NVConstant a -> case a of
2018-04-16 07:01:01 +02:00
NInt _ -> "int"
2018-04-07 21:02:50 +02:00
NFloat _ -> "float"
2018-04-16 07:01:01 +02:00
NBool _ -> "bool"
NNull -> "null"
NVStr _ _ -> "string"
NVList _ -> "list"
NVSet _ _ -> "set"
NVClosure {} -> "lambda"
NVPath _ -> "path"
2018-04-07 21:02:50 +02:00
NVBuiltin _ _ -> "lambda"
_ -> error "Pattern synonyms obscure complete patterns"
2018-04-07 21:02:50 +02:00
tryEval :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
tryEval e = catch (onSuccess <$> e) (pure . onError)
2018-04-07 23:33:15 +02:00
where
onSuccess v = flip nvSet M.empty $ M.fromList
[ ("success", valueThunk (nvConstant (NBool True)))
2018-04-07 23:33:15 +02:00
, ("value", valueThunk v)
]
onError :: SomeException -> NValue m
onError _ = flip nvSet M.empty $ M.fromList
[ ("success", valueThunk (nvConstant (NBool False)))
, ("value", valueThunk (nvConstant (NBool False)))
2018-04-07 23:33:15 +02:00
]
2018-04-28 23:28:16 +02:00
trace_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m) -> m (NValue m)
trace_ msg action = do
traceEffect . Text.unpack =<< fromValue @Text msg
action
2018-04-29 01:37:01 +02:00
exec_ :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
exec_ xs = do
ls <- fromValue @[NThunk m] xs
xs <- traverse (fromValue @Text . force') ls
exec (map Text.unpack xs)
fetchTarball :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
fetchTarball v = v >>= \case
NVSet s _ -> case M.lookup "url" s of
Nothing -> throwError $ ErrorCall
"builtins.fetchTarball: Missing url attribute"
Just url -> force url $ go (M.lookup "sha256" s)
v@NVStr {} -> go Nothing v
v -> throwError $ ErrorCall $
"builtins.fetchTarball: Expected URI or set, got " ++ show v
where
go :: Maybe (NThunk m) -> NValue m -> m (NValue m)
go msha = \case
NVStr uri _ -> fetch uri msha
v -> throwError $ ErrorCall $
"builtins.fetchTarball: Expected URI or string, got " ++ show v
{- jww (2018-04-11): This should be written using pipes in another module
fetch :: Text -> Maybe (NThunk m) -> m (NValue 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 (NThunk m) -> m (NValue m)
fetch uri Nothing =
nixInstantiateExpr $ "builtins.fetchTarball \"" ++
Text.unpack uri ++ "\""
fetch url (Just m) = fromValue m >>= \sha ->
nixInstantiateExpr $ "builtins.fetchTarball { "
++ "url = \"" ++ Text.unpack url ++ "\"; "
++ "sha256 = \"" ++ Text.unpack sha ++ "\"; }"
Implement builtins.fetchurl Squashed commit of the following: commit 15b10d898e0457237f07cda9e5e9525bac0e95f6 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:33:30 2018 -0700 Update Exec.hs commit d4a886dccf2715f1c1790e01adc242c352e7f427 Merge: 02afb27 4caacc1 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:55 2018 -0700 Merge branch 'master' into http commit 02afb275f2078c1184a901da3ea0262630fefeea Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:42 2018 -0700 Update Exec.hs commit 3733ce5888adb7161d2f57a16204ab953e9c4d7d Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:07:08 2018 -0700 Update Builtins.hs commit 4402be6d04ac34156d50f8ee29f9af300de75ce5 Merge: 2c60097 13f3ebd Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 15:06:28 2018 -0700 Merge branch 'master' into http commit 2c600976bb3a5d9267a0f313487dd0ab1a6ce1f7 Merge: 4a9d1a5 555ce95 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:25:59 2018 -0700 Merge branch 'master' into http commit 4a9d1a56d463567ad155a58fc39f5b24e2636120 Merge: 4dd46f2 431006f Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:20:57 2018 -0700 Merge branch 'master' into http commit 4dd46f21e3f594c4f7ae5bee8412a7841e566d4c Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sun Apr 29 12:51:11 2018 -0700 generated hnix.cabal commit c87ae993fb7dbb1117f03133862799e1549c4259 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:55:11 2018 -0700 remove dep from hnix.cabal commit 0bb8856c8759ad3c67a0b4eb1d26b6195da82667 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:53:54 2018 -0700 remove http-client stuff from default.nix commit d298756a2ba4376f8cb3c54fb723a00697e0821d Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:49:59 2018 -0700 getURL is implemented for both http and https commit a3d66c07a097aedb03f30bcc636fcb3d5717e1fe Merge: c4cb48a a73eae5 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:14:32 2018 -0700 Merge branch 'builtin2' into http commit c4cb48a8a756e82fb7d389ff501b2a85001dba38 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:13:25 2018 -0700 add getURL function commit ff23fc18ed16075353a58725d7d08f41605a6070 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:06:40 2018 -0700 use http-client-* instead of HTTP commit fcbe40f3bea84607a9d7849a9f3d2fc3a6cb9bef Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:58:07 2018 -0700 add HTTP commit a73eae573a193dbb8361e03b584a6cd55e7c427a Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:36:24 2018 -0700 implement fetchurl (as a copy of fetchTarball)
2018-05-03 06:38:13 +02:00
fetchurl :: forall e m. MonadNix e m => m (NValue m) -> m (NValue m)
fetchurl v = v >>= \case
NVSet s _ -> attrsetGet "url" s >>= force ?? (go (M.lookup "sha256" s))
v@NVStr {} -> go Nothing v
v -> throwError $ ErrorCall $ "builtins.fetchurl: Expected URI or set, got "
++ show v
where
go :: Maybe (NThunk m) -> NValue m -> m (NValue m)
2018-05-03 06:39:23 +02:00
go _msha = \case
Implement builtins.fetchurl Squashed commit of the following: commit 15b10d898e0457237f07cda9e5e9525bac0e95f6 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:33:30 2018 -0700 Update Exec.hs commit d4a886dccf2715f1c1790e01adc242c352e7f427 Merge: 02afb27 4caacc1 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:55 2018 -0700 Merge branch 'master' into http commit 02afb275f2078c1184a901da3ea0262630fefeea Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:42 2018 -0700 Update Exec.hs commit 3733ce5888adb7161d2f57a16204ab953e9c4d7d Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:07:08 2018 -0700 Update Builtins.hs commit 4402be6d04ac34156d50f8ee29f9af300de75ce5 Merge: 2c60097 13f3ebd Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 15:06:28 2018 -0700 Merge branch 'master' into http commit 2c600976bb3a5d9267a0f313487dd0ab1a6ce1f7 Merge: 4a9d1a5 555ce95 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:25:59 2018 -0700 Merge branch 'master' into http commit 4a9d1a56d463567ad155a58fc39f5b24e2636120 Merge: 4dd46f2 431006f Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:20:57 2018 -0700 Merge branch 'master' into http commit 4dd46f21e3f594c4f7ae5bee8412a7841e566d4c Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sun Apr 29 12:51:11 2018 -0700 generated hnix.cabal commit c87ae993fb7dbb1117f03133862799e1549c4259 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:55:11 2018 -0700 remove dep from hnix.cabal commit 0bb8856c8759ad3c67a0b4eb1d26b6195da82667 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:53:54 2018 -0700 remove http-client stuff from default.nix commit d298756a2ba4376f8cb3c54fb723a00697e0821d Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:49:59 2018 -0700 getURL is implemented for both http and https commit a3d66c07a097aedb03f30bcc636fcb3d5717e1fe Merge: c4cb48a a73eae5 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:14:32 2018 -0700 Merge branch 'builtin2' into http commit c4cb48a8a756e82fb7d389ff501b2a85001dba38 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:13:25 2018 -0700 add getURL function commit ff23fc18ed16075353a58725d7d08f41605a6070 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:06:40 2018 -0700 use http-client-* instead of HTTP commit fcbe40f3bea84607a9d7849a9f3d2fc3a6cb9bef Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:58:07 2018 -0700 add HTTP commit a73eae573a193dbb8361e03b584a6cd55e7c427a Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:36:24 2018 -0700 implement fetchurl (as a copy of fetchTarball)
2018-05-03 06:38:13 +02:00
NVStr uri _ -> getURL uri -- msha
2018-05-03 06:39:23 +02:00
v -> throwError $ ErrorCall $
Implement builtins.fetchurl Squashed commit of the following: commit 15b10d898e0457237f07cda9e5e9525bac0e95f6 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:33:30 2018 -0700 Update Exec.hs commit d4a886dccf2715f1c1790e01adc242c352e7f427 Merge: 02afb27 4caacc1 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:55 2018 -0700 Merge branch 'master' into http commit 02afb275f2078c1184a901da3ea0262630fefeea Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:08:42 2018 -0700 Update Exec.hs commit 3733ce5888adb7161d2f57a16204ab953e9c4d7d Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 16:07:08 2018 -0700 Update Builtins.hs commit 4402be6d04ac34156d50f8ee29f9af300de75ce5 Merge: 2c60097 13f3ebd Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 15:06:28 2018 -0700 Merge branch 'master' into http commit 2c600976bb3a5d9267a0f313487dd0ab1a6ce1f7 Merge: 4a9d1a5 555ce95 Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:25:59 2018 -0700 Merge branch 'master' into http commit 4a9d1a56d463567ad155a58fc39f5b24e2636120 Merge: 4dd46f2 431006f Author: John Wiegley <johnw@newartisans.com> Date: Wed May 2 14:20:57 2018 -0700 Merge branch 'master' into http commit 4dd46f21e3f594c4f7ae5bee8412a7841e566d4c Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sun Apr 29 12:51:11 2018 -0700 generated hnix.cabal commit c87ae993fb7dbb1117f03133862799e1549c4259 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:55:11 2018 -0700 remove dep from hnix.cabal commit 0bb8856c8759ad3c67a0b4eb1d26b6195da82667 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 16:53:54 2018 -0700 remove http-client stuff from default.nix commit d298756a2ba4376f8cb3c54fb723a00697e0821d Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:49:59 2018 -0700 getURL is implemented for both http and https commit a3d66c07a097aedb03f30bcc636fcb3d5717e1fe Merge: c4cb48a a73eae5 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:14:32 2018 -0700 Merge branch 'builtin2' into http commit c4cb48a8a756e82fb7d389ff501b2a85001dba38 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:13:25 2018 -0700 add getURL function commit ff23fc18ed16075353a58725d7d08f41605a6070 Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 15:06:40 2018 -0700 use http-client-* instead of HTTP commit fcbe40f3bea84607a9d7849a9f3d2fc3a6cb9bef Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:58:07 2018 -0700 add HTTP commit a73eae573a193dbb8361e03b584a6cd55e7c427a Author: Ian-Woo Kim <ianwookim@gmail.com> Date: Sat Apr 28 14:36:24 2018 -0700 implement fetchurl (as a copy of fetchTarball)
2018-05-03 06:38:13 +02:00
"builtins.fetchurl: Expected URI or string, got " ++ show v
partition_ :: forall e m. MonadNix e m
=> m (NValue m) -> m (NValue m) -> m (NValue m)
partition_ fun xs = fun >>= \f ->
fromValue @[NThunk m] xs >>= \l -> do
let match t = f `callFunc` force' t >>= fmap (, t) . fromValue
selection <- traverse match l
let (right, wrong) = partition fst selection
let makeSide = valueThunk . nvList . map snd
toValue @(AttrSet (NThunk m)) $
M.fromList [("right", makeSide right), ("wrong", makeSide wrong)]
2018-04-07 21:02:50 +02:00
currentSystem :: MonadNix e m => m (NValue m)
2018-04-07 21:02:50 +02:00
currentSystem = do
os <- getCurrentSystemOS
arch <- getCurrentSystemArch
return $ nvStr (arch <> "-" <> os) mempty
2018-04-07 21:02:50 +02:00
2018-05-03 06:32:00 +02:00
currentTime_ :: MonadNix e m => m (NValue m)
currentTime_ = do
opts :: Options <- asks (view hasLens)
toNix @Integer $ round $ Time.utcTimeToPOSIXSeconds (currentTime opts)
derivationStrict_ :: MonadNix e m => m (NValue m) -> m (NValue m)
derivationStrict_ = (>>= derivationStrict)
2018-04-08 00:34:54 +02:00
2018-04-07 21:02:50 +02:00
newtype Prim m a = Prim { runPrim :: m a }
-- | Types that support conversion to nix in a particular monad
class ToBuiltin m a | a -> m where
toBuiltin :: String -> a -> m (NValue m)
instance (MonadNix e m, ToNix a m (NValue m))
=> ToBuiltin m (Prim m a) where
toBuiltin _ p = toNix =<< runPrim p
2018-04-07 21:02:50 +02:00
instance (MonadNix e m, FromNix a m (NValue m), ToBuiltin m b)
2018-04-07 21:02:50 +02:00
=> ToBuiltin m (a -> b) where
toBuiltin name f = return $ nvBuiltin name (fromNix >=> toBuiltin name . f)