Skip to content

Commit

Permalink
Merge pull request #6794 from phadej/remote-text
Browse files Browse the repository at this point in the history
Remove Text type-class
  • Loading branch information
phadej authored May 13, 2020
2 parents 7004140 + c0ec505 commit 8d9e8af
Show file tree
Hide file tree
Showing 36 changed files with 300 additions and 868 deletions.
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/BuildReports/Upload.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import System.FilePath.Posix
( (</>) )
import qualified Distribution.Client.BuildReports.Anonymous as BuildReport
import Distribution.Client.BuildReports.Anonymous (BuildReport, showBuildReport)
import Distribution.Deprecated.Text (display)
import Distribution.Pretty (prettyShow)
import Distribution.Verbosity (Verbosity)
import Distribution.Simple.Utils (die')
import Distribution.Client.HttpUtils
Expand All @@ -43,7 +43,7 @@ uploadReports verbosity repoCtxt auth uri reports = do

postBuildReport :: Verbosity -> RepoContext -> (String, String) -> URI -> BuildReport -> IO BuildReportId
postBuildReport verbosity repoCtxt auth uri buildReport = do
let fullURI = uri { uriPath = "/package" </> display (BuildReport.package buildReport) </> "reports" }
let fullURI = uri { uriPath = "/package" </> prettyShow (BuildReport.package buildReport) </> "reports" }
transport <- repoContextGetTransport repoCtxt
res <- postHttp transport verbosity fullURI (showBuildReport buildReport) (Just auth)
case res of
Expand All @@ -53,7 +53,7 @@ postBuildReport verbosity repoCtxt auth uri buildReport = do
{-
setAllowRedirects False
(_, response) <- request Request {
rqURI = uri { uriPath = "/package" </> display (BuildReport.package buildReport) </> "reports" },
rqURI = uri { uriPath = "/package" </> prettyShow (BuildReport.package buildReport) </> "reports" },
rqMethod = POST,
rqHeaders = [Header HdrContentType ("text/plain"),
Header HdrContentLength (show (length body)),
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/CmdBench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,8 @@ import Distribution.Simple.Setup
( HaddockFlags, TestFlags, BenchmarkFlags, fromFlagOrDefault )
import Distribution.Simple.Command
( CommandUI(..), usageAlternatives )
import Distribution.Deprecated.Text
( display )
import Distribution.Pretty
( prettyShow )
import Distribution.Verbosity
( Verbosity, normal )
import Distribution.Simple.Utils
Expand Down Expand Up @@ -235,7 +235,7 @@ renderTargetProblem (TargetProblemComponentNotBenchmark pkgid cname) =
"The bench command is for running benchmarks, but the target '"
++ showTargetSelector targetSelector ++ "' refers to "
++ renderTargetSelector targetSelector ++ " from the package "
++ display pkgid ++ "."
++ prettyShow pkgid ++ "."
where
targetSelector = TargetComponent pkgid cname WholeComponent

Expand Down
54 changes: 27 additions & 27 deletions cabal-install/Distribution/Client/CmdErrorMessages.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,8 @@ import Distribution.Types.LibraryName
( LibraryName(..) )
import Distribution.Solver.Types.OptionalStanza
( OptionalStanza(..) )
import Distribution.Deprecated.Text
( display )
import Distribution.Pretty
( prettyShow )

import qualified Data.List.NonEmpty as NE
import Data.Function (on)
Expand Down Expand Up @@ -74,7 +74,7 @@ renderListSemiAnd (x:xs) = x ++ "; " ++ renderListSemiAnd xs
-- things, e.g. grouping components by package name
--
-- > renderListSemiAnd
-- > [ "the package " ++ display pkgname ++ " components "
-- > [ "the package " ++ prettyShow pkgname ++ " components "
-- > ++ renderListCommaAnd showComponentName components
-- > | (pkgname, components) <- sortGroupOn packageName allcomponents ]
--
Expand All @@ -91,19 +91,19 @@ sortGroupOn key = map (\(x:|xs) -> (key x, x:xs))
renderTargetSelector :: TargetSelector -> String
renderTargetSelector (TargetPackage _ pkgids Nothing) =
"the " ++ plural (listPlural pkgids) "package" "packages" ++ " "
++ renderListCommaAnd (map display pkgids)
++ renderListCommaAnd (map prettyShow pkgids)

renderTargetSelector (TargetPackage _ pkgids (Just kfilter)) =
"the " ++ renderComponentKind Plural kfilter
++ " in the " ++ plural (listPlural pkgids) "package" "packages" ++ " "
++ renderListCommaAnd (map display pkgids)
++ renderListCommaAnd (map prettyShow pkgids)

renderTargetSelector (TargetPackageNamed pkgname Nothing) =
"the package " ++ display pkgname
"the package " ++ prettyShow pkgname

renderTargetSelector (TargetPackageNamed pkgname (Just kfilter)) =
"the " ++ renderComponentKind Plural kfilter
++ " in the package " ++ display pkgname
++ " in the package " ++ prettyShow pkgname

renderTargetSelector (TargetAllPackages Nothing) =
"all the packages in the project"
Expand All @@ -117,8 +117,8 @@ renderTargetSelector (TargetComponent pkgid cname subtarget) =
++ renderComponentName (packageName pkgid) cname

renderTargetSelector (TargetComponentUnknown pkgname (Left ucname) subtarget) =
renderSubComponentTarget subtarget ++ "the component " ++ display ucname
++ " in the package " ++ display pkgname
renderSubComponentTarget subtarget ++ "the component " ++ prettyShow ucname
++ " in the package " ++ prettyShow pkgname

renderTargetSelector (TargetComponentUnknown pkgname (Right cname) subtarget) =
renderSubComponentTarget subtarget ++ "the "
Expand All @@ -129,7 +129,7 @@ renderSubComponentTarget WholeComponent = ""
renderSubComponentTarget (FileTarget filename) =
"the file " ++ filename ++ "in "
renderSubComponentTarget (ModuleTarget modname) =
"the module" ++ display modname ++ "in "
"the module" ++ prettyShow modname ++ "in "


renderOptionalStanza :: Plural -> OptionalStanza -> String
Expand Down Expand Up @@ -169,12 +169,12 @@ targetSelectorFilter TargetComponent{} = Nothing
targetSelectorFilter TargetComponentUnknown{} = Nothing

renderComponentName :: PackageName -> ComponentName -> String
renderComponentName pkgname (CLibName LMainLibName) = "library " ++ display pkgname
renderComponentName _ (CLibName (LSubLibName name)) = "library " ++ display name
renderComponentName _ (CFLibName name) = "foreign library " ++ display name
renderComponentName _ (CExeName name) = "executable " ++ display name
renderComponentName _ (CTestName name) = "test suite " ++ display name
renderComponentName _ (CBenchName name) = "benchmark " ++ display name
renderComponentName pkgname (CLibName LMainLibName) = "library " ++ prettyShow pkgname
renderComponentName _ (CLibName (LSubLibName name)) = "library " ++ prettyShow name
renderComponentName _ (CFLibName name) = "foreign library " ++ prettyShow name
renderComponentName _ (CExeName name) = "executable " ++ prettyShow name
renderComponentName _ (CTestName name) = "test suite " ++ prettyShow name
renderComponentName _ (CBenchName name) = "benchmark " ++ prettyShow name

renderComponentKind :: Plural -> ComponentKind -> String
renderComponentKind Singular ckind = case ckind of
Expand All @@ -197,27 +197,27 @@ renderComponentKind Plural ckind = case ckind of

renderTargetProblemCommon :: String -> TargetProblemCommon -> String
renderTargetProblemCommon verb (TargetNotInProject pkgname) =
"Cannot " ++ verb ++ " the package " ++ display pkgname ++ ", it is not "
"Cannot " ++ verb ++ " the package " ++ prettyShow pkgname ++ ", it is not "
++ "in this project (either directly or indirectly). If you want to add it "
++ "to the project then edit the cabal.project file."

renderTargetProblemCommon verb (TargetAvailableInIndex pkgname) =
"Cannot " ++ verb ++ " the package " ++ display pkgname ++ ", it is not "
"Cannot " ++ verb ++ " the package " ++ prettyShow pkgname ++ ", it is not "
++ "in this project (either directly or indirectly), but it is in the current "
++ "package index. If you want to add it to the project then edit the "
++ "cabal.project file."

renderTargetProblemCommon verb (TargetComponentNotProjectLocal pkgid cname _) =
"Cannot " ++ verb ++ " the " ++ showComponentName cname ++ " because the "
++ "package " ++ display pkgid ++ " is not local to the project, and cabal "
++ "package " ++ prettyShow pkgid ++ " is not local to the project, and cabal "
++ "does not currently support building test suites or benchmarks of "
++ "non-local dependencies. To run test suites or benchmarks from "
++ "dependencies you can unpack the package locally and adjust the "
++ "cabal.project file to include that package directory."

renderTargetProblemCommon verb (TargetComponentNotBuildable pkgid cname _) =
"Cannot " ++ verb ++ " the " ++ showComponentName cname ++ " because it is "
++ "marked as 'buildable: False' within the '" ++ display (packageName pkgid)
++ "marked as 'buildable: False' within the '" ++ prettyShow (packageName pkgid)
++ ".cabal' file (at least for the current configuration). If you believe it "
++ "should be buildable then check the .cabal file to see if the buildable "
++ "property is conditional on flags. Alternatively you may simply have to "
Expand All @@ -240,7 +240,7 @@ renderTargetProblemCommon verb (TargetOptionalStanzaDisabledByUser _ cname _) =
renderTargetProblemCommon verb (TargetOptionalStanzaDisabledBySolver pkgid cname _) =
"Cannot " ++ verb ++ " the " ++ showComponentName cname ++ " because the "
++ "solver did not find a plan that included the " ++ compkinds
++ " for " ++ display pkgid ++ ". It is probably worth trying again with "
++ " for " ++ prettyShow pkgid ++ ". It is probably worth trying again with "
++ compkinds ++ " explicitly enabled in the configuration in the "
++ "cabal.project{.local} file. This will ask the solver to find a plan with "
++ "the " ++ compkinds ++ " available. It will either fail with an "
Expand All @@ -253,9 +253,9 @@ renderTargetProblemCommon verb (TargetOptionalStanzaDisabledBySolver pkgid cname
renderTargetProblemCommon verb (TargetProblemUnknownComponent pkgname ecname) =
"Cannot " ++ verb ++ " the "
++ (case ecname of
Left ucname -> "component " ++ display ucname
Left ucname -> "component " ++ prettyShow ucname
Right cname -> renderComponentName pkgname cname)
++ " from the package " ++ display pkgname
++ " from the package " ++ prettyShow pkgname
++ ", because the package does not contain a "
++ (case ecname of
Left _ -> "component"
Expand All @@ -264,13 +264,13 @@ renderTargetProblemCommon verb (TargetProblemUnknownComponent pkgname ecname) =

renderTargetProblemCommon verb (TargetProblemNoSuchPackage pkgid) =
"Internal error when trying to " ++ verb ++ " the package "
++ display pkgid ++ ". The package is not in the set of available targets "
++ prettyShow pkgid ++ ". The package is not in the set of available targets "
++ "for the project plan, which would suggest an inconsistency "
++ "between readTargetSelectors and resolveTargets."

renderTargetProblemCommon verb (TargetProblemNoSuchComponent pkgid cname) =
"Internal error when trying to " ++ verb ++ " the "
++ showComponentName cname ++ " from the package " ++ display pkgid
++ showComponentName cname ++ " from the package " ++ prettyShow pkgid
++ ". The package,component pair is not in the set of available targets "
++ "for the project plan, which would suggest an inconsistency "
++ "between readTargetSelectors and resolveTargets."
Expand Down Expand Up @@ -385,9 +385,9 @@ renderCannotPruneDependencies (CannotPruneDependencies brokenPackages) =
"Cannot select only the dependencies (as requested by the "
++ "'--only-dependencies' flag), "
++ (case pkgids of
[pkgid] -> "the package " ++ display pkgid ++ " is "
[pkgid] -> "the package " ++ prettyShow pkgid ++ " is "
_ -> "the packages "
++ renderListCommaAnd (map display pkgids) ++ " are ")
++ renderListCommaAnd (map prettyShow pkgids) ++ " are ")
++ "required by a dependency of one of the other targets."
where
-- throw away the details and just list the deps that are needed
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/CmdInstall.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,8 +124,8 @@ import Distribution.Simple.Utils
, ordNub )
import Distribution.Utils.Generic
( safeHead, writeFileAtomic )
import Distribution.Deprecated.Text
( simpleParse )
import Distribution.Parsec
( simpleParsec )
import Distribution.Pretty
( prettyShow )

Expand Down Expand Up @@ -235,7 +235,7 @@ installAction ( configFlags, configExFlags, installFlags
(targetStrings'', packageIds) =
partitionEithers .
flip fmap targetStrings' $
\str -> case simpleParse str of
\str -> case simpleParsec str of
Just (pkgId :: PackageId)
| pkgVersion pkgId /= nullVersion -> Right pkgId
_ -> Left str
Expand Down
4 changes: 1 addition & 3 deletions cabal-install/Distribution/Client/CmdRepl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,8 +87,6 @@ import Distribution.Types.Version
( mkVersion )
import Distribution.Types.VersionRange
( anyVersion )
import Distribution.Deprecated.Text
( display )
import Distribution.Utils.Generic
( safeHead )
import Distribution.Verbosity
Expand Down Expand Up @@ -568,7 +566,7 @@ renderTargetProblem (TargetProblemMatchesMultiple targetSelector targets) =
++ renderListSemiAnd
[ "the " ++ renderComponentKind Plural ckind ++ " " ++
renderListCommaAnd
[ maybe (display pkgname) display (componentNameString cname)
[ maybe (prettyShow pkgname) prettyShow (componentNameString cname)
| t <- ts
, let cname = availableTargetComponentName t
pkgname = packageName (availableTargetPackageId t)
Expand Down
16 changes: 7 additions & 9 deletions cabal-install/Distribution/Client/CmdRun.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,9 +37,9 @@ import Distribution.Simple.Command
( CommandUI(..), usageAlternatives )
import Distribution.Types.ComponentName
( showComponentName )
import Distribution.Deprecated.Text
( display )
import Distribution.CabalSpecVersion (CabalSpecVersion (..))
import Distribution.Pretty
( prettyShow )
import Distribution.CabalSpecVersion (CabalSpecVersion (..), cabalSpecLatest)
import Distribution.Verbosity
( Verbosity, normal )
import Distribution.Simple.Utils
Expand All @@ -65,8 +65,6 @@ import Distribution.Simple.Program.Run
import Distribution.Types.UnitId
( UnitId )

import Distribution.CabalSpecVersion
( cabalSpecLatest )
import Distribution.Client.Types
( PackageLocation(..), PackageSpecifier(..) )
import Distribution.FieldGrammar
Expand Down Expand Up @@ -275,17 +273,17 @@ runAction ( configFlags, configExFlags, installFlags
[] -> die' verbosity $ "Unknown executable "
++ exeName
++ " in package "
++ display selectedUnitId
++ prettyShow selectedUnitId
[elabPkg] -> do
info verbosity $ "Selecting "
++ display selectedUnitId
++ prettyShow selectedUnitId
++ " to supply " ++ exeName
return elabPkg
elabPkgs -> die' verbosity
$ "Multiple matching executables found matching "
++ exeName
++ ":\n"
++ unlines (fmap (\p -> " - in package " ++ display (elabUnitId p)) elabPkgs)
++ unlines (fmap (\p -> " - in package " ++ prettyShow (elabUnitId p)) elabPkgs)
let exePath = binDirectoryFor (distDirLayout baseCtx)
(elaboratedShared buildCtx)
pkg
Expand Down Expand Up @@ -617,7 +615,7 @@ renderTargetProblem (TargetProblemComponentNotExe pkgid cname) =
"The run command is for running executables, but the target '"
++ showTargetSelector targetSelector ++ "' refers to "
++ renderTargetSelector targetSelector ++ " from the package "
++ display pkgid ++ "."
++ prettyShow pkgid ++ "."
where
targetSelector = TargetComponent pkgid cname WholeComponent

Expand Down
6 changes: 3 additions & 3 deletions cabal-install/Distribution/Client/CmdTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@ import Distribution.Simple.Command
( CommandUI(..), usageAlternatives )
import Distribution.Simple.Flag
( Flag(..) )
import Distribution.Deprecated.Text
( display )
import Distribution.Pretty
( prettyShow )
import Distribution.Verbosity
( Verbosity, normal )
import Distribution.Simple.Utils
Expand Down Expand Up @@ -264,7 +264,7 @@ renderTargetProblem (TargetProblemComponentNotTest pkgid cname) =
"The test command is for running test suites, but the target '"
++ showTargetSelector targetSelector ++ "' refers to "
++ renderTargetSelector targetSelector ++ " from the package "
++ display pkgid ++ "."
++ prettyShow pkgid ++ "."
where
targetSelector = TargetComponent pkgid cname WholeComponent

Expand Down
Loading

0 comments on commit 8d9e8af

Please sign in to comment.