diff --git a/.github/workflows/format.yml b/.github/workflows/format.yml index 0308e4a595c06873415bb25935e5b5c6f4552b2c..7e75af1af625af6b1a933c3dd103733617b36da1 100644 --- a/.github/workflows/format.yml +++ b/.github/workflows/format.yml @@ -15,9 +15,4 @@ jobs: pattern: | Cabal/**/*.hs Cabal-syntax/**/*.hs - Cabal-install/**/*.hs - !Cabal-syntax/src/Distribution/Fields/Lexer.hs - !Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs - !Cabal-syntax/src/Distribution/SPDX/LicenseId.hs - !Cabal/src/Distribution/Simple/Build/Macros/Z.hs - !Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs + cabal-install/**/*.hs diff --git a/Cabal-syntax/src/Distribution/Fields/Lexer.hs b/Cabal-syntax/src/Distribution/Fields/Lexer.hs index 2372fde3787234ea7e0ce2e5afca63b6c0246a97..a24606f64fffb1c7f0da550973a380100d3415f2 100644 --- a/Cabal-syntax/src/Distribution/Fields/Lexer.hs +++ b/Cabal-syntax/src/Distribution/Fields/Lexer.hs @@ -1,3 +1,4 @@ +{- FOURMOLU_DISABLE -} {-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-missing-signatures #-} {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} diff --git a/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs b/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs index b25a9e693419fcd8d547c03b4b3302fde243d3b9..59077b29a354a13664f293e0039f3f3825f9ffba 100644 --- a/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs +++ b/Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs @@ -1,4 +1,5 @@ -- This file is generated. See Makefile's spdx rule +{- FOURMOLU_DISABLE -} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} module Distribution.SPDX.LicenseExceptionId ( diff --git a/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs b/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs index 6d5361ba366a6413f2274d4712e01e5a1ee87f54..22ea912f3e4c4115e4d16d050c1f3fb59754c544 100644 --- a/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs +++ b/Cabal-syntax/src/Distribution/SPDX/LicenseId.hs @@ -1,4 +1,5 @@ -- This file is generated. See Makefile's spdx rule +{- FOURMOLU_DISABLE -} {-# LANGUAGE DeriveDataTypeable #-} module Distribution.SPDX.LicenseId ( LicenseId (..), diff --git a/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs b/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs index d75466355453804204726e99a8866d7bf95572a3..7578907b5901f8acb4647d078b22d64acf754762 100644 --- a/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs +++ b/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs @@ -79,8 +79,8 @@ ipiFieldGrammar = mkInstalledPackageInfo -- Deprecated fields <$> monoidalFieldAla "hugs-options" (alaList' FSep Token) unitedList - --- https://github.com/haskell/cabal/commit/40f3601e17024f07e0da8e64d3dd390177ce908b - ^^^ deprecatedSince CabalSpecV1_22 "hugs isn't supported anymore" + --- https://github.com/haskell/cabal/commit/40f3601e17024f07e0da8e64d3dd390177ce908b + ^^^ deprecatedSince CabalSpecV1_22 "hugs isn't supported anymore" -- Very basic fields: name, version, package-name, lib-name and visibility <@> blurFieldGrammar basic basicFieldGrammar -- Basic fields diff --git a/Cabal/src/Distribution/Simple/Build/Macros/Z.hs b/Cabal/src/Distribution/Simple/Build/Macros/Z.hs index 4c14843e041d13c6958d1c1699a852db8113c796..77e0ca4a94d04e3e35301b5f9e4996df2cad92af 100644 --- a/Cabal/src/Distribution/Simple/Build/Macros/Z.hs +++ b/Cabal/src/Distribution/Simple/Build/Macros/Z.hs @@ -1,3 +1,4 @@ +{- FOURMOLU_DISABLE -} {-# LANGUAGE DeriveGeneric #-} module Distribution.Simple.Build.Macros.Z (render, Z(..), ZPackage (..), ZTool (..)) where import Distribution.ZinzaPrelude diff --git a/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs b/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs index 9100dc629ec0c9ea62db546bd6805c12f911ff2e..25c924720ec523afc6c96781ddb3339f7892dcef 100644 --- a/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs +++ b/Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs @@ -1,3 +1,4 @@ +{- FOURMOLU_DISABLE -} {-# LANGUAGE DeriveGeneric #-} module Distribution.Simple.Build.PathsModule.Z (render, Z(..)) where import Distribution.ZinzaPrelude diff --git a/Makefile b/Makefile index 306faea8f8de211db3ea5371843c1f767077c241..8f35c847af67ce3577840cab12cab70fde47810e 100644 --- a/Makefile +++ b/Makefile @@ -19,21 +19,10 @@ init: ## Set up git hooks and ignored revisions ## TODO style: ## Run the code styler - @find Cabal Cabal-syntax cabal-install -name '*.hs' \ - ! -path Cabal-syntax/src/Distribution/Fields/Lexer.hs \ - ! -path Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs \ - ! -path Cabal-syntax/src/Distribution/SPDX/LicenseId.hs \ - ! -path Cabal/src/Distribution/Simple/Build/Macros/Z.hs \ - ! -path Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs \ - | xargs -P $(PROCS) -I {} fourmolu -q -i {} + @fourmolu -q -i Cabal Cabal-syntax cabal-install style-modified: ## Run the code styler on modified files @git ls-files --modified Cabal Cabal-syntax cabal-install \ - -X Cabal-syntax/src/Distribution/Fields/Lexer.hs \ - -X Cabal-syntax/src/Distribution/SPDX/LicenseExceptionId.hs \ - -X Cabal-syntax/src/Distribution/SPDX/LicenseId.hs \ - -X Cabal/src/Distribution/Simple/Build/Macros/Z.hs \ - -X Cabal/src/Distribution/Simple/Build/PathsModule/Z.hs \ | grep '.hs$$' | xargs -P $(PROCS) -I {} fourmolu -q -i {} # source generation: Lexer @@ -44,7 +33,9 @@ lexer : $(LEXER_HS) $(LEXER_HS) : templates/Lexer.x alex --latin1 --ghc -o $@ $^ - cat -s $@ > Lexer.tmp + @rm -f Lexer.tmp + echo '{- FOURMOLU_DISABLE -}' >> Lexer.tmp + cat -s $@ >> Lexer.tmp mv Lexer.tmp $@ # source generation: SPDX @@ -250,8 +241,8 @@ doc/requirements.txt: .python-sphinx-virtualenv . .python-sphinx-virtualenv/bin/activate \ && make -C doc build-and-check-requirements -ifeq ($(UNAME), Darwin) - PROCS := $(shell sysctl -n hw.logicalcpu) +ifeq ($(shell uname), Darwin) +PROCS := $(shell sysctl -n hw.logicalcpu) else - PROCS := $(shell nproc) +PROCS := $(shell nproc) endif diff --git a/cabal-dev-scripts/src/GenCabalMacros.hs b/cabal-dev-scripts/src/GenCabalMacros.hs index 3dd3be142b44bd20ea89101e66dd1d8d5af45c6b..7ca0317fbe460269a8abe285be027c9afb5b2f9f 100644 --- a/cabal-dev-scripts/src/GenCabalMacros.hs +++ b/cabal-dev-scripts/src/GenCabalMacros.hs @@ -77,7 +77,8 @@ config :: ModuleConfig Z config = ModuleConfig { mcRender = "render" , mcHeader = - [ "{-# LANGUAGE DeriveGeneric #-}" + [ "{- FOURMOLU_DISABLE -}" + , "{-# LANGUAGE DeriveGeneric #-}" , "module Distribution.Simple.Build.Macros.Z (render, Z(..), ZPackage (..), ZTool (..)) where" , "import Distribution.ZinzaPrelude" , decls diff --git a/cabal-dev-scripts/src/GenPathsModule.hs b/cabal-dev-scripts/src/GenPathsModule.hs index dfe582067f83674b214fd50f2100428411175a9b..46ef779e2aff9426dc289294206da9a2230aa3c4 100644 --- a/cabal-dev-scripts/src/GenPathsModule.hs +++ b/cabal-dev-scripts/src/GenPathsModule.hs @@ -71,7 +71,8 @@ config :: ModuleConfig Z config = ModuleConfig { mcRender = "render" , mcHeader = - [ "{-# LANGUAGE DeriveGeneric #-}" + [ "{- FOURMOLU_DISABLE -}" + , "{-# LANGUAGE DeriveGeneric #-}" , "module Distribution.Simple.Build.PathsModule.Z (render, Z(..)) where" , "import Distribution.ZinzaPrelude" , decls diff --git a/cabal-install/src/Distribution/Client/CmdHaddockProject.hs b/cabal-install/src/Distribution/Client/CmdHaddockProject.hs index e402a8db87cddda7ccb56b551547e61fe0c85c1e..d63e890a3eea5e51823fa8909d7ab187d8f3bfea 100644 --- a/cabal-install/src/Distribution/Client/CmdHaddockProject.hs +++ b/cabal-install/src/Distribution/Client/CmdHaddockProject.hs @@ -161,208 +161,216 @@ haddockProjectAction flags _extraArgs globalFlags = do -- we need. -- - withContextAndSelectors RejectNoTargets Nothing - (commandDefaultFlags CmdBuild.buildCommand) - ["all"] globalFlags HaddockCommand - $ \targetCtx ctx targetSelectors -> do - baseCtx <- case targetCtx of - ProjectContext -> return ctx - GlobalContext -> return ctx - ScriptContext path exemeta -> updateContextAndWriteProjectFile ctx path exemeta - let distLayout = distDirLayout baseCtx - cabalLayout = cabalDirLayout baseCtx - buildCtx <- - runProjectPreBuildPhase verbosity baseCtx $ \elaboratedPlan -> do - -- Interpret the targets on the command line as build targets - -- (as opposed to say repl or haddock targets). - targets <- - either reportTargetProblems return $ - resolveTargets - selectPackageTargets - selectComponentTargetBasic - elaboratedPlan - Nothing - targetSelectors - - let elaboratedPlan' = - pruneInstallPlanToTargets - TargetActionBuild - targets + withContextAndSelectors + RejectNoTargets + Nothing + (commandDefaultFlags CmdBuild.buildCommand) + ["all"] + globalFlags + HaddockCommand + $ \targetCtx ctx targetSelectors -> do + baseCtx <- case targetCtx of + ProjectContext -> return ctx + GlobalContext -> return ctx + ScriptContext path exemeta -> updateContextAndWriteProjectFile ctx path exemeta + let distLayout = distDirLayout baseCtx + cabalLayout = cabalDirLayout baseCtx + buildCtx <- + runProjectPreBuildPhase verbosity baseCtx $ \elaboratedPlan -> do + -- Interpret the targets on the command line as build targets + -- (as opposed to say repl or haddock targets). + targets <- + either reportTargetProblems return $ + resolveTargets + selectPackageTargets + selectComponentTargetBasic elaboratedPlan - return (elaboratedPlan', targets) + Nothing + targetSelectors - printPlan verbosity baseCtx buildCtx + let elaboratedPlan' = + pruneInstallPlanToTargets + TargetActionBuild + targets + elaboratedPlan + return (elaboratedPlan', targets) - let elaboratedPlan :: ElaboratedInstallPlan - elaboratedPlan = elaboratedPlanOriginal buildCtx + printPlan verbosity baseCtx buildCtx - sharedConfig :: ElaboratedSharedConfig - sharedConfig = elaboratedShared buildCtx + let elaboratedPlan :: ElaboratedInstallPlan + elaboratedPlan = elaboratedPlanOriginal buildCtx - pkgs :: [Either InstalledPackageInfo ElaboratedConfiguredPackage] - pkgs = matchingPackages elaboratedPlan + sharedConfig :: ElaboratedSharedConfig + sharedConfig = elaboratedShared buildCtx - progs <- - reconfigurePrograms - verbosity - (haddockProjectProgramPaths flags) - (haddockProjectProgramArgs flags) - -- we need to insert 'haddockProgram' before we reconfigure it, - -- otherwise 'set - . addKnownProgram haddockProgram - . pkgConfigCompilerProgs - $ sharedConfig - let sharedConfig' = sharedConfig{pkgConfigCompilerProgs = progs} + pkgs :: [Either InstalledPackageInfo ElaboratedConfiguredPackage] + pkgs = matchingPackages elaboratedPlan - _ <- - requireProgramVersion - verbosity - haddockProgram - (orLaterVersion (mkVersion [2, 26, 1])) - progs + progs <- + reconfigurePrograms + verbosity + (haddockProjectProgramPaths flags) + (haddockProjectProgramArgs flags) + -- we need to insert 'haddockProgram' before we reconfigure it, + -- otherwise 'set + . addKnownProgram haddockProgram + . pkgConfigCompilerProgs + $ sharedConfig + let sharedConfig' = sharedConfig{pkgConfigCompilerProgs = progs} - -- - -- Build project; we need to build dependencies. - -- Issue #8958. - -- - - when localStyle $ - CmdBuild.buildAction - (commandDefaultFlags CmdBuild.buildCommand) - ["all"] - globalFlags + _ <- + requireProgramVersion + verbosity + haddockProgram + (orLaterVersion (mkVersion [2, 26, 1])) + progs - -- - -- Build haddocks of each components - -- + -- + -- Build project; we need to build dependencies. + -- Issue #8958. + -- - CmdHaddock.haddockAction - nixFlags - ["all"] - globalFlags + when localStyle $ + CmdBuild.buildAction + (commandDefaultFlags CmdBuild.buildCommand) + ["all"] + globalFlags - -- - -- Copy haddocks to the destination folder - -- + -- + -- Build haddocks of each components + -- - packageInfos <- fmap (nub . concat) $ for pkgs $ \pkg -> - case pkg of - Left _ - | not localStyle -> - return [] - Left package -> do - -- TODO: this might not work for public packages with sublibraries. - -- Issue #9026. - let packageName = unPackageName (pkgName $ sourcePackageId package) - destDir = outputDir </> packageName - fmap catMaybes $ for (haddockInterfaces package) $ \interfacePath -> do - let docDir = takeDirectory interfacePath - a <- doesFileExist interfacePath - case a of - True -> - copyDirectoryRecursive verbosity docDir destDir - >> return - ( Just - ( packageName - , interfacePath - , Hidden - ) - ) - False -> return Nothing - Right package -> - case elabLocalToProject package of - True -> do - let distDirParams = elabDistDirParams sharedConfig' package - unitId = unUnitId (elabUnitId package) - buildDir = distBuildDirectory distLayout distDirParams - packageName = unPackageName (pkgName $ elabPkgSourceId package) - let docDir = - buildDir - </> "doc" - </> "html" - </> packageName - destDir = outputDir </> unitId - interfacePath = - destDir - </> packageName - <.> "haddock" - a <- doesDirectoryExist docDir - case a of - True -> - copyDirectoryRecursive verbosity docDir destDir - >> return - [ - ( unitId - , interfacePath - , Visible - ) - ] - False -> do - warn verbosity - ("haddocks of " - ++ show unitId - ++ " not found in the store") - return [] - False - | not localStyle -> - return [] - False -> do - let packageName = unPackageName (pkgName $ elabPkgSourceId package) - unitId = unUnitId (elabUnitId package) - packageDir = - storePackageDirectory - (cabalStoreDirLayout cabalLayout) - (compilerId (pkgConfigCompiler sharedConfig')) - (elabUnitId package) - docDir = packageDir </> "share" </> "doc" </> "html" - destDir = outputDir </> packageName - interfacePath = - destDir - </> packageName - <.> "haddock" - a <- doesDirectoryExist docDir + CmdHaddock.haddockAction + nixFlags + ["all"] + globalFlags + + -- + -- Copy haddocks to the destination folder + -- + + packageInfos <- fmap (nub . concat) $ for pkgs $ \pkg -> + case pkg of + Left _ + | not localStyle -> + return [] + Left package -> do + -- TODO: this might not work for public packages with sublibraries. + -- Issue #9026. + let packageName = unPackageName (pkgName $ sourcePackageId package) + destDir = outputDir </> packageName + fmap catMaybes $ for (haddockInterfaces package) $ \interfacePath -> do + let docDir = takeDirectory interfacePath + a <- doesFileExist interfacePath case a of True -> copyDirectoryRecursive verbosity docDir destDir - -- non local packages will be hidden in haddock's - -- generated contents page >> return - [ - ( unitId - , interfacePath - , Hidden - ) - ] - False -> do - warn verbosity - ("haddocks of " - ++ show unitId - ++ " not found in the store") - return [] + ( Just + ( packageName + , interfacePath + , Hidden + ) + ) + False -> return Nothing + Right package -> + case elabLocalToProject package of + True -> do + let distDirParams = elabDistDirParams sharedConfig' package + unitId = unUnitId (elabUnitId package) + buildDir = distBuildDirectory distLayout distDirParams + packageName = unPackageName (pkgName $ elabPkgSourceId package) + let docDir = + buildDir + </> "doc" + </> "html" + </> packageName + destDir = outputDir </> unitId + interfacePath = + destDir + </> packageName + <.> "haddock" + a <- doesDirectoryExist docDir + case a of + True -> + copyDirectoryRecursive verbosity docDir destDir + >> return + [ + ( unitId + , interfacePath + , Visible + ) + ] + False -> do + warn + verbosity + ( "haddocks of " + ++ show unitId + ++ " not found in the store" + ) + return [] + False + | not localStyle -> + return [] + False -> do + let packageName = unPackageName (pkgName $ elabPkgSourceId package) + unitId = unUnitId (elabUnitId package) + packageDir = + storePackageDirectory + (cabalStoreDirLayout cabalLayout) + (compilerId (pkgConfigCompiler sharedConfig')) + (elabUnitId package) + docDir = packageDir </> "share" </> "doc" </> "html" + destDir = outputDir </> packageName + interfacePath = + destDir + </> packageName + <.> "haddock" + a <- doesDirectoryExist docDir + case a of + True -> + copyDirectoryRecursive verbosity docDir destDir + -- non local packages will be hidden in haddock's + -- generated contents page + >> return + [ + ( unitId + , interfacePath + , Hidden + ) + ] + False -> do + warn + verbosity + ( "haddocks of " + ++ show unitId + ++ " not found in the store" + ) + return [] - -- - -- generate index, content, etc. - -- + -- + -- generate index, content, etc. + -- - let flags' = - flags - { haddockProjectDir = Flag outputDir - , haddockProjectInterfaces = - Flag - [ ( interfacePath - , Just name - , Just name - , visibility - ) - | (name, interfacePath, visibility) <- packageInfos - ] - } - createHaddockIndex - verbosity - (pkgConfigCompilerProgs sharedConfig') - (pkgConfigCompiler sharedConfig') - (pkgConfigPlatform sharedConfig') - flags' + let flags' = + flags + { haddockProjectDir = Flag outputDir + , haddockProjectInterfaces = + Flag + [ ( interfacePath + , Just name + , Just name + , visibility + ) + | (name, interfacePath, visibility) <- packageInfos + ] + } + createHaddockIndex + verbosity + (pkgConfigCompilerProgs sharedConfig') + (pkgConfigCompiler sharedConfig') + (pkgConfigPlatform sharedConfig') + flags' where verbosity = fromFlagOrDefault normal (haddockProjectVerbosity flags) diff --git a/cabal-install/tests/UnitTests/Distribution/Client/FetchUtils.hs b/cabal-install/tests/UnitTests/Distribution/Client/FetchUtils.hs index 76bd1d94d52065c4e5d6f96f8e4d5efd2ecff899..4131f01a70c9ae2ca423d56fbd963ea98667b45c 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/FetchUtils.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/FetchUtils.hs @@ -16,12 +16,12 @@ import Distribution.Client.Types.Repo (Repo (..), emptyRemoteRepo) import Distribution.Client.Types.RepoName (RepoName (..)) import Distribution.Types.PackageId (PackageIdentifier (..)) import Distribution.Types.PackageName (mkPackageName) +import Distribution.Utils.TempTestDir (withTestDir) import qualified Distribution.Verbosity as Verbosity import Distribution.Version (mkVersion) import Network.URI (URI, uriPath) import Test.Tasty import Test.Tasty.HUnit -import Distribution.Utils.TempTestDir (withTestDir) tests :: [TestTree] tests = diff --git a/cabal-install/tests/UnitTests/Distribution/Client/Get.hs b/cabal-install/tests/UnitTests/Distribution/Client/Get.hs index 88b794d7c4c1aa42259d3f810cbc1d33a7129e53..fadca21d0cb95721140f13c18e0d45c9084367ab 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/Get.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/Get.hs @@ -20,10 +20,10 @@ import System.Exit import System.FilePath import System.IO.Error +import Distribution.Utils.TempTestDir (withTestDir) import Test.Tasty import Test.Tasty.HUnit import UnitTests.Options (RunNetworkTests (..)) -import Distribution.Utils.TempTestDir (withTestDir) tests :: [TestTree] tests = diff --git a/fourmolu.yaml b/fourmolu.yaml index 6ba33930bd5f1f18b9f1cc5eb55d572b3d3983a4..acd4a16632815ef05856e4fe57adbb2fdb54e5b6 100644 --- a/fourmolu.yaml +++ b/fourmolu.yaml @@ -7,8 +7,21 @@ respectful: true # don't be too opinionated about newlines etc. haddock-style: single-line # '--' vs. '{-' haddock-style-module: single-line newlines-between-decls: 1 # number of newlines between top-level declarations -fixities: [] function-arrows: leading single-constraint-parens: never in-style: right-align let-style: auto + +fixities: + # Distribution.Compat.Parsing + - infixr 0 <?> + # Distribution.FieldGrammar + - infixl 5 ^^^ + # Distribution.Types.InstalledPackageInfo.FieldGrammar + - infixl 4 <@> + +reexports: + - module Distribution.Client.Compat.Prelude exports Distribution.Compat.Prelude.Internal + - module Distribution.Compat.Prelude.Internal exports Distribution.Compat.Prelude + - module Distribution.Compat.Prelude exports Prelude + - module Distribution.Compat.Prelude exports Control.Applicative diff --git a/templates/SPDX.LicenseExceptionId.template.hs b/templates/SPDX.LicenseExceptionId.template.hs index d18641c3768fa87be312efba782d0dbbf45a9b2e..5881bec600b4f9179cc2e63e92353fc6bcebe569 100644 --- a/templates/SPDX.LicenseExceptionId.template.hs +++ b/templates/SPDX.LicenseExceptionId.template.hs @@ -1,3 +1,4 @@ +{- FOURMOLU_DISABLE -} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} module Distribution.SPDX.LicenseExceptionId ( diff --git a/templates/SPDX.LicenseId.template.hs b/templates/SPDX.LicenseId.template.hs index 9aa5d2c1737b6ceb6cf2be9d7fde6e09d594ca96..648625271f6743cb27aa3f2ee62ef31c8ce80841 100644 --- a/templates/SPDX.LicenseId.template.hs +++ b/templates/SPDX.LicenseId.template.hs @@ -1,3 +1,4 @@ +{- FOURMOLU_DISABLE -} {-# LANGUAGE DeriveDataTypeable #-} module Distribution.SPDX.LicenseId ( LicenseId (..),