about summary refs log tree commit diff
path: root/users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs
diff options
context:
space:
mode:
authorProfpatsch <mail@profpatsch.de>2021-01-10T19·56+0100
committerProfpatsch <mail@profpatsch.de>2021-01-10T20·03+0000
commit2f807d7f141068d2d60676a89213eaa5353ca6e0 (patch)
tree4f2b13aab630c4febb5d9ccd3d701565009b6c39 /users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs
parentc1cb4c260c97ad83a68f323dfeb4534f972c375a (diff)
feat(users/Profpatsch): add a rewriter for lib.stdenv changes r/2070
This is in order to advance the rewriting from stdenv.lib to lib.
https://github.com/NixOS/nixpkgs/issues/108938

The hard part about changing the argument is that a package might not
include lib in its arguments, which is why I use hnix to check whether
lib is included and add it to the import list if it doesn’t already
exist there.

So far, only the really common pattern of

    meta = with stdenv.lib;

is rewritten.

Change-Id: I370f0a321b0e5a5bd21ec21fc7cefdd65ec845ed
Reviewed-on: https://cl.tvl.fyi/c/depot/+/2345
Tested-by: BuildkiteCI
Reviewed-by: Profpatsch <mail@profpatsch.de>
Diffstat (limited to 'users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs')
-rw-r--r--users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs80
1 files changed, 80 insertions, 0 deletions
diff --git a/users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs b/users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs
new file mode 100644
index 000000000000..3ed96a7b6eac
--- /dev/null
+++ b/users/Profpatsch/nixpkgs-rewriter/MetaStdenvLib.hs
@@ -0,0 +1,80 @@
+{-# LANGUAGE PartialTypeSignatures #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE NamedFieldPuns #-}
+import Nix.Parser
+import Nix.Expr.Types
+import Nix.Expr.Types.Annotated
+import System.Environment (getArgs)
+import System.Exit (die)
+import Data.Fix (Fix(..))
+import qualified Data.Text as Text
+import qualified Data.ByteString.Lazy.Char8 as BL
+import qualified Data.Aeson as A
+import qualified Data.Aeson.Encoding as A
+import Data.Function ((&))
+import qualified System.IO as IO
+import qualified Text.Megaparsec.Pos as MP
+
+main = do
+  (nixFile:_) <- getArgs
+  (parseNixFileLoc nixFile :: IO _) >>= \case
+    Failure err -> do
+      ePutStrLn $ show err
+      die "oh no"
+    Success expr -> do
+      case snd $ match expr of
+        NoArguments -> do
+          ePutStrLn $ "NoArguments in " <> nixFile
+          printPairs mempty
+        YesLib vars -> do
+          ePutStrLn $ "lib in " <> show vars <> " in " <> nixFile
+          printPairs mempty
+        NoLib vars srcSpan -> do
+          ePutStrLn $ nixFile <> " needs lib added"
+          printPairs
+            $ "fileName" A..= nixFile
+            <> "fromLine" A..= (srcSpan & spanBegin & sourceLine)
+            <> "fromColumn" A..= (srcSpan & spanBegin & sourceColumn)
+            <> "toLine" A..= (srcSpan & spanEnd & sourceLine)
+            <> "toColumn" A..= (srcSpan & spanEnd & sourceColumn)
+
+printPairs pairs = BL.putStrLn $ A.encodingToLazyByteString $ A.pairs pairs
+
+ePutStrLn = IO.hPutStrLn IO.stderr
+
+data Descend = YesDesc | NoDesc
+  deriving Show
+data Matched =  NoArguments | NoLib [VarName] SrcSpan | YesLib [VarName]
+  deriving Show
+
+match :: Fix (Compose (Ann SrcSpan) NExprF) -> (Descend, Matched)
+match = \case
+  (AnnE outerSpan (NAbs (ParamSet params _ _) (AnnE innerSpan _))) -> (NoDesc,
+    let vars = map fst params in
+    case (any (== "lib") vars) of
+      True -> YesLib vars
+      False ->
+          -- The span of the arglist is from the beginning of the match
+          -- to the beginning of the inner expression
+          let varSpan = SrcSpan
+                { spanBegin = outerSpan & spanBegin
+                -- -1 to prevent the spans from overlapping
+                , spanEnd = sourcePosMinus1 (innerSpan & spanBegin) }
+          in NoLib vars varSpan)
+  _ -> (NoDesc, NoArguments)
+
+-- | Remove one from a source positon.
+--
+-- That means if the current position is at the very beginning of a line,
+-- jump to the previous line.
+sourcePosMinus1 :: SourcePos -> SourcePos
+sourcePosMinus1 src@(SourcePos { sourceLine, sourceColumn }) =
+  let
+    col = MP.mkPos $ max (MP.unPos sourceColumn - 1) 1
+    line = MP.mkPos $ case MP.unPos sourceColumn of
+      1 -> max (MP.unPos sourceLine - 1) 1
+      _ -> MP.unPos sourceLine
+  in src
+    { sourceLine = line
+    , sourceColumn = col }