Skip to content

Commit

Permalink
Fix CI (Container Update) (#935)
Browse files Browse the repository at this point in the history
* Cleanup match gaurds

Match guards are hard to read for a number of reasons, but the latest
formatter changes have made it unbearable.
We are now outlawing all match guards.

* fmt: haddock in records

* Add todo

* Forbid match guards

* traverse = sequence . map

* Fix imports

* mapMaybe = catMaybe . map

* concatMap = concat . map

* Fix ref link syntax
  • Loading branch information
Wesley Van Melle authored May 16, 2022
1 parent afc710b commit bde67a0
Show file tree
Hide file tree
Showing 16 changed files with 90 additions and 58 deletions.
22 changes: 22 additions & 0 deletions docs/contributing/STYLE-GUIDE.md
Original file line number Diff line number Diff line change
Expand Up @@ -120,6 +120,25 @@ make sure that you have a solid justification for doing so.
In almost all cases, `map`, `filter`, `fold`, and the `[]` monad are more
flexible and readable.

### Do not use match guards

While matching data at the function binding is appealing as an idea, but has
several drawbacks:

- Match guards in function definitions are adding more info into an area
that may already be cluttered.
- Match guards with multiple bindings are essentially the same syntax as list
comprehensions, which are also forbidden.
- Match guards offer an alternative to `case` and `if`, which makes it harder
to establish a guideline of "There should only be one right and obvious way to
do something" (which is a loose goal for the codebase).

If your match guards are any less readable than the introductory examples in
[Learn you a haskell][guards], then you should stick to `case` and `if`
expressions within the function body.

[guards]: http://learnyouahaskell.com/syntax-in-functions#guards-guards

### Don't go crazy with point-free definitions

Point-free style can help or hinder readability, depending on the context. If a
Expand Down Expand Up @@ -339,3 +358,6 @@ Use these instead of `decodeUtf8`/`encodeUTF8`/`Text.pack`
compiles identically, then remove it.
- Avoid nested `where` blocks. If you feel that you need them, rethink your
design. Consider making an `Internal` module instead.
- In do-notation, use `let` bindings, otherwise, use `where` clauses. Don't
use `let` expressions (exammple: `let ... in ...`).

10 changes: 5 additions & 5 deletions src/App/Fossa/VSI/Fingerprint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -214,11 +214,11 @@ basicCStyleCommentStripC =
-- 2. If the substring was not found, the result is @Nothing@,
-- instead of one of the options being a blank @ByteString@.
breakSubstringAndRemove :: ByteString -> ByteString -> Maybe (ByteString, ByteString)
breakSubstringAndRemove needle haystack
| (before, after) <- BS.breakSubstring needle haystack
, BS.isPrefixOf needle after =
Just (before, BS.drop (BS.length needle) after)
| otherwise = Nothing
breakSubstringAndRemove needle haystack = do
let (before, after) = BS.breakSubstring needle haystack
if needle `BS.isPrefixOf` after
then pure (before, BS.drop (BS.length needle) after)
else Nothing

-- | Remove leading and trailing spaces.
stripSpace :: ByteString -> ByteString
Expand Down
10 changes: 5 additions & 5 deletions src/Data/Text/Extra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,11 +37,11 @@ splitOnceOnEnd needle haystack = (strippedInitial, end)
-- >>> breakOnAndRemove "foo" "bar"
-- Nothing
breakOnAndRemove :: Text -> Text -> Maybe (Text, Text)
breakOnAndRemove needle haystack
| (before, after) <- Text.breakOn needle haystack
, Text.isPrefixOf needle after =
Just (before, Text.drop (Text.length needle) after)
| otherwise = Nothing
breakOnAndRemove needle haystack = do
let (before, after) = Text.breakOn needle haystack
if needle `Text.isPrefixOf` after
then pure (before, Text.drop (Text.length needle) after)
else Nothing

underBS :: (ByteString -> ByteString) -> Text -> Text
underBS f = decodeUtf8 . f . encodeUtf8
Expand Down
12 changes: 6 additions & 6 deletions src/Effect/Exec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,12 +74,12 @@ import Text.Megaparsec (Parsec, runParser)
import Text.Megaparsec.Error (errorBundlePretty)

data Command = Command
{ -- | Command name to use. E.g., "pip", "pip3", "./gradlew".
cmdName :: Text
, -- | Arguments for the command
cmdArgs :: [Text]
, -- | Error (i.e. non-zero exit code) tolerance policy for running commands. This is helpful for commands like @npm@, that nonsensically return non-zero exit codes when a command succeeds
cmdAllowErr :: AllowErr
{ cmdName :: Text
-- ^ Command name to use. E.g., "pip", "pip3", "./gradlew".
, cmdArgs :: [Text]
-- ^ Arguments for the command
, cmdAllowErr :: AllowErr
-- ^ Error (i.e. non-zero exit code) tolerance policy for running commands. This is helpful for commands like @npm@, that nonsensically return non-zero exit codes when a command succeeds
}
deriving (Eq, Ord, Show, Generic)

Expand Down
12 changes: 6 additions & 6 deletions src/Srclib/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -180,8 +180,8 @@ instance FromJSON LicenseUnitMatchData where
data SourceUnit = SourceUnit
{ sourceUnitName :: Text
, sourceUnitType :: Text
, -- | path to manifest file
sourceUnitManifest :: Text
, sourceUnitManifest :: Text
-- ^ path to manifest file
, sourceUnitBuild :: Maybe SourceUnitBuild
, sourceUnitGraphBreadth :: GraphBreadth
, sourceUnitOriginPaths :: [SomeBase File]
Expand All @@ -190,10 +190,10 @@ data SourceUnit = SourceUnit
deriving (Eq, Ord, Show)

data SourceUnitBuild = SourceUnitBuild
{ -- | always "default"
buildArtifact :: Text
, -- | always true
buildSucceeded :: Bool
{ buildArtifact :: Text
-- ^ always "default"
, buildSucceeded :: Bool
-- ^ always true
, buildImports :: [Locator]
, buildDependencies :: [SourceUnitDependency]
}
Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Cargo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -210,8 +210,8 @@ instance AnalyzeProject CargoProject where

data CargoPackage = CargoPackage
{ license :: Maybe Text.Text
, -- | Path relative to Cargo.toml containing the license
cargoLicenseFile :: Maybe FilePath
, cargoLicenseFile :: Maybe FilePath
-- ^ Path relative to Cargo.toml containing the license
}
deriving (Eq, Show)

Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Composer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -135,8 +135,8 @@ data ComposerLock = ComposerLock
data CompDep = CompDep
{ depName :: Text
, depVersion :: Text
, -- | name to version spec
depRequire :: Maybe (Map Text Text)
, depRequire :: Maybe (Map Text Text)
-- ^ name to version spec
, depRequireDev :: Maybe (Map Text Text)
}
deriving (Eq, Ord, Show)
Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Gradle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ import Data.ByteString (ByteString)
import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BL
import Data.FileEmbed (embedFile)
import Data.Foldable (find)
import Data.Foldable (find, traverse_)
import Data.List (isPrefixOf)
import Data.Maybe (mapMaybe)
import Data.Set (Set)
Expand Down Expand Up @@ -296,6 +296,6 @@ analyze foundTargets dir = withSystemTempDir "fossa-gradle" $ \tmpDir -> do
let graphFromResolutionApi = ResolutionApi.buildGraph resolvedProjects (onlyConfigurations)

-- Log debug messages as seen in gradle script
sequence_ $ logDebug . pretty <$> (getDebugMessages text)
traverse_ (logDebug . pretty) (getDebugMessages text)

context "Building dependency graph" $ pure graphFromResolutionApi
7 changes: 4 additions & 3 deletions src/Strategy/Leiningen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -241,12 +241,13 @@ ednVecToMap :: EDN.EDNVec -> Parser EDN.EDNMap
ednVecToMap = go Map.empty
where
go :: EDN.EDNMap -> EDN.EDNVec -> Parser EDN.EDNMap
-- TODO: refactor this to not use match guards
go m vec
| V.null vec = pure m
| otherwise = do
key <- EDN.vecGet 0 vec
value <- EDN.vecGet 1 vec
go (Map.insert key value m) (V.drop 2 vec)
key <- EDN.vecGet 0 vec
value <- EDN.vecGet 1 vec
go (Map.insert key value m) (V.drop 2 vec)

-- | The FromEDN type for lein deps output
newtype Deps = Deps
Expand Down
9 changes: 4 additions & 5 deletions src/Strategy/Maven/Pom.hs
Original file line number Diff line number Diff line change
Expand Up @@ -191,8 +191,7 @@ interpolate properties text =
-- find the first maven property in the string, e.g., `${foo}`, returning text
-- before the property, the property, and the text after the property
splitMavenProperty :: Text -> Maybe (Text, Text, Text)
splitMavenProperty text
| Just (beforeBegin, afterBegin) <- breakOnAndRemove "${" text
, Just (property, afterEnd) <- breakOnAndRemove "}" afterBegin =
Just (beforeBegin, property, afterEnd)
| otherwise = Nothing
splitMavenProperty text = do
(beforeBegin, afterBegin) <- breakOnAndRemove "${" text
(property, afterEnd) <- breakOnAndRemove "}" afterBegin
pure (beforeBegin, property, afterEnd)
8 changes: 4 additions & 4 deletions src/Strategy/Maven/Pom/Closure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,10 +99,10 @@ determineProjectRoots rootDir closure = go . Set.fromList
frontier = Set.unions $ Set.map (\coord -> AM.postSet coord (globalGraph closure)) remainingCoords

data MavenProjectClosure = MavenProjectClosure
{ -- | the root of global fossa-analyze analysis; needed for pathfinder license scan
closureAnalysisRoot :: Path Abs Dir
, -- | path of the pom file used as the root of this project closure
closurePath :: Path Abs File
{ closureAnalysisRoot :: Path Abs Dir
-- ^ the root of global fossa-analyze analysis; needed for pathfinder license scan
, closurePath :: Path Abs File
-- ^ path of the pom file used as the root of this project closure
, closureRootCoord :: MavenCoordinate
, closureRootPom :: Pom
, closureGraph :: AM.AdjacencyMap MavenCoordinate
Expand Down
16 changes: 11 additions & 5 deletions src/Strategy/Nim/NimbleLock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,14 @@ module Strategy.Nim.NimbleLock (
) where

import Algebra.Graph.AdjacencyMap qualified as AM
import Control.Carrier.Diagnostics (ToDiagnostic, errCtx, warnOnErr)
import Control.Effect.Diagnostics (Diagnostics, ToDiagnostic (renderDiagnostic), context, recover)
import Control.Effect.Diagnostics (
Diagnostics,
ToDiagnostic (renderDiagnostic),
context,
errCtx,
recover,
warnOnErr,
)
import Data.Aeson (
FromJSON (parseJSON),
FromJSONKey,
Expand All @@ -28,7 +34,7 @@ import Data.Aeson.Types (Parser)
import Data.HashMap.Strict qualified as HM
import Data.Map (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe (catMaybes, mapMaybe)
import Data.Maybe (mapMaybe)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Traversable (for)
Expand All @@ -48,7 +54,7 @@ import Graphing (
toAdjacencyMap,
unfoldDeep,
)
import Path
import Path (Abs, Dir, File, Path)
import Types (GraphBreadth (..))

-- | Represents nimble lock file.
Expand Down Expand Up @@ -136,7 +142,7 @@ buildGraph lockFile nimbleDump =
applyDirect :: Graphing NimPackage -> Graphing NimPackage
applyDirect gr = case nimbleDump of
Nothing -> Graphing.directs (getVerticesWithoutPredecessors gr) <> gr
Just nd -> Graphing.directs (catMaybes $ (`Map.lookup` pkgRegistry) <$> map nameOf (requires nd)) <> gr
Just nd -> Graphing.directs (mapMaybe ((`Map.lookup` pkgRegistry) . nameOf) (requires nd)) <> gr

toDependency :: NimPackage -> Maybe Dependency
toDependency nimPkg = case downloadMethod nimPkg of
Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Node/Npm/PackageLock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,8 +85,8 @@ data PkgLockDependency = PkgLockDependency
{ depVersion :: Text
, depDev :: Bool
, depResolved :: NpmResolved
, -- | name to version spec
depRequires :: Map Text Text
, depRequires :: Map Text Text
-- ^ name to version spec
, depDependencies :: Map Text PkgLockDependency
}
deriving (Eq, Ord, Show)
Expand Down
12 changes: 6 additions & 6 deletions src/Strategy/Node/YarnV2/Resolvers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,12 +39,12 @@ import Strategy.Node.YarnV2.Lockfile
import Text.Megaparsec

data Resolver = Resolver
{ -- | Used for error messages
resolverName :: Text
, -- | Does this resolver support the locator?
resolverSupportsLocator :: Locator -> Bool
, -- | Convert this locator to a yarn package
resolverLocatorToPackage :: Locator -> Either Text Package
{ resolverName :: Text
-- ^ Used for error messages
, resolverSupportsLocator :: Locator -> Bool
-- ^ Does this resolver support the locator?
, resolverLocatorToPackage :: Locator -> Either Text Package
-- ^ Convert this locator to a yarn package
}

data Package
Expand Down
6 changes: 5 additions & 1 deletion src/Strategy/NuGet/ProjectAssetsJson.hs
Original file line number Diff line number Diff line change
Expand Up @@ -215,7 +215,11 @@ graphOfFramework projectFrameworkDeps (targetFramework, targetFrameworkDeps) = d
isDirectDep d = depName d `elem` (getProjectDirectDepsByFramework)

getTransitiveDeps :: NuGetDep -> [NuGetDep]
getTransitiveDeps nugetDep = concat $ (\(name, _) -> filter (\d -> depName d == name) allResolvedDeps) <$> Map.toList (completeDeepDeps nugetDep)
getTransitiveDeps nugetDep =
concatMap
(\(name, _) -> filter (\d -> depName d == name) allResolvedDeps)
. Map.toList
$ completeDeepDeps nugetDep

allResolvedDeps :: [NuGetDep]
allResolvedDeps = map toNugetDep $ Map.toList targetFrameworkDeps
Expand Down
8 changes: 4 additions & 4 deletions src/Strategy/Swift/Xcode/Pbxproj.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,10 +32,10 @@ import Strategy.Swift.Xcode.PbxprojParser (AsciiValue (..), PbxProj (..), lookup

-- | Represents the version rules for a Swift Package as defined in Xcode project file.
data XCRemoteSwiftPackageReference = XCRemoteSwiftPackageReference
{ -- | Represents repositoryURL field from project file.
urlOf :: Text
, -- | Represents requirement field from project file.
requirementOf :: SwiftPackageGitDepRequirement
{ urlOf :: Text
-- ^ Represents repositoryURL field from project file.
, requirementOf :: SwiftPackageGitDepRequirement
-- ^ Represents requirement field from project file.
}
deriving (Show, Eq, Ord)

Expand Down

0 comments on commit bde67a0

Please sign in to comment.