Skip to content
Snippets Groups Projects
Unverified Commit 6401689d authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling:
Browse files

Migrate v3 singletons-base

parent e0a63d1d
No related branches found
No related tags found
1 merge request!23Wip/romes/migration v2 + v3
......@@ -144,12 +144,15 @@ index c968978..0000000
- condTree' = condTree { condTreeData = testSuite' }
diff --git a/SetupHooks.hs b/SetupHooks.hs
new file mode 100644
index 0000000..8119872
index 0000000..016435a
--- /dev/null
+++ b/SetupHooks.hs
@@ -0,0 +1,114 @@
@@ -0,0 +1,108 @@
+{-# OPTIONS_GHC -Wall #-}
+{-# LANGUAGE DisambiguateRecordFields #-}
+{-# LANGUAGE StaticPointers #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedLists #-}
+module SetupHooks (setupHooks) where
+
+import Distribution.PackageDescription
......@@ -159,6 +162,7 @@ index 0000000..8119872
+import Distribution.Simple.Program
+import Distribution.Simple.SetupHooks
+import Distribution.Simple.Utils
+import Distribution.Utils.Path (getSymbolicPath)
+import Distribution.Text
+
+import System.Directory
......@@ -169,39 +173,29 @@ index 0000000..8119872
+ noSetupHooks
+ { buildHooks =
+ noBuildHooks
+ { preBuildComponentRules = fromRulesM $ RulesM $
+ \PreBuildComponentInputs{buildingWhat=flags, localBuildInfo=lbi, targetInfo=tgt} ->
+ { preBuildComponentRules = Just $ rules $ static
+ (\PreBuildComponentInputs{buildingWhat=flags, localBuildInfo=lbi, targetInfo=tgt} ->
+ case targetComponent tgt of
+ CTest suite
+ | unUnqualComponentName (testName suite) == testSuiteName
+ -> do
+ actId <- registerAction $ Action $ \_deps resolve -> do
+ generateBuildModule flags (localPkgDescr lbi) lbi
+ (targetCLBI tgt) (resolveLocation resolve SrcFile)
+ return $ do
+ _ <- registerRule $
+ Rule
+ { unresolvedDependencies = []
+ , monitoredValue = Nothing
+ , monitoredDirs = []
+ , results = [(SrcFile, buildSingletonsBaseModule <.> "hs")]
+ , actionId = actId
+ }
+ return ()
+ _ -> return . return $ ()
+ let
+ autogend = getSymbolicPath $ autogenComponentModulesDir lbi (targetCLBI tgt)
+ cmd = mkCommand (static Dict) (static generateBuildModule) (flags, lbi, autogend)
+ registerRule_ "build-module" $
+ staticRule cmd [] [(autogend, buildSingletonsBaseModule <.> "hs")]
+ _ -> return ())
+ }
+ }
+
+generateBuildModule
+ :: BuildingWhat -> PackageDescription -> LocalBuildInfo
+ -> ComponentLocalBuildInfo
+ -> FilePath
+ -- ^ Autogen dir
+ :: (BuildingWhat, LocalBuildInfo, FilePath {- Autogen dir -})
+ -> IO ()
+generateBuildModule flags pkg lbi _suitecfg testAutogenDir = do
+generateBuildModule (flags, lbi, testAutogenDir) = do
+ let pkg = localPkgDescr lbi
+ rootDir <- getCurrentDirectory
+ let verbosity = buildingWhatVerbosity flags
+ distPref = buildingWhatDistPref flags
+ distPref = getSymbolicPath $ buildingWhatDistPref flags
+ distPref' | isRelative distPref = rootDir </> distPref
+ | otherwise = distPref
+ -- Package DBs
......@@ -263,11 +257,11 @@ index 0000000..8119872
+testSuiteName :: String
+testSuiteName = "singletons-base-test-suite"
diff --git a/singletons-base.cabal b/singletons-base.cabal
index 18c562c..564cdcf 100644
index 18c562c..a88dca5 100644
--- a/singletons-base.cabal
+++ b/singletons-base.cabal
@@ -1,6 +1,6 @@
+cabal-version: 3.0
+cabal-version: 3.12
name: singletons-base
version: 3.2
-cabal-version: 1.24
......@@ -292,7 +286,7 @@ index 18c562c..564cdcf 100644
description:
@singletons-base@ uses @singletons-th@ to define promoted and singled
functions from the @base@ library, including the "Prelude". This library was
@@ -65,8 +65,8 @@ source-repository head
@@ -65,20 +65,21 @@ source-repository head
custom-setup
setup-depends:
......@@ -300,10 +294,27 @@ index 18c562c..564cdcf 100644
- Cabal >= 3.0 && < 3.11,
+ base >= 4.18 && < 4.20,
+ Cabal >= 3.0 && < 3.12,
+ Cabal-hooks,
directory >= 1,
filepath >= 1.3
@@ -153,7 +153,9 @@ test-suite singletons-base-test-suite
library
hs-source-dirs: src
- build-depends: base >= 4.18 && < 4.19,
+ build-depends: base >= 4.18 && < 4.20,
pretty,
singletons == 3.0.*,
- singletons-th >= 3.2 && < 3.3,
- template-haskell >= 2.20 && < 2.21,
+ singletons-th >= 3.2 && < 3.5,
+ template-haskell >= 2.20 && < 2.23,
text >= 1.2,
- th-desugar >= 1.15 && < 1.16
+ th-desugar >= 1.15 && < 1.18
default-language: GHC2021
other-extensions: TemplateHaskell
exposed-modules: Data.Singletons.Base.CustomStar
@@ -153,7 +154,9 @@ test-suite singletons-base-test-suite
ghc-options: -Wall -Wcompat -threaded -with-rtsopts=-maxN16
default-language: GHC2021
main-is: SingletonsBaseTestSuite.hs
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment