Skip to content

Commit ac27be9

Browse files
committed
Resolve proper version specifiers for haskell dependencies
1 parent 26c5f7a commit ac27be9

File tree

13 files changed

+291
-160
lines changed

13 files changed

+291
-160
lines changed

.last-exported-commit

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
Last exported commit from parent repo: b4a296093f5e7ee90367d58a20e8c4c67d8f7e64
1+
Last exported commit from parent repo: 184e5869a6f7c79f4adaca446e08f30371aa3946

nix-bootstrap.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ library
5858
Bootstrap.Data.ContinuousIntegration
5959
Bootstrap.Data.DevContainer
6060
Bootstrap.Data.GHCVersion
61+
Bootstrap.Data.HaskellDependency
6162
Bootstrap.Data.HList
6263
Bootstrap.Data.PreCommitHook
6364
Bootstrap.Data.ProjectName
@@ -71,6 +72,7 @@ library
7172
Bootstrap.Nix.Evaluate
7273
Bootstrap.Nix.Expr
7374
Bootstrap.Nix.Expr.BuildInputs
75+
Bootstrap.Nix.Expr.Haskell
7476
Bootstrap.Nix.Expr.MkShell
7577
Bootstrap.Nix.Expr.Nixpkgs
7678
Bootstrap.Nix.Expr.PreCommitHooks
@@ -181,7 +183,6 @@ test-suite nix-bootstrap-test
181183
Bootstrap.Data.Bootstrappable.Go.ModfileSpec
182184
Bootstrap.Data.Bootstrappable.Haskell.LibHsSpec
183185
Bootstrap.Data.Bootstrappable.Haskell.MainHsSpec
184-
Bootstrap.Data.Bootstrappable.Haskell.PackageYamlSpec
185186
Bootstrap.Data.Bootstrappable.Haskell.PreludeHsSpec
186187
Bootstrap.Data.Bootstrappable.NixPreCommitHookConfigSpec
187188
Bootstrap.Data.Bootstrappable.NixShellCompatSpec

src/Bootstrap.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -516,7 +516,7 @@ makeBuildPlan MakeBuildPlanArgs {..} = do
516516
~: elmPackageJsonFor mbpProjectType
517517
~: elmIndexHtmlFor mbpProjectName mbpProjectType
518518
~: elmIndexJsFor mbpProjectType
519-
~: packageYamlFor mbpProjectType mbpProjectName
519+
~: packageYamlFor mbpNixBinaryPaths mbpRunConfig mbpProjectName mbpProjectType
520520
~: preludeHsFor mbpProjectType
521521
~: libHsFor mbpProjectType
522522
~: mainHsFor mbpProjectType

src/Bootstrap/Data/Bootstrappable/Haskell/PackageYaml.hs

Lines changed: 33 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,50 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE TemplateHaskell #-}
3+
14
-- | Copyright : (c) Crown Copyright GCHQ
25
module Bootstrap.Data.Bootstrappable.Haskell.PackageYaml
36
( PackageYaml,
47
packageYamlFor,
58
)
69
where
710

11+
import Bootstrap.Cli (RunConfig)
812
import Bootstrap.Data.Bootstrappable
913
( Bootstrappable (bootstrapContent, bootstrapName, bootstrapReason),
1014
bootstrapContentYaml,
1115
)
16+
import Bootstrap.Data.HaskellDependency
17+
( HaskellDependency,
18+
VersionKnown (VersionKnown),
19+
getHaskellDependencyVersions,
20+
hdep,
21+
)
1222
import Bootstrap.Data.ProjectName (ProjectName (unProjectName))
13-
import Bootstrap.Data.ProjectType (HaskellOptions (HaskellOptions), HaskellProjectType (HaskellProjectTypeBasic, HaskellProjectTypeReplOnly), ProjectType (Haskell))
23+
import Bootstrap.Data.ProjectType (HaskellOptions (HaskellOptions, haskellOptionsHaskellProjectType), HaskellProjectType (HaskellProjectTypeBasic, HaskellProjectTypeReplOnly), ProjectType (Haskell))
24+
import Bootstrap.Nix.Evaluate (NixBinaryPaths)
1425
import Data.Aeson (ToJSON (toJSON))
1526
import qualified Data.Aeson as Aeson
27+
import Relude.Extra.Bifunctor (firstF)
1628

1729
-- | The haskell project's package.yaml
18-
newtype PackageYaml = PackageYaml ProjectName
30+
data PackageYaml = PackageYaml NixBinaryPaths RunConfig ProjectName HaskellOptions
1931

2032
instance Bootstrappable PackageYaml where
2133
bootstrapName = const "package.yaml"
2234
bootstrapReason = const "The configuration of your haskell project"
23-
bootstrapContent = pure . pure . bootstrapContentYaml
35+
bootstrapContent (PackageYaml nbps rc n opts@HaskellOptions {haskellOptionsHaskellProjectType}) = runExceptT do
36+
dependencies <- ExceptT
37+
. firstF (("Could not get haskell dependency versions: " <>) . displayException)
38+
. getHaskellDependencyVersions nbps rc opts
39+
$ case haskellOptionsHaskellProjectType of
40+
HaskellProjectTypeReplOnly -> []
41+
HaskellProjectTypeBasic -> [$(hdep "base"), $(hdep "relude")]
42+
pure . bootstrapContentYaml $ PackageYamlWithDependencies n dependencies
2443

25-
instance ToJSON PackageYaml where
26-
toJSON (PackageYaml n) =
44+
data PackageYamlWithDependencies = PackageYamlWithDependencies ProjectName [HaskellDependency 'VersionKnown]
45+
46+
instance ToJSON PackageYamlWithDependencies where
47+
toJSON (PackageYamlWithDependencies n deps) =
2748
Aeson.object
2849
[ ("name", Aeson.String $ unProjectName n),
2950
("version", "0.1.0.0"),
@@ -41,14 +62,7 @@ instance ToJSON PackageYaml where
4162
]
4263
),
4364
( "dependencies",
44-
Aeson.Array $
45-
fromList
46-
[ Aeson.object
47-
[ ("name", "base"),
48-
("mixin", Aeson.Array $ fromList ["hiding (Prelude)"])
49-
],
50-
"relude"
51-
]
65+
Aeson.Array . fromList $ toJSON <$> deps
5266
),
5367
( "flags",
5468
Aeson.object
@@ -110,9 +124,9 @@ instance ToJSON PackageYaml where
110124
)
111125
]
112126

113-
packageYamlFor :: ProjectType -> ProjectName -> Maybe PackageYaml
114-
packageYamlFor = \case
115-
Haskell (HaskellOptions _ haskellProjectType) -> case haskellProjectType of
116-
HaskellProjectTypeReplOnly -> const Nothing
117-
HaskellProjectTypeBasic -> Just . PackageYaml
118-
_ -> const Nothing
127+
packageYamlFor :: NixBinaryPaths -> RunConfig -> ProjectName -> ProjectType -> Maybe PackageYaml
128+
packageYamlFor nbps rc projectName = \case
129+
Haskell haskellOptions@(HaskellOptions _ haskellProjectType) -> case haskellProjectType of
130+
HaskellProjectTypeReplOnly -> Nothing
131+
HaskellProjectTypeBasic -> Just $ PackageYaml nbps rc projectName haskellOptions
132+
_ -> Nothing

src/Bootstrap/Data/Bootstrappable/NixShell.hs

Lines changed: 4 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,6 @@ import Bootstrap.Data.Bootstrappable
2323
import Bootstrap.Data.Bootstrappable.NixPreCommitHookConfig
2424
( NixPreCommitHookConfig (nixPreCommitHookConfigRequiresNixpkgs),
2525
)
26-
import Bootstrap.Data.GHCVersion (ghcVersionAttributeName)
2726
import Bootstrap.Data.PreCommitHook (PreCommitHooksConfig (unPreCommitHooksConfig))
2827
import Bootstrap.Data.ProjectType
2928
( ElmMode (ElmModeBare, ElmModeNode),
@@ -37,20 +36,18 @@ import Bootstrap.Data.ProjectType
3736
)
3837
import Bootstrap.Nix.Expr
3938
( Binding,
40-
Expr (EApplication, EFunc, EGrouping, EIdent, ELetIn, EList, ELit, EPropertyAccess, EWith),
39+
Expr (EApplication, EFunc, EGrouping, EIdent, ELetIn, EList, EPropertyAccess, EWith),
4140
Identifier,
4241
IsNixExpr (toNixExpr),
43-
Literal (LString),
4442
nix,
4543
nixargs,
4644
nixbinding,
4745
nixident,
4846
nixproperty,
49-
(|*),
50-
(|.),
5147
(|=),
5248
)
5349
import Bootstrap.Nix.Expr.BuildInputs (BuildInputSpec (bisOtherPackages))
50+
import Bootstrap.Nix.Expr.Haskell (haskellPackagesExpr)
5451
import Bootstrap.Nix.Expr.MkShell
5552
( BuildInputSpec
5653
( BuildInputSpec,
@@ -103,11 +100,9 @@ nixShellFor RunConfig {rcUseFlakes} projectType preCommitHooksConfig nixPreCommi
103100
where
104101
extraBindingsFor :: ProjectType -> [(Bool, Binding)]
105102
extraBindingsFor = \case
106-
Haskell (HaskellOptions ghcVersion haskellProjectType) ->
103+
Haskell haskellOptions@(HaskellOptions _ haskellProjectType) ->
107104
(True,)
108-
<$> [ [nixproperty|ghcAttribute|] |= ELit (LString $ ghcVersionAttributeName ghcVersion),
109-
[nixproperty|haskellPackages|]
110-
|= applyOverridesFunc haskellProjectType [nix|nixpkgs.haskell.packages.${ghcAttribute}|],
105+
<$> [ [nixproperty|haskellPackages|] |= haskellPackagesExpr haskellOptions,
111106
[nixproperty|haskellEnv|]
112107
|= ghcWithPackages
113108
( case haskellProjectType of
@@ -118,18 +113,6 @@ nixShellFor RunConfig {rcUseFlakes} projectType preCommitHooksConfig nixPreCommi
118113
Python _ -> (False,) <$> (machNixLegacyNixBinding : one (pythonPackagesBinding False))
119114
_ -> []
120115
where
121-
applyOverridesFunc :: HaskellProjectType -> Expr -> Expr
122-
applyOverridesFunc = \case
123-
HaskellProjectTypeReplOnly -> id
124-
HaskellProjectTypeBasic -> \e ->
125-
(e |. [nixproperty|override|])
126-
|* [nix|{
127-
overrides = _: super: {
128-
# The line below may be needed to circumvent a bug in nixpkgs.
129-
# If the devshell builds successfully without it, feel free to remove it.
130-
pretty-simple = super.pretty-simple.overrideAttrs { doCheck = false; };
131-
};
132-
}|]
133116
ghcWithPackages :: [Identifier] -> Expr
134117
ghcWithPackages =
135118
EApplication [nix|haskellPackages.ghcWithPackages|]

src/Bootstrap/Data/GHCVersion.hs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,14 @@ module Bootstrap.Data.GHCVersion
1313
parseGHCVersion,
1414

1515
-- * Formatting
16-
ghcVersionAttributeName,
1716
printGHCVersion,
17+
18+
-- * Use in Nix expressions
19+
ghcVersionProperty,
1820
)
1921
where
2022

23+
import Bootstrap.Nix.Expr (Identifier (Identifier), Property (PIdent))
2124
import qualified Data.Char as C
2225
import qualified Data.Text as T
2326
import Dhall (FromDhall, ToDhall)
@@ -46,11 +49,9 @@ data GHCVersion = GHCVersion
4649
deriving stock (Eq, Generic, Ord, Show)
4750
deriving (FromDhall, ToDhall) via Codec (Field (CamelCase <<< DropPrefix "ghcVersion")) GHCVersion
4851

49-
-- | Gets the attribute name of the GHC version.
50-
--
51-
-- Result should always succeed when parsed by `parseGHCVersion`.
52-
ghcVersionAttributeName :: GHCVersion -> Text
53-
ghcVersionAttributeName = ("ghc" <>) . T.filter (/= '.') . printGHCVersion
52+
-- | Gets the attribute name of the GHC version, able to be queried in nixpkgs
53+
ghcVersionProperty :: GHCVersion -> Property
54+
ghcVersionProperty = PIdent . Identifier . ("ghc" <>) . T.filter (/= '.') . printGHCVersion
5455

5556
-- | Parses a nixpkgs attribute representing a GHC version
5657
--
Lines changed: 172 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,172 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE FlexibleInstances #-}
3+
{-# LANGUAGE KindSignatures #-}
4+
{-# LANGUAGE QuasiQuotes #-}
5+
{-# LANGUAGE TemplateHaskellQuotes #-}
6+
7+
-- | Copyright : (c) Crown Copyright GCHQ
8+
-- Description : Represent dependencies of haskell projects
9+
module Bootstrap.Data.HaskellDependency
10+
( HaskellDependency,
11+
VersionKnown (..),
12+
getHaskellDependencyVersions,
13+
hdep,
14+
)
15+
where
16+
17+
import Bootstrap.Cli (RunConfig)
18+
import Bootstrap.Data.ProjectType (HaskellOptions)
19+
import Bootstrap.Nix.Evaluate
20+
( NixBinaryPaths,
21+
evaluateNixExpression,
22+
extractNixVersionString,
23+
)
24+
import Bootstrap.Nix.Expr
25+
( Expr (EGrouping, ELetIn),
26+
Identifier (Identifier),
27+
Property (PIdent),
28+
nixproperty,
29+
(|.),
30+
(|=),
31+
)
32+
import Bootstrap.Nix.Expr.Haskell (haskellPackagesExpr)
33+
import Bootstrap.Nix.Expr.Nixpkgs (nixpkgsExpr)
34+
import Control.Exception (IOException)
35+
import Data.Aeson (ToJSON (toJSON))
36+
import qualified Data.Aeson as Aeson
37+
import Language.Haskell.TH (ExpQ)
38+
import qualified Relude.Extra.Map as M
39+
40+
-- | Whether the version of a particular dependency is known
41+
data VersionKnown = VersionKnown | VersionUnknown
42+
43+
-- | Represents a library on which a haskell project depends
44+
data HaskellDependency (versionKnown :: VersionKnown) where
45+
HaskellDependencyBase :: HaskellDependency versionKnown
46+
HaskellDependencyBoot :: Text -> HaskellDependency versionKnown
47+
HaskellDependencyVersioned ::
48+
Text ->
49+
HaskellDependencyVersion versionKnown ->
50+
HaskellDependency versionKnown
51+
52+
instance ToJSON (HaskellDependency 'VersionKnown) where
53+
toJSON = \case
54+
HaskellDependencyBase ->
55+
Aeson.object
56+
[ ("name", "base"),
57+
("mixin", Aeson.Array $ fromList ["hiding (Prelude)"])
58+
]
59+
HaskellDependencyBoot d -> Aeson.String d
60+
HaskellDependencyVersioned d (HaskellDependencyVersionExact v) ->
61+
Aeson.String $
62+
d <> " == " <> v
63+
64+
data HaskellDependencyVersion (versionKnown :: VersionKnown) where
65+
HaskellDependencyVersionUnknown :: HaskellDependencyVersion 'VersionUnknown
66+
HaskellDependencyVersionExact :: Text -> HaskellDependencyVersion 'VersionKnown
67+
68+
dependencies :: Map Text (HaskellDependency 'VersionUnknown)
69+
dependencies =
70+
fromList
71+
[ ("base", HaskellDependencyBase),
72+
hDepBoot "Cabal",
73+
hDepBoot "Cabal-syntax",
74+
hDepBoot "Win32",
75+
hDepBoot "array",
76+
hDepBoot "bin-package-db",
77+
hDepBoot "binary",
78+
hDepBoot "bytestring",
79+
hDepBoot "containers",
80+
hDepBoot "deepseq",
81+
hDepBoot "directory",
82+
hDepBoot "exceptions",
83+
hDepBoot "extensible-exceptions",
84+
hDepBoot "ffi",
85+
hDepBoot "filepath",
86+
hDepBoot "ghc",
87+
hDepBoot "ghc-bignum",
88+
hDepBoot "ghc-binary",
89+
hDepBoot "ghc-boot",
90+
hDepBoot "ghc-boot-th",
91+
hDepBoot "ghc-compact",
92+
hDepBoot "ghc-heap",
93+
hDepBoot "ghc-prim",
94+
hDepBoot "ghci",
95+
hDepBoot "haskeline",
96+
hDepBoot "haskell2010",
97+
hDepBoot "haskell98",
98+
hDepBoot "hoopl",
99+
hDepBoot "hpc",
100+
hDepBoot "integer-gmp",
101+
hDepBoot "libiserv",
102+
hDepBoot "mtl",
103+
hDepBoot "old-locale",
104+
hDepBoot "old-time",
105+
hDepBoot "parsec",
106+
hDepBoot "pretty",
107+
hDepBoot "process",
108+
hDepBoot "random",
109+
hDepBoot "rts",
110+
hDepBoot "stm",
111+
hDepBoot "system-cxx-std-lib",
112+
hDepBoot "template-haskell",
113+
hDepBoot "terminfo",
114+
hDepBoot "text",
115+
hDepBoot "time",
116+
hDepBoot "transformers",
117+
hDepBoot "unix",
118+
hDepBoot "xhtml",
119+
hDepUnknown "relude"
120+
]
121+
where
122+
hDepBoot :: Text -> (Text, HaskellDependency 'VersionUnknown)
123+
hDepBoot name = (name, HaskellDependencyBoot name)
124+
hDepUnknown :: Text -> (Text, HaskellDependency 'VersionUnknown)
125+
hDepUnknown name = (name, HaskellDependencyVersioned name HaskellDependencyVersionUnknown)
126+
127+
-- | Get a `HaskellDependency 'VersionUnknown` for the given dependency name
128+
hdep :: Text -> ExpQ
129+
hdep name = case M.lookup name dependencies of
130+
Just dep -> case dep of
131+
HaskellDependencyBase -> [|HaskellDependencyBase|]
132+
HaskellDependencyBoot _ ->
133+
[|HaskellDependencyBoot name|]
134+
HaskellDependencyVersioned _ HaskellDependencyVersionUnknown ->
135+
[|HaskellDependencyVersioned name HaskellDependencyVersionUnknown|]
136+
Nothing -> error $ "Could not find " <> name <> " in dependency map in Bootstrap.Data.HaskellDependency"
137+
138+
getHaskellDependencyVersions ::
139+
MonadIO m =>
140+
NixBinaryPaths ->
141+
RunConfig ->
142+
HaskellOptions ->
143+
[HaskellDependency 'VersionUnknown] ->
144+
m (Either IOException [HaskellDependency 'VersionKnown])
145+
getHaskellDependencyVersions nixBinaryPaths rc haskellOptions deps = do
146+
results <- forM deps \case
147+
HaskellDependencyBase -> pure $ Right HaskellDependencyBase
148+
HaskellDependencyBoot d -> pure . Right $ HaskellDependencyBoot d
149+
HaskellDependencyVersioned d HaskellDependencyVersionUnknown -> do
150+
evaluateNixExpression
151+
nixBinaryPaths
152+
rc
153+
( ELetIn
154+
(one $ [nixproperty|nixpkgs|] |= nixpkgsExpr rc)
155+
( EGrouping (haskellPackagesExpr haskellOptions)
156+
|. PIdent (Identifier d)
157+
|. [nixproperty|version|]
158+
)
159+
)
160+
<&> fmap
161+
( HaskellDependencyVersioned d
162+
. HaskellDependencyVersionExact
163+
. toText
164+
. extractNixVersionString
165+
)
166+
pure $ foldr throwAnyErrors (Right []) results
167+
where
168+
-- If we hit any errors, fail the whole thing
169+
throwAnyErrors _ e@(Left _) = e
170+
throwAnyErrors (Left e) _ = Left e
171+
-- Keep building up the accumulator as long as we're succeeding
172+
throwAnyErrors (Right next) (Right acc) = Right (next : acc)

0 commit comments

Comments
 (0)