Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
H
head.hackage
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
Alex Biehl
head.hackage
Commits
32401f52
Commit
32401f52
authored
6 years ago
by
Kosyrev Serge
Browse files
Options
Downloads
Patches
Plain Diff
generate-nix-overrides.hs: properly handle cases when both .cabal and .patch are present
parent
ef867aad
No related branches found
Branches containing commit
No related tags found
No related merge requests found
Changes
1
Hide whitespace changes
Inline
Side-by-side
Showing
1 changed file
scripts/generate-nix-overrides.hs
+25
-13
25 additions, 13 deletions
scripts/generate-nix-overrides.hs
with
25 additions
and
13 deletions
scripts/generate-nix-overrides.hs
+
25
−
13
View file @
32401f52
#!
/
usr
/
bin
/
env
nix
-
shell
#!
nix
-
shell
-
i
runghc
-
p
"haskellPackages.ghcWithPackages (ps: [])"
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
import
Data.List
import
Distribution.Package
...
...
@@ -19,7 +22,8 @@ groupPatches assocs = Map.toAscList $ Map.fromListWith (++) [(k, [v]) | (k, v) <
generateOverrides
::
FilePath
->
FilePath
->
IO
String
generateOverrides
prefix
patchDir
=
do
patches
<-
listDirectory
patchDir
override_groups
<-
groupPatches
<$>
mapM
(
generateOverride
prefix
patchDir
)
patches
override_groups
<-
groupPatches
<$>
mapM
(
generateOverride
prefix
patchDir
)
(
groupPatches
[
(
dropExtension
pf
,
decidePatchType
pf
)
|
pf
<-
patches
])
let
overrides
=
map
mkOverride
override_groups
return
$
intercalate
"
\n
"
overrides
...
...
@@ -39,30 +43,38 @@ mkOverride (display -> pName, patches) =
,
quotes
(
intercalate
"."
(
map
show
version
))
,
" then ("
,
patch
,
")"
]
override
::
FilePath
->
FilePath
->
FilePath
->
String
->
PatchType
->
String
override
prefix
patchDir
extlessPath
nixexpr
ptype
=
unwords
[
"("
,
patchFunction
ptype
,
nixexpr
,
prefix
</>
patchDir
</>
addExtension
extlessPath
(
patchTypeExt
ptype
),
")"
]
generateOverride
::
FilePath
->
FilePath
->
FilePath
->
IO
(
PackageName
,
([
Int
],
String
))
generateOverride
prefix
patchDir
patch
=
do
let
ftype
=
decidePatchType
patch
pid'
::
Maybe
PackageId
=
simpleParse
(
takeBaseName
patch
)
pid
<-
maybe
(
fail
(
"invalid patch file name: "
++
show
patch
))
return
pid'
generateOverride
::
FilePath
->
FilePath
->
(
FilePath
,
[
PatchType
])
->
IO
(
PackageName
,
([
Int
],
String
))
generateOverride
prefix
patchDir
(
patchExtless
,
patchTypes
)
=
do
let
pid'
::
Maybe
PackageId
=
simpleParse
(
takeFileName
patchExtless
)
pid
<-
maybe
(
fail
(
"invalid patch file name: "
++
show
patchExtless
))
return
pid'
let
pname
=
display
(
packageName
pid
)
version
=
versionNumbers
(
packageVersion
pid
)
return
$
(
packageName
pid
,
(
version
,
unwords
[
"dontRevise
("
,
patchFunction
ftype
,
"super."
++
pname
,
prefix
</>
patchDir
</>
patch
,
")"
]))
return
.
(
packageName
pid
,
)
.
(
version
,
)
$
"dontRevise
"
++
foldl'
(
override
prefix
patchDir
patchExtless
)
(
"super."
++
pname
)
patchTypes
patchFunction
::
PatchType
->
String
patchFunction
CabalPatch
=
"setCabalFile"
patchFunction
NormalPatch
=
"haskell.lib.appendPatch"
patchFunction
=
\
case
CabalPatch
->
"setCabalFile"
NormalPatch
->
"haskell.lib.appendPatch"
patchTypeExt
::
PatchType
->
String
patchTypeExt
=
\
case
CabalPatch
->
".cabal"
NormalPatch
->
".patch"
decidePatchType
::
FilePath
->
PatchType
decidePatchType
patch
=
case
takeExtension
patch
of
".cabal"
->
CabalPatch
_
->
NormalPatch
".patch"
->
NormalPatch
_
->
error
$
"Unexpected patch extension: "
++
patch
data
PatchType
=
CabalPatch
|
NormalPatch
data
PatchType
=
CabalPatch
|
NormalPatch
deriving
Eq
main
::
IO
()
main
=
do
...
...
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment