Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
G
ghcup-hs
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Iterations
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
Haskell
ghcup-hs
Merge requests
!211
Refactor main
Code
Review changes
Check out branch
Download
Patches
Plain diff
Closed
Refactor main
refactor-mainn
into
master
Overview
0
Commits
2
Pipelines
0
Changes
20
Closed
Julian Ospald
requested to merge
refactor-mainn
into
master
3 years ago
Overview
0
Commits
2
Pipelines
0
Changes
20
Expand
0
0
Merge request reports
Compare
master
version 2
e88e131b
3 years ago
version 1
e88e131b
3 years ago
master (base)
and
latest version
latest version
e88e131b
2 commits,
3 years ago
version 2
e88e131b
3 commits,
3 years ago
version 1
e88e131b
2 commits,
3 years ago
20 files
+
4374
−
2838
Inline
Compare changes
Side-by-side
Inline
Show whitespace changes
Show one file at a time
Files
20
Search (e.g. *.vue) (Ctrl+P)
app/ghcup/GHCup/OptParse/ChangeLog.hs
0 → 100644
+
151
−
0
Options
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE RankNTypes #-}
module
GHCup.OptParse.ChangeLog
where
import
GHCup.Types
import
GHCup.Utils.Logger
import
GHCup.OptParse.Common
import
GHCup.Utils.String.QQ
#
if
!
MIN_VERSION_base
(
4
,
13
,
0
)
import
Control.Monad.Fail
(
MonadFail
)
#
endif
import
Control.Monad.Reader
import
Control.Monad.Trans.Resource
import
Data.Functor
import
Data.Maybe
import
Options.Applicative
hiding
(
style
)
import
Prelude
hiding
(
appendFile
)
import
System.Exit
import
Text.PrettyPrint.HughesPJClass
(
prettyShow
)
import
qualified
Data.Text
as
T
import
Control.Exception.Safe
(
MonadMask
)
import
GHCup.Types.Optics
import
GHCup.Utils
import
Data.Versions
import
URI.ByteString
(
serializeURIRef'
)
import
GHCup.Utils.Prelude
import
GHCup.Utils.File
(
exec
)
import
Data.Char
(
toLower
)
---------------
--[ Options ]--
---------------
data
ChangeLogOptions
=
ChangeLogOptions
{
clOpen
::
Bool
,
clTool
::
Maybe
Tool
,
clToolVer
::
Maybe
ToolVersion
}
---------------
--[ Parsers ]--
---------------
changelogP
::
Parser
ChangeLogOptions
changelogP
=
(
\
x
y
->
ChangeLogOptions
x
y
)
<$>
switch
(
short
'o'
<>
long
"open"
<>
help
"xdg-open the changelog url"
)
<*>
optional
(
option
(
eitherReader
(
\
s'
->
case
fmap
toLower
s'
of
"ghc"
->
Right
GHC
"cabal"
->
Right
Cabal
"ghcup"
->
Right
GHCup
"stack"
->
Right
Stack
e
->
Left
e
)
)
(
short
't'
<>
long
"tool"
<>
metavar
"<ghc|cabal|ghcup>"
<>
help
"Open changelog for given tool (default: ghc)"
)
)
<*>
optional
(
toolVersionArgument
Nothing
Nothing
)
--------------
--[ Footer ]--
--------------
changeLogFooter
::
String
changeLogFooter
=
[
s
|
Discussion:
By default returns the URI of the ChangeLog of the latest GHC release.
Pass '-o' to automatically open via xdg-open.
|]
------------------
--[ Entrypoint ]--
------------------
changelog
::
(
Monad
m
,
MonadMask
m
,
MonadUnliftIO
m
,
MonadFail
m
)
=>
ChangeLogOptions
->
(
forall
a
.
ReaderT
AppState
m
a
->
m
a
)
->
(
ReaderT
LeanAppState
m
()
->
m
()
)
->
m
ExitCode
changelog
ChangeLogOptions
{
..
}
runAppState
runLogger
=
do
GHCupInfo
{
_ghcupDownloads
=
dls
}
<-
runAppState
getGHCupInfo
let
tool
=
fromMaybe
GHC
clTool
ver'
=
maybe
(
Right
Latest
)
(
\
case
ToolVersion
tv
->
Left
(
_tvVersion
tv
)
-- FIXME: ugly sharing of ToolVersion
ToolTag
t
->
Right
t
)
clToolVer
muri
=
getChangeLog
dls
tool
ver'
case
muri
of
Nothing
->
do
runLogger
(
logWarn
$
"Could not find ChangeLog for "
<>
T
.
pack
(
prettyShow
tool
)
<>
", version "
<>
either
prettyVer
(
T
.
pack
.
show
)
ver'
)
pure
ExitSuccess
Just
uri
->
do
pfreq
<-
runAppState
getPlatformReq
let
uri'
=
T
.
unpack
.
decUTF8Safe
.
serializeURIRef'
$
uri
cmd
=
case
_rPlatform
pfreq
of
Darwin
->
"open"
Linux
_
->
"xdg-open"
FreeBSD
->
"xdg-open"
Windows
->
"start"
if
clOpen
then
do
runAppState
$
exec
cmd
[
T
.
unpack
$
decUTF8Safe
$
serializeURIRef'
uri
]
Nothing
Nothing
>>=
\
case
Right
_
->
pure
ExitSuccess
Left
e
->
logError
(
T
.
pack
$
prettyShow
e
)
>>
pure
(
ExitFailure
13
)
else
liftIO
$
putStrLn
uri'
>>
pure
ExitSuccess
Loading