Skip to content
This repository has been archived by the owner on Apr 1, 2022. It is now read-only.

Commit

Permalink
Gomod: ignore local modules in a multi-module project (#171)
Browse files Browse the repository at this point in the history
  • Loading branch information
cnr authored Dec 28, 2020
1 parent 6b6257d commit 2736544
Show file tree
Hide file tree
Showing 3 changed files with 38 additions and 9 deletions.
40 changes: 31 additions & 9 deletions src/Strategy/Go/Gomod.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,9 @@ module Strategy.Go.Gomod
where

import Control.Effect.Diagnostics hiding (fromMaybe)
import Data.Char (isSpace)
import Data.Foldable (traverse_)
import Data.Functor (void)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe (fromMaybe)
Expand All @@ -35,6 +37,7 @@ import qualified Text.Megaparsec.Char.Lexer as L
data Statement =
RequireStatement Text Text -- ^ package, version
| ReplaceStatement Text Text Text -- ^ old, new, newVersion
| LocalReplaceStatement Text Text -- ^ old, dir (local "submodule" dependency -- dir can be a resolvable string (e.g., "../foo") or an actual directory (e.g., "/foo" or "foo/"))
| ExcludeStatement Text Text -- ^ package, version
| GoVersionStatement Text
deriving (Eq, Ord, Show)
Expand All @@ -45,6 +48,7 @@ data Gomod = Gomod
{ modName :: PackageName
, modRequires :: [Require]
, modReplaces :: Map PackageName Require
, modLocalReplaces :: Map PackageName Text
, modExcludes :: [Require]
} deriving (Eq, Ord, Show)

Expand All @@ -57,10 +61,11 @@ type Parser = Parsec Void Text

gomodParser :: Parser Gomod
gomodParser = do
_ <- sc
_ <- scn
_ <- lexeme (chunk "module")
name <- packageName
statements <- many statement
_ <- scn
statements <- many (statement <* scn)
eof

let statements' = concat statements
Expand Down Expand Up @@ -98,12 +103,15 @@ gomodParser = do
-- golang.org/x/text => golang.org/x/text v3.0.0
-- )
replaceStatements :: Parser [Statement]
replaceStatements = block "replace" singleReplace
replaceStatements = block "replace" (try singleReplace <|> singleLocalReplace)

-- parse the body of a single replace (without the leading "replace" lexeme)
singleReplace :: Parser Statement
singleReplace = ReplaceStatement <$> packageName <* optional semver <* lexeme (chunk "=>") <*> packageName <*> semver

singleLocalReplace :: Parser Statement
singleLocalReplace = LocalReplaceStatement <$> packageName <* optional semver <* lexeme (chunk "=>") <*> anyToken

-- top-level exclude statements
-- e.g.:
-- exclude golang.org/x/text v3.0.0
Expand Down Expand Up @@ -131,7 +139,7 @@ gomodParser = do
-- )
block prefix parseSingle = do
_ <- lexeme (chunk prefix)
parens (many parseSingle) <|> (singleton <$> parseSingle)
parens (many (parseSingle <* scn)) <|> (singleton <$> parseSingle)

-- package name, e.g., golang.org/x/text
packageName :: Parser Text
Expand All @@ -149,25 +157,39 @@ gomodParser = do

-- lexer combinators
parens = between (symbol "(") (symbol ")")
symbol = L.symbol sc
symbol = L.symbol scn
lexeme = L.lexeme sc

-- space consumer (for use with Text.Megaparsec.Char.Lexer combinators)
anyToken :: Parser Text
anyToken = lexeme (takeWhile1P (Just "any token") (not . isSpace))

-- space consumer WITHOUT newlines (for use with Text.Megaparsec.Char.Lexer combinators)
sc :: Parser ()
sc = L.space space1 (L.skipLineComment "//") (L.skipBlockComment "/*" "*/")
sc = L.space (void $ some (char ' ' <|> char '\t')) (L.skipLineComment "//") (L.skipBlockComment "/*" "*/")

-- space consumer with newlines
scn :: Parser ()
scn = L.space space1 (L.skipLineComment "//") (L.skipBlockComment "/*" "*/")

toGomod :: Text -> [Statement] -> Gomod
toGomod name = foldr apply (Gomod name [] M.empty [])
toGomod name = foldr apply (Gomod name [] M.empty M.empty [])
where
apply (RequireStatement package version) gomod = gomod { modRequires = Require package version : modRequires gomod }
apply (ReplaceStatement old new newVersion) gomod = gomod { modReplaces = M.insert old (Require new newVersion) (modReplaces gomod) }
apply (LocalReplaceStatement old path) gomod = gomod { modLocalReplaces = M.insert old path (modLocalReplaces gomod) }
apply (ExcludeStatement package version) gomod = gomod { modExcludes = Require package version : modExcludes gomod }
apply _ gomod = gomod

-- lookup modRequires and replace them with modReplaces as appropriate, producing the resolved list of requires
resolve :: Gomod -> [Require]
resolve gomod = map resolveReplace (modRequires gomod)
resolve gomod = map resolveReplace . filter nonLocalPackage $ modRequires gomod
where
-- nonLocalPackage determines whether the package name is used in a "local
-- replace" statement -- i.e., a replace statement pointing to a filepath as a
-- local module
nonLocalPackage :: Require -> Bool
nonLocalPackage = not . (`elem` M.keys (modLocalReplaces gomod)) . reqPackage

resolveReplace require = fromMaybe require (M.lookup (reqPackage require) (modReplaces gomod))

analyze' ::
Expand Down
5 changes: 5 additions & 0 deletions test/Go/GomodSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ gomod = Gomod
, Require "github.com/pkg/three/v3" "v3.0.0"
]
, modReplaces = M.fromList [("github.com/pkg/two/v2", Require "github.com/pkg/overridden" "overridden")]
, modLocalReplaces = M.empty
, modExcludes = []
}

Expand Down Expand Up @@ -92,6 +93,10 @@ spec_parse = do
, ("repo/E", Require "alias/repo/E" "v0.0.0-20170808103936-000000000005+incompatible")
, ("repo/F_underscore", Require "repo/F_underscore" "v2.0.0")
]
, modLocalReplaces = M.fromList
[ ("foo", "../foo")
, ("bar", "/foo/bar/baz")
]
, modExcludes = [ Require "repo/B" "v0.9.0"
, Require "repo/C" "v1.0.0"
, Require "repo/name/D" "v3.0.0"
Expand Down
2 changes: 2 additions & 0 deletions test/Go/testdata/go.mod.edgecases
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ replace repo/B => alias/repo/B v0.1.0
replace (
repo/C => alias/repo/C v0.0.0-20180207000608-000000000003
repo/E => alias/repo/E v0.0.0-20170808103936-000000000005+incompatible
foo v0 => ../foo
bar => /foo/bar/baz
repo/F_underscore v1.0.0 => repo/F_underscore v2.0.0
)

Expand Down

0 comments on commit 2736544

Please sign in to comment.