diff --git a/Cabal/Distribution/Compiler.hs b/Cabal/Distribution/Compiler.hs index 92018eafe402ddb94b00b94d3948f1c3c45bd852..a76ef888c936abec60375c3320a9d6cef63cb3ec 100644 --- a/Cabal/Distribution/Compiler.hs +++ b/Cabal/Distribution/Compiler.hs @@ -154,11 +154,18 @@ instance Binary CompilerId instance NFData CompilerId where rnf = genericRnf -instance Text CompilerId where - disp (CompilerId f v) - | v == nullVersion = disp f - | otherwise = disp f <<>> Disp.char '-' <<>> disp v +instance Pretty CompilerId where + pretty (CompilerId f v) + | v == nullVersion = pretty f + | otherwise = pretty f <<>> Disp.char '-' <<>> pretty v + +instance Parsec CompilerId where + parsec = do + flavour <- parsec + version <- (P.char '-' >> parsec) <|> return nullVersion + return (CompilerId flavour version) +instance Text CompilerId where parse = do flavour <- parse version <- (Parse.char '-' >> parse) Parse.<++ return nullVersion diff --git a/Cabal/Distribution/Simple/Bench.hs b/Cabal/Distribution/Simple/Bench.hs index 3f720ffa04dfc25af2d0963246c636cf8a8ed89b..ab76e69e2f77afcd490d2f78d5ddcbdf6fa38357 100644 --- a/Cabal/Distribution/Simple/Bench.hs +++ b/Cabal/Distribution/Simple/Bench.hs @@ -30,7 +30,7 @@ import qualified Distribution.Simple.LocalBuildInfo as LBI import Distribution.Simple.Setup import Distribution.Simple.UserHooks import Distribution.Simple.Utils -import Distribution.Text +import Distribution.Pretty import System.Exit ( ExitCode(..), exitFailure, exitSuccess ) import System.Directory ( doesFileExist ) @@ -72,7 +72,7 @@ bench args pkg_descr lbi flags = do _ -> do notice verbosity $ "No support for running " ++ "benchmark " ++ name ++ " of type: " - ++ display (PD.benchmarkType bm) + ++ prettyShow (PD.benchmarkType bm) exitFailure where name = unUnqualComponentName $ PD.benchmarkName bm diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs index 1ba8d324849c45c0180b7c799e36d77c27c6fb75..ef4ed6b73489404069da1583b9a7a4d8ea755145 100644 --- a/Cabal/Distribution/Simple/Build.hs +++ b/Cabal/Distribution/Simple/Build.hs @@ -75,7 +75,7 @@ import Distribution.Simple.Test.LibV09 import Distribution.Simple.Utils import Distribution.System -import Distribution.Text +import Distribution.Pretty import Distribution.Verbosity import Distribution.Compat.Graph (IsNode(..)) @@ -300,7 +300,7 @@ buildComponent verbosity numJobs pkg_descr lbi0 suffixes buildComponent verbosity _ _ _ _ (CTest TestSuite { testInterface = TestSuiteUnsupported tt }) _ _ = - die' verbosity $ "No support for building test suite type " ++ display tt + die' verbosity $ "No support for building test suite type " ++ prettyShow tt buildComponent verbosity numJobs pkg_descr lbi suffixes @@ -320,7 +320,7 @@ buildComponent verbosity numJobs pkg_descr lbi suffixes buildComponent verbosity _ _ _ _ (CBench Benchmark { benchmarkInterface = BenchmarkUnsupported tt }) _ _ = - die' verbosity $ "No support for building benchmark type " ++ display tt + die' verbosity $ "No support for building benchmark type " ++ prettyShow tt -- | Add extra C sources generated by preprocessing to build @@ -400,7 +400,7 @@ replComponent replFlags verbosity pkg_descr lbi0 suffixes replComponent _ verbosity _ _ _ (CTest TestSuite { testInterface = TestSuiteUnsupported tt }) _ _ = - die' verbosity $ "No support for building test suite type " ++ display tt + die' verbosity $ "No support for building test suite type " ++ prettyShow tt replComponent replFlags verbosity pkg_descr lbi suffixes @@ -417,7 +417,7 @@ replComponent replFlags verbosity pkg_descr lbi suffixes replComponent _ verbosity _ _ _ (CBench Benchmark { benchmarkInterface = BenchmarkUnsupported tt }) _ _ = - die' verbosity $ "No support for building benchmark type " ++ display tt + die' verbosity $ "No support for building benchmark type " ++ prettyShow tt ---------------------------------------------------- -- Shared code for buildComponent and replComponent @@ -689,7 +689,7 @@ writeAutogenFiles verbosity pkg lbi clbi = do createDirectoryIfMissingVerbose verbosity True (takeDirectory sigPath) rewriteFileEx verbosity sigPath $ "{-# LANGUAGE NoImplicitPrelude #-}\n" ++ - "signature " ++ display mod_name ++ " where" + "signature " ++ prettyShow mod_name ++ " where" _ -> return () let cppHeaderPath = autogenComponentModulesDir lbi clbi </> cppHeaderName diff --git a/Cabal/Distribution/Simple/Build/Macros.hs b/Cabal/Distribution/Simple/Build/Macros.hs index 89069673e69b2d6b388f700bc740ceeb9240ec85..52c7ffaa75be2cfd2dea0f39590e4297ce830786 100644 --- a/Cabal/Distribution/Simple/Build/Macros.hs +++ b/Cabal/Distribution/Simple/Build/Macros.hs @@ -35,7 +35,7 @@ import Distribution.Simple.Program.Types import Distribution.Types.MungedPackageId import Distribution.Types.MungedPackageName import Distribution.Types.PackageId -import Distribution.Text +import Distribution.Pretty -- ------------------------------------------------------------ -- * Generate cabal_macros.h @@ -96,10 +96,10 @@ generate pkg_descr lbi clbi = -- generatePackageVersionMacros :: [PackageId] -> String generatePackageVersionMacros pkgids = concat - [ line ("/* package " ++ display pkgid ++ " */") + [ line ("/* package " ++ prettyShow pkgid ++ " */") ++ generateMacros "" pkgname version | pkgid@(PackageIdentifier name version) <- pkgids - , let pkgname = map fixchar (display name) + , let pkgname = map fixchar (prettyShow name) ] -- | Helper function that generates just the @TOOL_VERSION_pkg@ and @@ -111,7 +111,7 @@ generateToolVersionMacros progs = concat ++ generateMacros "TOOL_" progname version | prog <- progs , isJust . programVersion $ prog - , let progid = programId prog ++ "-" ++ display version + , let progid = programId prog ++ "-" ++ prettyShow version progname = map fixchar (programId prog) Just version = programVersion prog ] @@ -122,7 +122,7 @@ generateToolVersionMacros progs = concat generateMacros :: String -> String -> Version -> String generateMacros macro_prefix name version = concat - [ifndefDefineStr (macro_prefix ++ "VERSION_" ++ name) (display version) + [ifndefDefineStr (macro_prefix ++ "VERSION_" ++ name) (prettyShow version) ,ifndefDefine ("MIN_" ++ macro_prefix ++ "VERSION_" ++ name) (Just ["major1","major2","minor"]) $ concat [ @@ -144,14 +144,14 @@ generateComponentIdMacro _lbi clbi = LibComponentLocalBuildInfo{} -> ifndefDefineStr "CURRENT_PACKAGE_KEY" (componentCompatPackageKey clbi) _ -> "" - ,ifndefDefineStr "CURRENT_COMPONENT_ID" (display (componentComponentId clbi)) + ,ifndefDefineStr "CURRENT_COMPONENT_ID" (prettyShow (componentComponentId clbi)) ] -- | Generate the @CURRENT_PACKAGE_VERSION@ definition for the declared version -- of the current package. generateCurrentPackageVersion :: PackageDescription -> String generateCurrentPackageVersion pd = - ifndefDefineStr "CURRENT_PACKAGE_VERSION" (display (pkgVersion (package pd))) + ifndefDefineStr "CURRENT_PACKAGE_VERSION" (prettyShow (pkgVersion (package pd))) fixchar :: Char -> Char fixchar '-' = '_' diff --git a/Cabal/Distribution/Simple/Build/PathsModule.hs b/Cabal/Distribution/Simple/Build/PathsModule.hs index 678ccbca3222820cca33a3134617ae4cb667572d..f6a20387475cf00c10a31a6ebbdeb9bdd6a44ac5 100644 --- a/Cabal/Distribution/Simple/Build/PathsModule.hs +++ b/Cabal/Distribution/Simple/Build/PathsModule.hs @@ -28,7 +28,7 @@ import Distribution.PackageDescription import Distribution.Simple.LocalBuildInfo import Distribution.Simple.BuildPaths import Distribution.Simple.Utils -import Distribution.Text +import Distribution.Pretty import Distribution.Version import System.FilePath ( pathSeparator ) @@ -80,7 +80,7 @@ generate pkg_descr lbi clbi = header = pragmas++ - "module " ++ display paths_modulename ++ " (\n"++ + "module " ++ prettyShow paths_modulename ++ " (\n"++ " version,\n"++ " getBinDir, getLibDir, getDynLibDir, getDataDir, getLibexecDir,\n"++ " getDataFileName, getSysconfDir\n"++ @@ -267,7 +267,7 @@ pkgPathEnvVar :: PackageDescription pkgPathEnvVar pkg_descr var = showPkgName (packageName pkg_descr) ++ "_" ++ var where - showPkgName = map fixchar . display + showPkgName = map fixchar . prettyShow fixchar '-' = '_' fixchar c = c diff --git a/Cabal/Distribution/Simple/BuildPaths.hs b/Cabal/Distribution/Simple/BuildPaths.hs index d7aeabab14938f8a81c4b7e5141a4dbe127adf95..a51ec68aec2e6ff222dc4e3d01f16ee1f0d10a56 100644 --- a/Cabal/Distribution/Simple/BuildPaths.hs +++ b/Cabal/Distribution/Simple/BuildPaths.hs @@ -52,7 +52,7 @@ import Distribution.Compiler import Distribution.PackageDescription import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Setup -import Distribution.Text +import Distribution.Pretty import Distribution.System import Distribution.Verbosity import Distribution.Simple.Utils @@ -71,8 +71,8 @@ hscolourPref = haddockPref -- | This is the name of the directory in which the generated haddocks -- should be stored. It does not include the @<dist>/doc/html@ prefix. haddockDirName :: HaddockTarget -> PackageDescription -> FilePath -haddockDirName ForDevelopment = display . packageName -haddockDirName ForHackage = (++ "-docs") . display . packageId +haddockDirName ForDevelopment = prettyShow . packageName +haddockDirName ForHackage = (++ "-docs") . prettyShow . packageId -- | The directory to which generated haddock documentation should be written. haddockPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath @@ -109,12 +109,12 @@ autogenModuleName = autogenPathsModuleName autogenPathsModuleName :: PackageDescription -> ModuleName autogenPathsModuleName pkg_descr = ModuleName.fromString $ - "Paths_" ++ map fixchar (display (packageName pkg_descr)) + "Paths_" ++ map fixchar (prettyShow (packageName pkg_descr)) where fixchar '-' = '_' fixchar c = c haddockName :: PackageDescription -> FilePath -haddockName pkg_descr = display (packageName pkg_descr) <.> "haddock" +haddockName pkg_descr = prettyShow (packageName pkg_descr) <.> "haddock" -- ----------------------------------------------------------------------------- -- Source File helper @@ -168,7 +168,7 @@ getSourceFiles verbosity dirs modules = flip traverse modules $ \m -> fmap ((,) findFileWithExtension ["hs", "lhs", "hsig", "lhsig"] dirs (ModuleName.toFilePath m) >>= maybe (notFound m) (return . normalise) where - notFound module_ = die' verbosity $ "can't find source for module " ++ display module_ + notFound module_ = die' verbosity $ "can't find source for module " ++ prettyShow module_ -- | The directory where we put build results for an executable exeBuildDir :: LocalBuildInfo -> Executable -> FilePath @@ -202,7 +202,7 @@ mkProfLibName lib = mkGenericStaticLibName (getHSLibraryName lib ++ "_p") mkGenericSharedLibName :: Platform -> CompilerId -> String -> String mkGenericSharedLibName platform (CompilerId compilerFlavor compilerVersion) lib = mconcat [ "lib", lib, "-", comp <.> dllExtension platform ] - where comp = display compilerFlavor ++ display compilerVersion + where comp = prettyShow compilerFlavor ++ prettyShow compilerVersion -- Implement proper name mangling for dynamical shared objects -- libHS<packagename>-<compilerFlavour><compilerVersion> @@ -216,7 +216,7 @@ mkSharedLibName platform comp lib mkStaticLibName :: Platform -> CompilerId -> UnitId -> String mkStaticLibName platform (CompilerId compilerFlavor compilerVersion) lib = "lib" ++ getHSLibraryName lib ++ "-" ++ comp <.> staticLibExtension platform - where comp = display compilerFlavor ++ display compilerVersion + where comp = prettyShow compilerFlavor ++ prettyShow compilerVersion -- ------------------------------------------------------------ -- * Platform file extensions diff --git a/Cabal/Distribution/Simple/BuildTarget.hs b/Cabal/Distribution/Simple/BuildTarget.hs index e3aa8ef5f9bff4facc0f7f92ce432e8c2a08bfe8..0a210db552122b6e8dc302803b0abe41ed580218 100644 --- a/Cabal/Distribution/Simple/BuildTarget.hs +++ b/Cabal/Distribution/Simple/BuildTarget.hs @@ -49,13 +49,12 @@ import Distribution.Package import Distribution.PackageDescription import Distribution.ModuleName import Distribution.Simple.LocalBuildInfo -import Distribution.Text +import Distribution.Pretty +import Distribution.Parsec.Class import Distribution.Simple.Utils import Distribution.Verbosity -import qualified Distribution.Compat.ReadP as Parse -import Distribution.Compat.ReadP ( (+++), (<++) ) -import Distribution.ParseUtils ( readPToMaybe ) +import qualified Distribution.Compat.CharParsing as P import Control.Monad ( msum ) import Data.List ( stripPrefix, groupBy, partition ) @@ -180,33 +179,59 @@ readUserBuildTargets :: [String] -> ([UserBuildTargetProblem] ,[UserBuildTarget]) readUserBuildTargets = partitionEithers . map readUserBuildTarget +-- | +-- +-- >>> readUserBuildTarget "comp" +-- Right (UserBuildTargetSingle "comp") +-- +-- >>> readUserBuildTarget "lib:comp" +-- Right (UserBuildTargetDouble "lib" "comp") +-- +-- >>> readUserBuildTarget "pkg:lib:comp" +-- Right (UserBuildTargetTriple "pkg" "lib" "comp") +-- +-- >>> readUserBuildTarget "\"comp\"" +-- Right (UserBuildTargetSingle "comp") +-- +-- >>> readUserBuildTarget "lib:\"comp\"" +-- Right (UserBuildTargetDouble "lib" "comp") +-- +-- >>> readUserBuildTarget "pkg:lib:\"comp\"" +-- Right (UserBuildTargetTriple "pkg" "lib" "comp") +-- +-- >>> readUserBuildTarget "pkg:lib:comp:more" +-- Left (UserBuildTargetUnrecognised "pkg:lib:comp:more") +-- +-- >>> readUserBuildTarget "pkg:\"lib\":comp" +-- Left (UserBuildTargetUnrecognised "pkg:\"lib\":comp") +-- readUserBuildTarget :: String -> Either UserBuildTargetProblem UserBuildTarget readUserBuildTarget targetstr = - case readPToMaybe parseTargetApprox targetstr of - Nothing -> Left (UserBuildTargetUnrecognised targetstr) - Just tgt -> Right tgt + case explicitEitherParsec parseTargetApprox targetstr of + Left _ -> Left (UserBuildTargetUnrecognised targetstr) + Right tgt -> Right tgt where - parseTargetApprox :: Parse.ReadP r UserBuildTarget - parseTargetApprox = - (do a <- tokenQ - return (UserBuildTargetSingle a)) - +++ (do a <- token - _ <- Parse.char ':' - b <- tokenQ - return (UserBuildTargetDouble a b)) - +++ (do a <- token - _ <- Parse.char ':' - b <- token - _ <- Parse.char ':' - c <- tokenQ - return (UserBuildTargetTriple a b c)) - - token = Parse.munch1 (\x -> not (isSpace x) && x /= ':') - tokenQ = parseHaskellString <++ token - parseHaskellString :: Parse.ReadP r String - parseHaskellString = Parse.readS_to_P reads + parseTargetApprox :: CabalParsing m => m UserBuildTarget + parseTargetApprox = do + -- read one, two, or three tokens, where last could be "hs-string" + ts <- tokens + return $ case ts of + (a, Nothing) -> UserBuildTargetSingle a + (a, Just (b, Nothing)) -> UserBuildTargetDouble a b + (a, Just (b, Just c)) -> UserBuildTargetTriple a b c + + tokens :: CabalParsing m => m (String, Maybe (String, Maybe String)) + tokens = (\s -> (s, Nothing)) <$> parsecHaskellString + <|> (,) <$> token <*> P.optional (P.char ':' *> tokens2) + + tokens2 :: CabalParsing m => m (String, Maybe String) + tokens2 = (\s -> (s, Nothing)) <$> parsecHaskellString + <|> (,) <$> token <*> P.optional (P.char ':' *> (parsecHaskellString <|> token)) + + token :: CabalParsing m => m String + token = P.munch1 (\x -> not (isSpace x) && x /= ':') data UserBuildTargetProblem = UserBuildTargetUnrecognised String @@ -346,15 +371,15 @@ renderBuildTarget ql target pkgid = where single (BuildTargetComponent cn ) = dispCName cn - single (BuildTargetModule _ m) = display m + single (BuildTargetModule _ m) = prettyShow m single (BuildTargetFile _ f) = f double (BuildTargetComponent cn ) = (dispKind cn, dispCName cn) - double (BuildTargetModule cn m) = (dispCName cn, display m) + double (BuildTargetModule cn m) = (dispCName cn, prettyShow m) double (BuildTargetFile cn f) = (dispCName cn, f) triple (BuildTargetComponent _ ) = error "triple BuildTargetComponent" - triple (BuildTargetModule cn m) = (dispKind cn, dispCName cn, display m) + triple (BuildTargetModule cn m) = (dispKind cn, dispCName cn, prettyShow m) triple (BuildTargetFile cn f) = (dispKind cn, dispCName cn, f) dispCName = componentStringName pkgid @@ -477,7 +502,7 @@ pkgComponentInfo pkg = , let bi = componentBuildInfo c ] componentStringName :: Package pkg => pkg -> ComponentName -> ComponentStringName -componentStringName pkg CLibName = display (packageName pkg) +componentStringName pkg CLibName = prettyShow (packageName pkg) componentStringName _ (CSubLibName name) = unUnqualComponentName name componentStringName _ (CFLibName name) = unUnqualComponentName name componentStringName _ (CExeName name) = unUnqualComponentName name @@ -489,7 +514,7 @@ componentModules :: Component -> [ModuleName] -- a user could very well ask to build a specific signature -- that was inherited from other packages. To fix this -- we have to plumb 'LocalBuildInfo' through this code. --- Fortunately, this is only used by 'pkgComponentInfo' +-- Fortunately, this is only used by 'pkgComponentInfo' -- Please don't export this function unless you plan on fixing -- this. componentModules (CLib lib) = explicitLibModules lib @@ -659,7 +684,7 @@ matchModuleName ms str = orNoSuchThing "module" str $ increaseConfidenceFor $ matchInexactly caseFold - [ (display m, m) + [ (prettyShow m, m) | m <- ms ] str @@ -1005,7 +1030,7 @@ checkBuildTargets verbosity pkg_descr lbi targets = do ((cname,reason):_) -> die' verbosity $ formatReason (showComponentName cname) reason for_ [ (c, t) | (c, Just t) <- enabled ] $ \(c, t) -> - warn verbosity $ "Ignoring '" ++ either display id t ++ ". The whole " + warn verbosity $ "Ignoring '" ++ either prettyShow id t ++ ". The whole " ++ showComponentName c ++ " will be processed. (Support for " ++ "module and file targets has not been implemented yet.)" diff --git a/Cabal/Distribution/Simple/Command.hs b/Cabal/Distribution/Simple/Command.hs index 4a8dd4cc91842398e79352aaf41c93b48dd4a7ac..b2facefdc35a335753fd8a2abdb3a01ae675a58b 100644 --- a/Cabal/Distribution/Simple/Command.hs +++ b/Cabal/Distribution/Simple/Command.hs @@ -72,9 +72,10 @@ import Prelude () import Distribution.Compat.Prelude hiding (get) import qualified Distribution.GetOpt as GetOpt -import Distribution.Text +import Distribution.Pretty import Distribution.ParseUtils import Distribution.ReadE +import Distribution.Parsec.Class (parsec) import Distribution.Simple.Utils import Text.PrettyPrint ( punctuate, cat, comma, text ) @@ -280,7 +281,7 @@ viewAsFieldDescr (OptionField n dd) = FieldDescr n get set fromMaybe PP.empty $ listToMaybe [ text lf | (_,(_,lf:_), _,enabled) <- alts, enabled t] - BoolOpt _ _ _ _ enabled -> (maybe PP.empty disp . enabled) t + BoolOpt _ _ _ _ enabled -> (maybe PP.empty pretty . enabled) t -- set :: LineNo -> String -> a -> ParseResult a set line val a = @@ -295,7 +296,7 @@ viewAsFieldDescr (OptionField n dd) = FieldDescr n get set Just f -> return (f a) _ -> syntaxError line val - BoolOpt _ _ _ setV _ -> (`setV` a) `liftM` runP line n parse val + BoolOpt _ _ _ setV _ -> (`setV` a) `liftM` runE line n (parsecToReadE ("<viewAsFieldDescr>" ++) parsec) val OptArg _ _ _ readE _ _ -> ($ a) `liftM` runE line n readE val -- Optional arguments are parsed just like diff --git a/Cabal/Distribution/Simple/Compiler.hs b/Cabal/Distribution/Simple/Compiler.hs index de416470edae8215780fbc87453b7229ed16e46f..0241418d050baa2b2a5bac2c91a2abcab8f47ee3 100644 --- a/Cabal/Distribution/Simple/Compiler.hs +++ b/Cabal/Distribution/Simple/Compiler.hs @@ -73,10 +73,10 @@ module Distribution.Simple.Compiler ( import Prelude () import Distribution.Compat.Prelude +import Distribution.Pretty import Distribution.Compiler import Distribution.Version -import Distribution.Text import Language.Haskell.Extension import Distribution.Simple.Utils @@ -105,11 +105,11 @@ data Compiler = Compiler { instance Binary Compiler showCompilerId :: Compiler -> String -showCompilerId = display . compilerId +showCompilerId = prettyShow . compilerId showCompilerIdWithAbi :: Compiler -> String showCompilerIdWithAbi comp = - display (compilerId comp) ++ + prettyShow (compilerId comp) ++ case compilerAbiTag comp of NoAbiTag -> [] AbiTag xs -> '-':xs diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 7b5ffd8337109e73536d4d7dbdbe626f1e470ae2..32aeabcb6986376cfecbd07d94431b9376d46411 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -130,8 +130,10 @@ import qualified System.Info ( compilerName, compilerVersion ) import System.IO ( hPutStrLn, hClose ) -import Distribution.Text - ( Text(disp), defaultStyle, display, simpleParse ) +import Distribution.Pretty + ( pretty, defaultStyle, prettyShow ) +import Distribution.Parsec.Class + ( simpleParsec ) import Text.PrettyPrint ( Doc, (<+>), ($+$), char, comma, hsep, nest , punctuate, quotes, render, renderStyle, sep, text ) @@ -171,12 +173,12 @@ dispConfigStateFileError (ConfigStateFileBadVersion oldCabal oldCompiler _) = where badCabal = text "• the Cabal version changed from" - <+> disp oldCabal <+> "to" <+> disp currentCabalId + <+> pretty oldCabal <+> "to" <+> pretty currentCabalId badCompiler | oldCompiler == currentCompilerId = mempty | otherwise = text "• the compiler changed from" - <+> disp oldCompiler <+> "to" <+> disp currentCompilerId + <+> pretty oldCompiler <+> "to" <+> pretty currentCompilerId instance Show ConfigStateFileError where show = renderStyle defaultStyle . dispConfigStateFileError @@ -269,9 +271,9 @@ parseHeader header = case BLC8.words header of ["Saved", "package", "config", "for", pkgId, "written", "by", cabalId, "using", compId] -> fromMaybe (throw ConfigStateFileBadHeader) $ do - _ <- simpleParse (BLC8.unpack pkgId) :: Maybe PackageIdentifier - cabalId' <- simpleParse (BLC8.unpack cabalId) - compId' <- simpleParse (BLC8.unpack compId) + _ <- simpleParsec (BLC8.unpack pkgId) :: Maybe PackageIdentifier + cabalId' <- simpleParsec (BLC8.unpack cabalId) + compId' <- simpleParsec (BLC8.unpack compId) return (cabalId', compId') _ -> throw ConfigStateFileNoHeader @@ -280,11 +282,11 @@ showHeader :: PackageIdentifier -- ^ The processed package. -> ByteString showHeader pkgId = BLC8.unwords [ "Saved", "package", "config", "for" - , BLC8.pack $ display pkgId + , BLC8.pack $ prettyShow pkgId , "written", "by" - , BLC8.pack $ display currentCabalId + , BLC8.pack $ prettyShow currentCabalId , "using" - , BLC8.pack $ display currentCompilerId + , BLC8.pack $ prettyShow currentCompilerId ] -- | Check that localBuildInfoFile is up-to-date with respect to the @@ -529,17 +531,17 @@ configure (pkg_descr0, pbi) cfg = do (enabledBuildInfos pkg_descr enabled) let langs = unsupportedLanguages comp langlist when (not (null langs)) $ - die' verbosity $ "The package " ++ display (packageId pkg_descr0) + die' verbosity $ "The package " ++ prettyShow (packageId pkg_descr0) ++ " requires the following languages which are not " - ++ "supported by " ++ display (compilerId comp) ++ ": " - ++ intercalate ", " (map display langs) + ++ "supported by " ++ prettyShow (compilerId comp) ++ ": " + ++ intercalate ", " (map prettyShow langs) let extlist = nub $ concatMap allExtensions (enabledBuildInfos pkg_descr enabled) let exts = unsupportedExtensions comp extlist when (not (null exts)) $ - die' verbosity $ "The package " ++ display (packageId pkg_descr0) + die' verbosity $ "The package " ++ prettyShow (packageId pkg_descr0) ++ " requires the following language extensions which are not " - ++ "supported by " ++ display (compilerId comp) ++ ": " - ++ intercalate ", " (map display exts) + ++ "supported by " ++ prettyShow (compilerId comp) ++ ": " + ++ intercalate ", " (map prettyShow exts) -- Check foreign library build requirements let flibs = [flib | CFLib flib <- enabledComponents pkg_descr enabled] @@ -763,8 +765,8 @@ configure (pkg_descr0, pbi) cfg = do ++ " support fully relocatable builds! " ++ " See #462 #2302 #2994 #3305 #3473 #3586 #3909 #4097 #4291 #4872" - info verbosity $ "Using " ++ display currentCabalId - ++ " compiled by " ++ display currentCompilerId + info verbosity $ "Using " ++ prettyShow currentCabalId + ++ " compiled by " ++ prettyShow currentCompilerId info verbosity $ "Using compiler: " ++ showCompilerId comp info verbosity $ "Using install prefix: " ++ prefix dirs @@ -949,7 +951,7 @@ configureFinalizedPackage verbosity cfg enabled Left missing -> die' verbosity $ "Encountered missing dependencies:\n" ++ (render . nest 4 . sep . punctuate comma - . map (disp . simplifyDependency) + . map (pretty . simplifyDependency) $ missing) -- add extra include/lib dirs as specified in cfg @@ -958,7 +960,7 @@ configureFinalizedPackage verbosity cfg enabled unless (nullFlagAssignment flags) $ info verbosity $ "Flags chosen: " - ++ intercalate ", " [ unFlagName fn ++ "=" ++ display value + ++ intercalate ", " [ unFlagName fn ++ "=" ++ prettyShow value | (fn, value) <- unFlagAssignment flags ] return (pkg_descr, flags) @@ -1038,7 +1040,7 @@ configureDependencies verbosity use_external_internal_deps when (not (null internalPkgDeps) && not (newPackageDepsBehaviour pkg_descr)) $ die' verbosity $ "The field 'build-depends: " - ++ intercalate ", " (map (display . packageName) internalPkgDeps) + ++ intercalate ", " (map (prettyShow . packageName) internalPkgDeps) ++ "' refers to a library which is defined within the same " ++ "package. To use this feature the package must specify at " ++ "least 'cabal-version: >= 1.8'." @@ -1160,7 +1162,7 @@ reportProgram verbosity prog (Just configuredProg) UserSpecified p -> " given by user at: " ++ p version = case programVersion configuredProg of Nothing -> "" - Just v -> " version " ++ display v + Just v -> " version " ++ prettyShow v hackageUrl :: String hackageUrl = "http://hackage.haskell.org/package/" @@ -1249,8 +1251,8 @@ reportSelectedDependencies :: Verbosity -> [ResolvedDependency] -> IO () reportSelectedDependencies verbosity deps = info verbosity $ unlines - [ "Dependency " ++ display (simplifyDependency dep) - ++ ": using " ++ display pkgid + [ "Dependency " ++ prettyShow (simplifyDependency dep) + ++ ": using " ++ prettyShow pkgid | (dep, resolution) <- deps , let pkgid = case resolution of ExternalDependency pkg' -> packageId pkg' @@ -1263,17 +1265,17 @@ reportFailedDependencies verbosity failed = where reportFailedDependency (DependencyNotExists pkgname) = - "there is no version of " ++ display pkgname ++ " installed.\n" + "there is no version of " ++ prettyShow pkgname ++ " installed.\n" ++ "Perhaps you need to download and install it from\n" - ++ hackageUrl ++ display pkgname ++ "?" + ++ hackageUrl ++ prettyShow pkgname ++ "?" reportFailedDependency (DependencyMissingInternal pkgname real_pkgname) = - "internal dependency " ++ display pkgname ++ " not installed.\n" + "internal dependency " ++ prettyShow pkgname ++ " not installed.\n" ++ "Perhaps you need to configure and install it first?\n" - ++ "(This library was defined by " ++ display real_pkgname ++ ")" + ++ "(This library was defined by " ++ prettyShow real_pkgname ++ ")" reportFailedDependency (DependencyNoVersion dep) = - "cannot satisfy dependency " ++ display (simplifyDependency dep) ++ "\n" + "cannot satisfy dependency " ++ prettyShow (simplifyDependency dep) ++ "\n" -- | List all installed packages in the given package databases. getInstalledPackages :: Verbosity -> Compiler @@ -1294,7 +1296,7 @@ getInstalledPackages verbosity comp packageDBs progdb = do HaskellSuite {} -> HaskellSuite.getInstalledPackages verbosity packageDBs progdb flv -> die' verbosity $ "don't know how to find the installed packages for " - ++ display flv + ++ prettyShow flv -- | Like 'getInstalledPackages', but for a single package DB. -- @@ -1327,7 +1329,7 @@ getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform = verbosity platform progdb packageDBs other -> do warn verbosity $ "don't know how to find change monitoring files for " - ++ "the installed package databases for " ++ display other + ++ "the installed package databases for " ++ prettyShow other return [] -- | The user interface specifies the package dbs to use with a combination of @@ -1404,7 +1406,7 @@ combinedConstraints constraints dependencies installedPackages = do dispDependencies deps = hsep [ text "--dependency=" - <<>> quotes (disp pkgname <<>> char '=' <<>> disp cid) + <<>> quotes (pretty pkgname <<>> char '=' <<>> pretty cid) | (pkgname, cid) <- deps ] -- ----------------------------------------------------------------------------- @@ -1507,7 +1509,7 @@ configurePkgconfigPackages verbosity pkg_descr progdb enabled version <- pkgconfig ["--modversion", pkg] `catchIO` (\_ -> die' verbosity notFound) `catchExit` (\_ -> die' verbosity notFound) - case simpleParse version of + case simpleParsec version of Nothing -> die' verbosity "parsing output of pkg-config --modversion failed" Just v | not (withinRange v range) -> die' verbosity (badVersion v) | otherwise -> info verbosity (depSatisfied v) @@ -1518,13 +1520,13 @@ configurePkgconfigPackages verbosity pkg_descr progdb enabled badVersion v = "The pkg-config package '" ++ pkg ++ "'" ++ versionRequirement ++ " is required but the version installed on the" - ++ " system is version " ++ display v - depSatisfied v = "Dependency " ++ display dep - ++ ": using version " ++ display v + ++ " system is version " ++ prettyShow v + depSatisfied v = "Dependency " ++ prettyShow dep + ++ ": using version " ++ prettyShow v versionRequirement | isAnyVersion range = "" - | otherwise = " version " ++ display range + | otherwise = " version " ++ prettyShow range pkg = unPkgconfigName pkgn @@ -1552,7 +1554,7 @@ configurePkgconfigPackages verbosity pkg_descr progdb enabled pkgconfigBuildInfo :: [PkgconfigDependency] -> NoCallStackIO BuildInfo pkgconfigBuildInfo [] = return mempty pkgconfigBuildInfo pkgdeps = do - let pkgs = nub [ display pkg | PkgconfigDependency pkg _ <- pkgdeps ] + let pkgs = nub [ prettyShow pkg | PkgconfigDependency pkg _ <- pkgdeps ] ccflags <- pkgconfig ("--cflags" : pkgs) ldflags <- pkgconfig ("--libs" : pkgs) return (ccLdOptionsBuildInfo (words ccflags) (words ldflags)) @@ -1876,7 +1878,7 @@ checkRelocatable verbosity pkg lbi -- Distribution.Simple.GHC.getRPaths checkOS = unless (os `elem` [ OSX, Linux ]) - $ die' verbosity $ "Operating system: " ++ display os ++ + $ die' verbosity $ "Operating system: " ++ prettyShow os ++ ", does not support relocatable builds" where (Platform _ os) = hostPlatform lbi diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index d871dfce38780373c77f13ba82d2b56494b5a01c..9353e39d45acea4ae446e860493ee0073baee0f1 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -101,7 +101,7 @@ import Distribution.Simple.Compiler hiding (Flag) import Distribution.Version import Distribution.System import Distribution.Verbosity -import Distribution.Text +import Distribution.Pretty import Distribution.Types.ForeignLib import Distribution.Types.ForeignLibType import Distribution.Types.ForeignLibOption @@ -141,8 +141,8 @@ configure verbosity hcPath hcPkgPath conf0 = do unless (ghcVersion < mkVersion [8,8]) $ warn verbosity $ "Unknown/unsupported 'ghc' version detected " - ++ "(Cabal " ++ display cabalVersion ++ " supports 'ghc' version < 8.8): " - ++ programPath ghcProg ++ " is version " ++ display ghcVersion + ++ "(Cabal " ++ prettyShow cabalVersion ++ " supports 'ghc' version < 8.8): " + ++ programPath ghcProg ++ " is version " ++ prettyShow ghcVersion -- This is slightly tricky, we have to configure ghc first, then we use the -- location of ghc to help find ghc-pkg in the case that the user did not @@ -155,8 +155,8 @@ configure verbosity hcPath hcPkgPath conf0 = do when (ghcVersion /= ghcPkgVersion) $ die' verbosity $ "Version mismatch between ghc and ghc-pkg: " - ++ programPath ghcProg ++ " is version " ++ display ghcVersion ++ " " - ++ programPath ghcPkgProg ++ " is version " ++ display ghcPkgVersion + ++ programPath ghcProg ++ " is version " ++ prettyShow ghcVersion ++ " " + ++ programPath ghcPkgProg ++ " is version " ++ prettyShow ghcPkgVersion -- Likewise we try to find the matching hsc2hs and haddock programs. let hsc2hsProgram' = hsc2hsProgram { @@ -532,7 +532,7 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do -- has the package name. I'm going to avoid changing this for -- now, but it would probably be better for this to be the -- component ID instead... - pkg_name = display (PD.package pkg_descr) + pkg_name = prettyShow (PD.package pkg_descr) distPref = fromFlag $ configDistPref $ configFlags lbi hpcdir way | forRepl = mempty -- HPC is not supported in ghci @@ -1119,7 +1119,7 @@ gbuildSources verbosity specVer tmpDir bm = -- specVersion < 2, as 'cabal-version:>=2.0' cabal files -- have no excuse anymore to keep doing it wrong... ;-) warn verbosity $ "Enabling workaround for Main module '" - ++ display mainModName + ++ prettyShow mainModName ++ "' listed in 'other-modules' illegally!" return BuildSources { @@ -1583,7 +1583,7 @@ extractRtsInfo lbi = } , rtsLibPaths = InstalledPackageInfo.libraryDirs rts } - withGhcVersion = (++ ("-ghc" ++ display (compilerVersion (compiler lbi)))) + withGhcVersion = (++ ("-ghc" ++ prettyShow (compilerVersion (compiler lbi)))) -- | Returns True if the modification date of the given source file is newer than -- the object file we last compiled for it, or if no object file exists yet. @@ -1919,7 +1919,7 @@ pkgRoot verbosity lbi = pkgRoot' appDir <- getAppUserDataDirectory "ghc" let ver = compilerVersion (compiler lbi) subdir = System.Info.arch ++ '-':System.Info.os - ++ '-':display ver + ++ '-':prettyShow ver rootDir = appDir </> subdir -- We must create the root directory for the user package database if it -- does not yet exists. Otherwise '${pkgroot}' will resolve to a diff --git a/Cabal/Distribution/Simple/GHC/Internal.hs b/Cabal/Distribution/Simple/GHC/Internal.hs index 118d551372e992d2fcb2b9cba5e011c23447f84a..b286c55fc72621cb8bded376146e592ef0510f48 100644 --- a/Cabal/Distribution/Simple/GHC/Internal.hs +++ b/Cabal/Distribution/Simple/GHC/Internal.hs @@ -65,7 +65,8 @@ import Distribution.Types.TargetInfo import Distribution.Simple.Utils import Distribution.Simple.BuildPaths import Distribution.System -import Distribution.Text ( display, simpleParse ) +import Distribution.Pretty ( prettyShow ) +import Distribution.Parsec.Class ( simpleParsec ) import Distribution.Utils.NubList ( toNubListR ) import Distribution.Verbosity import Distribution.Compat.Stack @@ -247,8 +248,8 @@ getExtensions verbosity implInfo ghcProg = do _ -> "No" ++ extStr , extStr'' <- [extStr, extStr'] ] - let extensions0 = [ (ext, Just $ "-X" ++ display ext) - | Just ext <- map simpleParse extStrs ] + let extensions0 = [ (ext, Just $ "-X" ++ prettyShow ext) + | Just ext <- map simpleParsec extStrs ] extensions1 = if alwaysNondecIndent implInfo then -- ghc-7.2 split NondecreasingIndentation off -- into a proper extension. Before that it @@ -517,7 +518,7 @@ profDetailLevelFlag forLib mpl = ghcArchString :: Arch -> String ghcArchString PPC = "powerpc" ghcArchString PPC64 = "powerpc64" -ghcArchString other = display other +ghcArchString other = prettyShow other -- | GHC's rendering of its host or target 'OS' as used in its platform -- strings and certain file locations (such as user package db location). @@ -526,7 +527,7 @@ ghcOsString :: OS -> String ghcOsString Windows = "mingw32" ghcOsString OSX = "darwin" ghcOsString Solaris = "solaris2" -ghcOsString other = display other +ghcOsString other = prettyShow other -- | GHC's rendering of its platform and compiler version string as used in -- certain file locations (such as user package db location). @@ -534,7 +535,7 @@ ghcOsString other = display other -- ghcPlatformAndVersionString :: Platform -> Version -> String ghcPlatformAndVersionString (Platform arch os) version = - intercalate "-" [ ghcArchString arch, ghcOsString os, display version ] + intercalate "-" [ ghcArchString arch, ghcOsString os, prettyShow version ] -- ----------------------------------------------------------------------------- @@ -599,7 +600,7 @@ renderGhcEnvironmentFileEntry :: GhcEnvironmentFileEntry -> String renderGhcEnvironmentFileEntry entry = case entry of GhcEnvFileComment comment -> format comment where format = intercalate "\n" . map ("-- " ++) . lines - GhcEnvFilePackageId pkgid -> "package-id " ++ display pkgid + GhcEnvFilePackageId pkgid -> "package-id " ++ prettyShow pkgid GhcEnvFilePackageDb pkgdb -> case pkgdb of GlobalPackageDB -> "global-package-db" diff --git a/Cabal/Distribution/Simple/GHCJS.hs b/Cabal/Distribution/Simple/GHCJS.hs index de05687fdccbf9d1e19fc9076ce6eb42f8737008..eddc816bd0b2ecd8d22c1eedf824da91309d2000 100644 --- a/Cabal/Distribution/Simple/GHCJS.hs +++ b/Cabal/Distribution/Simple/GHCJS.hs @@ -44,7 +44,7 @@ import Distribution.Version import Distribution.System import Distribution.Verbosity import Distribution.Utils.NubList -import Distribution.Text +import Distribution.Pretty import Distribution.Types.UnitId import qualified Data.Map as Map @@ -77,15 +77,15 @@ configure verbosity hcPath hcPkgPath progdb0 = do when (ghcjsVersion /= ghcjsPkgGhcjsVersion) $ die' verbosity $ "Version mismatch between ghcjs and ghcjs-pkg: " - ++ programPath ghcjsProg ++ " is version " ++ display ghcjsVersion ++ " " - ++ programPath ghcjsPkgProg ++ " is version " ++ display ghcjsPkgGhcjsVersion + ++ programPath ghcjsProg ++ " is version " ++ prettyShow ghcjsVersion ++ " " + ++ programPath ghcjsPkgProg ++ " is version " ++ prettyShow ghcjsPkgGhcjsVersion when (ghcjsGhcVersion /= ghcjsPkgVersion) $ die' verbosity $ "Version mismatch between ghcjs and ghcjs-pkg: " ++ programPath ghcjsProg - ++ " was built with GHC version " ++ display ghcjsGhcVersion ++ " " + ++ " was built with GHC version " ++ prettyShow ghcjsGhcVersion ++ " " ++ programPath ghcjsPkgProg - ++ " was built with GHC version " ++ display ghcjsPkgVersion + ++ " was built with GHC version " ++ prettyShow ghcjsPkgVersion -- be sure to use our versions of hsc2hs, c2hs, haddock and ghc let hsc2hsProgram' = @@ -304,7 +304,7 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do -- Determine if program coverage should be enabled and if so, what -- '-hpcdir' should be. let isCoverageEnabled = libCoverage lbi - pkg_name = display $ PD.package pkg_descr + pkg_name = prettyShow $ PD.package pkg_descr distPref = fromFlag $ configDistPref $ configFlags lbi hpcdir way | isCoverageEnabled = toFlag $ Hpc.mixDir distPref way pkg_name diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs index 94478d87b4765dccbc85884d0b47b3c4e6c657bb..fc22cc545ce9c89550baedd42fb02e8f05cb2ca1 100644 --- a/Cabal/Distribution/Simple/Haddock.hs +++ b/Cabal/Distribution/Simple/Haddock.hs @@ -60,7 +60,8 @@ import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo import Distribution.InstalledPackageInfo ( InstalledPackageInfo ) import Distribution.Simple.Utils import Distribution.System -import Distribution.Text +import Distribution.Pretty +import Distribution.Parsec.Class (simpleParsec) import Distribution.Utils.NubList import Distribution.Version import Distribution.Verbosity @@ -192,7 +193,7 @@ haddock pkg_descr lbi suffixes flags' = do haddockGhcVersionStr <- getProgramOutput verbosity haddockProg ["--ghc-version"] - case (simpleParse haddockGhcVersionStr, compilerCompatVersion GHC comp) of + case (simpleParsec haddockGhcVersionStr, compilerCompatVersion GHC comp) of (Nothing, _) -> die' verbosity "Could not get GHC version from Haddock" (_, Nothing) -> die' verbosity "Could not get GHC version from compiler" (Just haddockGhcVersion, Just ghcVersion) @@ -200,8 +201,8 @@ haddock pkg_descr lbi suffixes flags' = do | otherwise -> die' verbosity $ "Haddock's internal GHC version must match the configured " ++ "GHC version.\n" - ++ "The GHC version is " ++ display ghcVersion ++ " but " - ++ "haddock is using GHC version " ++ display haddockGhcVersion + ++ "The GHC version is " ++ prettyShow ghcVersion ++ " but " + ++ "haddock is using GHC version " ++ prettyShow haddockGhcVersion -- the tools match the requests, we can proceed @@ -357,7 +358,7 @@ fromPackageDescription haddockTarget pkg_descr = } where desc = PD.description pkg_descr - showPkg = display (packageId pkg_descr) + showPkg = prettyShow (packageId pkg_descr) subtitle | null (synopsis pkg_descr) = "" | otherwise = ": " ++ synopsis pkg_descr @@ -585,7 +586,7 @@ renderArgs verbosity tmpFileOpts version comp platform args k = do Hoogle -> pkgstr <.> "txt") $ arg argOutput where - pkgstr = display $ packageName pkgid + pkgstr = prettyShow $ packageName pkgid pkgid = arg argPackageName arg f = fromFlag $ f args @@ -595,8 +596,8 @@ renderPureArgs version comp platform args = concat . fromFlag . argInterfaceFile $ args , if isVersion 2 16 - then (\pkg -> [ "--package-name=" ++ display (pkgName pkg) - , "--package-version="++display (pkgVersion pkg) + then (\pkg -> [ "--package-name=" ++ prettyShow (pkgName pkg) + , "--package-version=" ++ prettyShow (pkgVersion pkg) ]) . fromFlag . argPackageName $ args else [] @@ -609,7 +610,7 @@ renderPureArgs version comp platform args = concat , [ "--hyperlinked-source" | isVersion 2 17 , fromFlag . argLinkedSource $ args ] - , (\(All b,xs) -> bool (map (("--hide=" ++). display) xs) [] b) + , (\(All b,xs) -> bool (map (("--hide=" ++) . prettyShow) xs) [] b) . argHideModules $ args , bool ["--ignore-all-exports"] [] . getAny . argIgnoreExports $ args @@ -717,7 +718,7 @@ haddockPackagePaths ipkgs mkHtmlPath = do let missing = [ pkgid | Left pkgid <- interfaces ] warning = "The documentation for the following packages are not " ++ "installed. No links will be generated to these packages: " - ++ intercalate ", " (map display missing) + ++ intercalate ", " (map prettyShow missing) flags = rights interfaces return (flags, if null missing then Nothing else Just warning) diff --git a/Cabal/Distribution/Simple/HaskellSuite.hs b/Cabal/Distribution/Simple/HaskellSuite.hs index 07a0fb03d8febc781640a8ac6ee01fe96811852c..85a8d30f42aba9bb4bca50f695b42742f90530df 100644 --- a/Cabal/Distribution/Simple/HaskellSuite.hs +++ b/Cabal/Distribution/Simple/HaskellSuite.hs @@ -14,7 +14,8 @@ import Distribution.Simple.Utils import Distribution.Simple.BuildPaths import Distribution.Verbosity import Distribution.Version -import Distribution.Text +import Distribution.Pretty +import Distribution.Parsec.Class (simpleParsec) import Distribution.Package import Distribution.InstalledPackageInfo hiding (includeDirs) import Distribution.Simple.PackageIndex as PackageIndex @@ -99,7 +100,7 @@ getCompilerVersion verbosity prog = do versionStr = last parts version <- maybe (die' verbosity "haskell-suite: couldn't determine compiler version") return $ - simpleParse versionStr + simpleParsec versionStr return (name, version) getExtensions :: Verbosity -> ConfiguredProgram -> IO [(Extension, Maybe Compiler.Flag)] @@ -108,7 +109,7 @@ getExtensions verbosity prog = do lines `fmap` rawSystemStdout verbosity (programPath prog) ["--supported-extensions"] return - [ (ext, Just $ "-X" ++ display ext) | Just ext <- map simpleParse extStrs ] + [ (ext, Just $ "-X" ++ prettyShow ext) | Just ext <- map simpleParsec extStrs ] getLanguages :: Verbosity -> ConfiguredProgram -> IO [(Language, Compiler.Flag)] getLanguages verbosity prog = do @@ -116,7 +117,7 @@ getLanguages verbosity prog = do lines `fmap` rawSystemStdout verbosity (programPath prog) ["--supported-languages"] return - [ (ext, "-G" ++ display ext) | Just ext <- map simpleParse langStrs ] + [ (ext, "-G" ++ prettyShow ext) | Just ext <- map simpleParsec langStrs ] -- Other compilers do some kind of a packagedb stack check here. Not sure -- if we need something like that as well. @@ -173,13 +174,13 @@ buildLib verbosity pkg_descr lbi lib clbi = do ,autogenPackageModulesDir lbi ,odir] ++ includeDirs bi ] ++ [ packageDbOpt pkgDb | pkgDb <- dbStack ] ++ - [ "--package-name", display pkgid ] ++ - concat [ ["--package-id", display ipkgid ] + [ "--package-name", prettyShow pkgid ] ++ + concat [ ["--package-id", prettyShow ipkgid ] | (ipkgid, _) <- componentPackageDeps clbi ] ++ - ["-G", display language] ++ - concat [ ["-X", display ex] | ex <- usedExtensions bi ] ++ + ["-G", prettyShow language] ++ + concat [ ["-X", prettyShow ex] | ex <- usedExtensions bi ] ++ cppOptions (libBuildInfo lib) ++ - [ display modu | modu <- allLibModules lib clbi ] + [ prettyShow modu | modu <- allLibModules lib clbi ] @@ -200,8 +201,8 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib clbi = do , "--build-dir", builtDir , "--target-dir", targetDir , "--dynlib-target-dir", dynlibTargetDir - , "--package-id", display $ packageId pkg - ] ++ map display (allLibModules lib clbi) + , "--package-id", prettyShow $ packageId pkg + ] ++ map prettyShow (allLibModules lib clbi) registerPackage :: Verbosity diff --git a/Cabal/Distribution/Simple/Install.hs b/Cabal/Distribution/Simple/Install.hs index 83305bc0dc5dedc8fd647e3db5a46567d8c29096..b13adfa8f14cb03abeb3bc242f0bbfe14a6a80ac 100644 --- a/Cabal/Distribution/Simple/Install.hs +++ b/Cabal/Distribution/Simple/Install.hs @@ -56,8 +56,8 @@ import System.FilePath ( takeFileName, takeDirectory, (</>), isRelative ) import Distribution.Verbosity -import Distribution.Text - ( display ) +import Distribution.Pretty + ( prettyShow ) -- |Perform the \"@.\/setup install@\" and \"@.\/setup copy@\" -- actions. Move files into place based on the prefix argument. @@ -166,7 +166,7 @@ copyComponent verbosity pkg_descr lbi (CLib lib) clbi copydest = do case libName lib of Nothing -> noticeNoWrap verbosity ("Installing library in " ++ libPref) - Just n -> noticeNoWrap verbosity ("Installing internal library " ++ display n ++ " in " ++ libPref) + Just n -> noticeNoWrap verbosity ("Installing internal library " ++ prettyShow n ++ " in " ++ libPref) -- install include files for all compilers - they may be needed to compile -- haskell files (using the CPP extension) @@ -179,7 +179,7 @@ copyComponent verbosity pkg_descr lbi (CLib lib) clbi copydest = do HaskellSuite _ -> HaskellSuite.installLib verbosity lbi libPref dynlibPref buildPref pkg_descr lib clbi _ -> die' verbosity $ "installing with " - ++ display (compilerFlavor (compiler lbi)) + ++ prettyShow (compilerFlavor (compiler lbi)) ++ " is not implemented" copyComponent verbosity pkg_descr lbi (CFLib flib) clbi copydest = do @@ -195,7 +195,7 @@ copyComponent verbosity pkg_descr lbi (CFLib flib) clbi copydest = do case compilerFlavor (compiler lbi) of GHC -> GHC.installFLib verbosity lbi flibPref buildPref pkg_descr flib _ -> die' verbosity $ "installing foreign lib with " - ++ display (compilerFlavor (compiler lbi)) + ++ prettyShow (compilerFlavor (compiler lbi)) ++ " is not implemented" copyComponent verbosity pkg_descr lbi (CExe exe) clbi copydest = do @@ -210,7 +210,7 @@ copyComponent verbosity pkg_descr lbi (CExe exe) clbi copydest = do progPrefixPref = substPathTemplate pkgid lbi uid (progPrefix lbi) progSuffixPref = substPathTemplate pkgid lbi uid (progSuffix lbi) progFix = (progPrefixPref, progSuffixPref) - noticeNoWrap verbosity ("Installing executable " ++ display (exeName exe) + noticeNoWrap verbosity ("Installing executable " ++ prettyShow (exeName exe) ++ " in " ++ binPref) inPath <- isInSearchPath binPref when (not inPath) $ @@ -222,7 +222,7 @@ copyComponent verbosity pkg_descr lbi (CExe exe) clbi copydest = do UHC -> return () HaskellSuite {} -> return () _ -> die' verbosity $ "installing with " - ++ display (compilerFlavor (compiler lbi)) + ++ prettyShow (compilerFlavor (compiler lbi)) ++ " is not implemented" -- Nothing to do for benchmark/testsuite diff --git a/Cabal/Distribution/Simple/InstallDirs.hs b/Cabal/Distribution/Simple/InstallDirs.hs index e63ea7361a3fa75e9d9c2c6cc862275b26c72de7..640dbf34419b46feb8f851e3c145d7c7cf6ad88a 100644 --- a/Cabal/Distribution/Simple/InstallDirs.hs +++ b/Cabal/Distribution/Simple/InstallDirs.hs @@ -52,10 +52,10 @@ import Prelude () import Distribution.Compat.Prelude import Distribution.Compat.Environment (lookupEnv) +import Distribution.Pretty import Distribution.Package import Distribution.System import Distribution.Compiler -import Distribution.Text import System.Directory (getAppUserDataDirectory) import System.FilePath @@ -430,29 +430,29 @@ initialPathTemplateEnv pkgId libname compiler platform = packageTemplateEnv :: PackageIdentifier -> UnitId -> PathTemplateEnv packageTemplateEnv pkgId uid = - [(PkgNameVar, PathTemplate [Ordinary $ display (packageName pkgId)]) - ,(PkgVerVar, PathTemplate [Ordinary $ display (packageVersion pkgId)]) + [(PkgNameVar, PathTemplate [Ordinary $ prettyShow (packageName pkgId)]) + ,(PkgVerVar, PathTemplate [Ordinary $ prettyShow (packageVersion pkgId)]) -- Invariant: uid is actually a HashedUnitId. Hard to enforce because -- it's an API change. - ,(LibNameVar, PathTemplate [Ordinary $ display uid]) - ,(PkgIdVar, PathTemplate [Ordinary $ display pkgId]) + ,(LibNameVar, PathTemplate [Ordinary $ prettyShow uid]) + ,(PkgIdVar, PathTemplate [Ordinary $ prettyShow pkgId]) ] compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv compilerTemplateEnv compiler = - [(CompilerVar, PathTemplate [Ordinary $ display (compilerInfoId compiler)]) + [(CompilerVar, PathTemplate [Ordinary $ prettyShow (compilerInfoId compiler)]) ] platformTemplateEnv :: Platform -> PathTemplateEnv platformTemplateEnv (Platform arch os) = - [(OSVar, PathTemplate [Ordinary $ display os]) - ,(ArchVar, PathTemplate [Ordinary $ display arch]) + [(OSVar, PathTemplate [Ordinary $ prettyShow os]) + ,(ArchVar, PathTemplate [Ordinary $ prettyShow arch]) ] abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv abiTemplateEnv compiler (Platform arch os) = - [(AbiVar, PathTemplate [Ordinary $ display arch ++ '-':display os ++ - '-':display (compilerInfoId compiler) ++ + [(AbiVar, PathTemplate [Ordinary $ prettyShow arch ++ '-':prettyShow os ++ + '-':prettyShow (compilerInfoId compiler) ++ case compilerInfoAbiTag compiler of NoAbiTag -> "" AbiTag tag -> '-':tag]) diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs index 6454ca6b5908d1270cb7a60a39420c073bf94c9e..8258955c81c18c1bf46d4f7e37867b7b430a3afe 100644 --- a/Cabal/Distribution/Simple/LocalBuildInfo.hs +++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs @@ -89,7 +89,7 @@ import Distribution.ModuleName import Distribution.Simple.Compiler import Distribution.Simple.PackageIndex import Distribution.Simple.Utils -import Distribution.Text +import Distribution.Pretty import qualified Distribution.Compat.Graph as Graph import Data.List (stripPrefix) @@ -109,13 +109,13 @@ componentBuildDir lbi clbi = buildDir lbi </> case componentLocalName clbi of CLibName -> - if display (componentUnitId clbi) == display (componentComponentId clbi) + if prettyShow (componentUnitId clbi) == prettyShow (componentComponentId clbi) then "" - else display (componentUnitId clbi) + else prettyShow (componentUnitId clbi) CSubLibName s -> - if display (componentUnitId clbi) == display (componentComponentId clbi) + if prettyShow (componentUnitId clbi) == prettyShow (componentComponentId clbi) then unUnqualComponentName s - else display (componentUnitId clbi) + else prettyShow (componentUnitId clbi) CFLibName s -> unUnqualComponentName s CExeName s -> unUnqualComponentName s CTestName s -> unUnqualComponentName s @@ -132,7 +132,7 @@ getComponentLocalBuildInfo lbi cname = clbis -> error $ "internal error: the component name " ++ show cname ++ "is ambiguous. Refers to: " - ++ intercalate ", " (map (display . componentUnitId) clbis) + ++ intercalate ", " (map (prettyShow . componentUnitId) clbis) -- | Perform the action on each enabled 'library' in the package -- description with the 'ComponentLocalBuildInfo'. @@ -217,7 +217,7 @@ componentNameToUnitIds :: LocalBuildInfo -> ComponentName -> [UnitId] componentNameToUnitIds lbi cname = case Map.lookup cname (componentNameMap lbi) of Just clbis -> map componentUnitId clbis - Nothing -> error $ "componentNameToUnitIds " ++ display cname + Nothing -> error $ "componentNameToUnitIds " ++ prettyShow cname {-# DEPRECATED componentsInBuildOrder "You've got 'TargetInfo' right? Use 'neededTargetsInBuildOrder' on the 'UnitId's you can 'nodeKey' out." #-} componentsInBuildOrder :: LocalBuildInfo -> [ComponentName] diff --git a/Cabal/Distribution/Simple/PreProcess.hs b/Cabal/Distribution/Simple/PreProcess.hs index 493302829420140b1fd0f8d5cd07f76459f73040..daf419ef2be1d062aee289dff94e8df61f5136cb 100644 --- a/Cabal/Distribution/Simple/PreProcess.hs +++ b/Cabal/Distribution/Simple/PreProcess.hs @@ -50,7 +50,7 @@ import Distribution.Simple.Program import Distribution.Simple.Program.ResponseFile import Distribution.Simple.Test.LibV09 import Distribution.System -import Distribution.Text +import Distribution.Pretty import Distribution.Version import Distribution.Verbosity import Distribution.Types.ForeignLib @@ -191,7 +191,7 @@ preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers = do preProcessTest test (stubFilePath test) testDir TestSuiteUnsupported tt -> die' verbosity $ "No support for preprocessing test " - ++ "suite type " ++ display tt + ++ "suite type " ++ prettyShow tt CBench bm@Benchmark{ benchmarkName = nm } -> do let nm' = unUnqualComponentName nm case benchmarkInterface bm of @@ -199,7 +199,7 @@ preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers = do preProcessBench bm f $ buildDir lbi </> nm' </> nm' ++ "-tmp" BenchmarkUnsupported tt -> die' verbosity $ "No support for preprocessing benchmark " - ++ "type " ++ display tt + ++ "type " ++ prettyShow tt where builtinHaskellSuffixes = ["hs", "lhs", "hsig", "lhsig"] builtinCSuffixes = cSourceExtensions @@ -719,7 +719,7 @@ preprocessExtras verbosity comp lbi = case comp of TestSuiteLibV09 _ _ -> pp $ buildDir lbi </> stubName test </> stubName test ++ "-tmp" TestSuiteUnsupported tt -> die' verbosity $ "No support for preprocessing test " - ++ "suite type " ++ display tt + ++ "suite type " ++ prettyShow tt CBench bm -> do let nm' = unUnqualComponentName $ benchmarkName bm case benchmarkInterface bm of @@ -727,7 +727,7 @@ preprocessExtras verbosity comp lbi = case comp of pp $ buildDir lbi </> nm' </> nm' ++ "-tmp" BenchmarkUnsupported tt -> die' verbosity $ "No support for preprocessing benchmark " - ++ "type " ++ display tt + ++ "type " ++ prettyShow tt where pp :: FilePath -> IO [FilePath] pp dir = (map (dir </>) . filter not_sub . concat) diff --git a/Cabal/Distribution/Simple/Program/Db.hs b/Cabal/Distribution/Simple/Program/Db.hs index 4aba5e8ae8a6eea986bcb5950afa8660fb102ad1..520601bf7bf1cf5322a509b68cf25234ed185f92 100644 --- a/Cabal/Distribution/Simple/Program/Db.hs +++ b/Cabal/Distribution/Simple/Program/Db.hs @@ -68,7 +68,7 @@ import Distribution.Simple.Program.Find import Distribution.Simple.Program.Builtin import Distribution.Simple.Utils import Distribution.Version -import Distribution.Text +import Distribution.Pretty import Distribution.Verbosity import Control.Monad (join) @@ -465,14 +465,14 @@ lookupProgramVersion verbosity prog range programDb = do badVersion v l = "The program '" ++ programName prog ++ "'" ++ versionRequirement ++ " is required but the version found at " - ++ locationPath l ++ " is version " ++ display v + ++ locationPath l ++ " is version " ++ prettyShow v unknownVersion l = "The program '" ++ programName prog ++ "'" ++ versionRequirement ++ " is required but the version of " ++ locationPath l ++ " could not be determined." versionRequirement | isAnyVersion range = "" - | otherwise = " version " ++ display range + | otherwise = " version " ++ prettyShow range -- | Like 'lookupProgramVersion', but raises an exception in case of error -- instead of returning 'Left errMsg'. diff --git a/Cabal/Distribution/Simple/Program/GHC.hs b/Cabal/Distribution/Simple/Program/GHC.hs index 8d8c052968a85c89badba76ffa297a5e43cf470b..c1850c0510747eb9cec335d8523b3b2aa68c1c89 100644 --- a/Cabal/Distribution/Simple/Program/GHC.hs +++ b/Cabal/Distribution/Simple/Program/GHC.hs @@ -33,7 +33,7 @@ import Distribution.Simple.Flag import Distribution.Simple.Program.Types import Distribution.Simple.Program.Run import Distribution.System -import Distribution.Text +import Distribution.Pretty import Distribution.Types.ComponentId import Distribution.Verbosity import Distribution.Version @@ -626,14 +626,14 @@ renderGhcOptions comp _platform@(Platform _arch os) opts , this_arg ] | this_arg <- flag ghcOptThisUnitId ] - , concat [ ["-this-component-id", display this_cid ] + , concat [ ["-this-component-id", prettyShow this_cid ] | this_cid <- flag ghcOptThisComponentId ] , if null (ghcOptInstantiatedWith opts) then [] else "-instantiated-with" - : intercalate "," (map (\(n,m) -> display n ++ "=" - ++ display m) + : intercalate "," (map (\(n,m) -> prettyShow n ++ "=" + ++ prettyShow m) (ghcOptInstantiatedWith opts)) : [] @@ -647,14 +647,14 @@ renderGhcOptions comp _platform@(Platform _arch os) opts , concat $ let space "" = "" space xs = ' ' : xs - in [ ["-package-id", display ipkgid ++ space (display rns)] + in [ ["-package-id", prettyShow ipkgid ++ space (prettyShow rns)] | (ipkgid,rns) <- flags ghcOptPackages ] ---------------------------- -- Language and extensions , if supportsHaskell2010 implInfo - then [ "-X" ++ display lang | lang <- flag ghcOptLanguage ] + then [ "-X" ++ prettyShow lang | lang <- flag ghcOptLanguage ] else [] , [ ext' @@ -664,7 +664,7 @@ renderGhcOptions comp _platform@(Platform _arch os) opts Just Nothing -> [] Nothing -> error $ "Distribution.Simple.Program.GHC.renderGhcOptions: " - ++ display ext ++ " not present in ghcOptExtensionMap." + ++ prettyShow ext ++ " not present in ghcOptExtensionMap." ] ---------------- @@ -676,7 +676,7 @@ renderGhcOptions comp _platform@(Platform _arch os) opts --------------- -- Inputs - , [ display modu | modu <- flags ghcOptInputModules ] + , [ prettyShow modu | modu <- flags ghcOptInputModules ] , flags ghcOptInputFiles , concat [ [ "-o", out] | out <- flag ghcOptOutputFile ] diff --git a/Cabal/Distribution/Simple/Program/HcPkg.hs b/Cabal/Distribution/Simple/Program/HcPkg.hs index c1b7cd3a94b300de05d74615ce00b9c3e3ea818a..84730333a6853002b9a6fcce97e1ea2544d8c5c6 100644 --- a/Cabal/Distribution/Simple/Program/HcPkg.hs +++ b/Cabal/Distribution/Simple/Program/HcPkg.hs @@ -50,7 +50,8 @@ import Distribution.Simple.Compiler import Distribution.Simple.Program.Types import Distribution.Simple.Program.Run import Distribution.Simple.Utils -import Distribution.Text +import Distribution.Parsec.Class +import Distribution.Pretty import Distribution.Types.ComponentId import Distribution.Types.PackageId import Distribution.Types.UnitId @@ -173,7 +174,7 @@ writeRegistrationFileDirectly :: Verbosity -> IO () writeRegistrationFileDirectly verbosity hpi (SpecificPackageDB dir) pkgInfo | supportsDirDbs hpi - = do let pkgfile = dir </> display (installedUnitId pkgInfo) <.> "conf" + = do let pkgfile = dir </> prettyShow (installedUnitId pkgInfo) <.> "conf" writeUTF8File pkgfile (showInstalledPackageInfo pkgInfo) | otherwise @@ -228,7 +229,7 @@ describe hpi verbosity packagedb pid = do case parsePackages output of Left ok -> return ok _ -> die' verbosity $ "failed to parse output of '" - ++ programId (hcPkgProgram hpi) ++ " describe " ++ display pid ++ "'" + ++ programId (hcPkgProgram hpi) ++ " describe " ++ prettyShow pid ++ "'" -- | Call @hc-pkg@ to hide a package. -- @@ -330,7 +331,7 @@ setUnitId pkginfo@InstalledPackageInfo { } | unUnitId uid == "" = pkginfo { installedUnitId = mkLegacyUnitId pid, - installedComponentId_ = mkComponentId (display pid) + installedComponentId_ = mkComponentId (prettyShow pid) } setUnitId pkginfo = pkginfo @@ -356,7 +357,7 @@ list hpi verbosity packagedb = do ++ programId (hcPkgProgram hpi) ++ " list'" where - parsePackageIds = traverse simpleParse . words + parsePackageIds = traverse simpleParsec . words -------------------------- -- The program invocations @@ -399,7 +400,7 @@ unregisterInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> ProgramInvocation unregisterInvocation hpi verbosity packagedb pkgid = programInvocation (hcPkgProgram hpi) $ - ["unregister", packageDbOpts hpi packagedb, display pkgid] + ["unregister", packageDbOpts hpi packagedb, prettyShow pkgid] ++ verbosityOpts hpi verbosity @@ -415,14 +416,14 @@ exposeInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> ProgramInvocation exposeInvocation hpi verbosity packagedb pkgid = programInvocation (hcPkgProgram hpi) $ - ["expose", packageDbOpts hpi packagedb, display pkgid] + ["expose", packageDbOpts hpi packagedb, prettyShow pkgid] ++ verbosityOpts hpi verbosity describeInvocation :: HcPkgInfo -> Verbosity -> PackageDBStack -> PackageId -> ProgramInvocation describeInvocation hpi verbosity packagedbs pkgid = programInvocation (hcPkgProgram hpi) $ - ["describe", display pkgid] + ["describe", prettyShow pkgid] ++ (if noPkgDbStack hpi then [packageDbOpts hpi (last packagedbs)] else packageDbStackOpts hpi packagedbs) @@ -432,7 +433,7 @@ hideInvocation :: HcPkgInfo -> Verbosity -> PackageDB -> PackageId -> ProgramInvocation hideInvocation hpi verbosity packagedb pkgid = programInvocation (hcPkgProgram hpi) $ - ["hide", packageDbOpts hpi packagedb, display pkgid] + ["hide", packageDbOpts hpi packagedb, prettyShow pkgid] ++ verbosityOpts hpi verbosity diff --git a/Cabal/Distribution/Simple/Program/Hpc.hs b/Cabal/Distribution/Simple/Program/Hpc.hs index 7d39bf7a770cb31bfb69ab4201a3393957a5aab6..152e382ac4a9a6eb5e62a9f6c0813c71d4944b58 100644 --- a/Cabal/Distribution/Simple/Program/Hpc.hs +++ b/Cabal/Distribution/Simple/Program/Hpc.hs @@ -25,7 +25,7 @@ import System.Directory (makeRelativeToCurrentDirectory) import Distribution.ModuleName import Distribution.Simple.Program.Run import Distribution.Simple.Program.Types -import Distribution.Text +import Distribution.Pretty import Distribution.Simple.Utils import Distribution.Verbosity import Distribution.Version @@ -49,7 +49,7 @@ markup hpc hpcVer verbosity tixFile hpcDirs destDir excluded = do hpcDirs' <- if withinRange hpcVer (orLaterVersion version07) then return hpcDirs else do - warn verbosity $ "Your version of HPC (" ++ display hpcVer + warn verbosity $ "Your version of HPC (" ++ prettyShow hpcVer ++ ") does not properly handle multiple search paths. " ++ "Coverage report generation may fail unexpectedly. These " ++ "issues are addressed in version 0.7 or later (GHC 7.8 or " @@ -82,7 +82,7 @@ markupInvocation hpc tixFile hpcDirs destDir excluded = , "--destdir=" ++ destDir ] ++ map ("--hpcdir=" ++) hpcDirs - ++ ["--exclude=" ++ display moduleName + ++ ["--exclude=" ++ prettyShow moduleName | moduleName <- excluded ] in programInvocation hpc args @@ -106,6 +106,6 @@ unionInvocation hpc tixFiles outFile excluded = [ ["sum", "--union"] , tixFiles , ["--output=" ++ outFile] - , ["--exclude=" ++ display moduleName + , ["--exclude=" ++ prettyShow moduleName | moduleName <- excluded ] ] diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs index 461b3123de85f68cbb89e7d735edf862b993b7b5..f3a098ab982a56ccfe73abc90e437b5bc7dc25ef 100644 --- a/Cabal/Distribution/Simple/Register.hs +++ b/Cabal/Distribution/Simple/Register.hs @@ -79,7 +79,7 @@ import Distribution.InstalledPackageInfo (InstalledPackageInfo) import Distribution.Simple.Utils import Distribution.Utils.MapAccum import Distribution.System -import Distribution.Text +import Distribution.Pretty import Distribution.Types.ComponentName import Distribution.Verbosity as Verbosity import Distribution.Version @@ -158,7 +158,7 @@ registerAll pkg lbi regFlags ipis -- Only print the public library's IPI when (packageId installedPkgInfo == packageId pkg && IPI.sourceLibName installedPkgInfo == Nothing) $ - putStrLn (display (IPI.installedUnitId installedPkgInfo)) + putStrLn (prettyShow (IPI.installedUnitId installedPkgInfo)) -- Three different modes: case () of @@ -174,7 +174,7 @@ registerAll pkg lbi regFlags ipis where modeGenerateRegFile = isJust (flagToMaybe (regGenPkgConf regFlags)) - regFile = fromMaybe (display (packageId pkg) <.> "conf") + regFile = fromMaybe (prettyShow (packageId pkg) <.> "conf") (fromFlag (regGenPkgConf regFlags)) modeGenerateRegScript = fromFlag (regGenScript regFlags) @@ -201,7 +201,7 @@ registerAll pkg lbi regFlags ipis where ys = take m xs number i = lpad (length (show num_ipis)) (show i) for_ (zip ([1..] :: [Int]) ipis) $ \(i, installedPkgInfo) -> - writeUTF8File (regFile </> (number i ++ "-" ++ display (IPI.installedUnitId installedPkgInfo))) + writeUTF8File (regFile </> (number i ++ "-" ++ prettyShow (IPI.installedUnitId installedPkgInfo))) (IPI.showInstalledPackageInfo installedPkgInfo) writeRegisterScript = @@ -512,7 +512,7 @@ inplaceInstalledPackageInfo inplaceDir distPref pkg abi_hash lib lbi clbi = haddockdir = inplaceHtmldir } inplaceDocdir = inplaceDir </> distPref </> "doc" - inplaceHtmldir = inplaceDocdir </> "html" </> display (packageName pkg) + inplaceHtmldir = inplaceDocdir </> "html" </> prettyShow (packageName pkg) -- | Construct 'InstalledPackageInfo' for the final install location of a diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs index 032ea2f4a7b7e8b1a063d91038cb4c74fb5bdf6c..1e1815d4ab18f190f6e75b76e4bd0d54f0e2fd4f 100644 --- a/Cabal/Distribution/Simple/Setup.hs +++ b/Cabal/Distribution/Simple/Setup.hs @@ -75,19 +75,16 @@ module Distribution.Simple.Setup ( maybeToFlag, BooleanFlag(..), boolOpt, boolOpt', trueArg, falseArg, - optionVerbosity, optionNumJobs, readPToMaybe ) where + optionVerbosity, optionNumJobs) where import Prelude () import Distribution.Compat.Prelude hiding (get) import Distribution.Compiler import Distribution.ReadE -import Distribution.Text import Distribution.Parsec.Class import Distribution.Pretty -import qualified Distribution.Compat.ReadP as Parse import qualified Distribution.Compat.CharParsing as P -import Distribution.ParseUtils (readPToMaybe) import qualified Text.PrettyPrint as Disp import Distribution.ModuleName import Distribution.PackageDescription hiding (Flag) @@ -110,6 +107,10 @@ import Distribution.Compat.Semigroup (Last' (..)) import Data.Function (on) +-- To be removed +import Distribution.Text (Text (..)) +import qualified Distribution.Compat.ReadP as Parse + -- FIXME Not sure where this should live defaultDistPref :: FilePath defaultDistPref = "dist" @@ -421,7 +422,7 @@ parsecModSubstEntry = do -- | Pretty-print a single entry of a module substitution. dispModSubstEntry :: (ModuleName, Module) -> Disp.Doc -dispModSubstEntry (k, v) = disp k <<>> Disp.char '=' <<>> disp v +dispModSubstEntry (k, v) = pretty k <<>> Disp.char '=' <<>> pretty v configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags] configureOptions showOrParseArgs = @@ -616,7 +617,7 @@ configureOptions showOrParseArgs = ,option "" ["cid"] "Installed component ID to compile this component as" - (fmap display . configCID) (\v flags -> flags {configCID = fmap mkComponentId v}) + (fmap prettyShow . configCID) (\v flags -> flags {configCID = fmap mkComponentId v}) (reqArgFlag "CID") ,option "" ["extra-lib-dirs"] @@ -640,14 +641,14 @@ configureOptions showOrParseArgs = configConstraints (\v flags -> flags { configConstraints = v}) (reqArg "DEPENDENCY" (parsecToReadE (const "dependency expected") ((\x -> [x]) `fmap` parsec)) - (map display)) + (map prettyShow)) ,option "" ["dependency"] "A list of exact dependencies. E.g., --dependency=\"void=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\"" configDependencies (\v flags -> flags { configDependencies = v}) (reqArg "NAME=CID" (parsecToReadE (const "dependency expected") ((\x -> [x]) `fmap` parsecDependency)) - (map (\x -> display (fst x) ++ "=" ++ display (snd x)))) + (map (\x -> prettyShow (fst x) ++ "=" ++ prettyShow (snd x)))) ,option "" ["instantiate-with"] "A mapping of signature names to concrete module instantiations." @@ -1357,13 +1358,19 @@ data HaddockTarget = ForHackage | ForDevelopment deriving (Eq, Show, Generic) instance Binary HaddockTarget -instance Text HaddockTarget where - disp ForHackage = Disp.text "for-hackage" - disp ForDevelopment = Disp.text "for-development" +instance Pretty HaddockTarget where + pretty ForHackage = Disp.text "for-hackage" + pretty ForDevelopment = Disp.text "for-development" + +instance Parsec HaddockTarget where + parsec = P.choice [ P.try $ P.string "for-hackage" >> return ForHackage + , P.string "for-development" >> return ForDevelopment] +instance Text HaddockTarget where parse = Parse.choice [ Parse.string "for-hackage" >> return ForHackage , Parse.string "for-development" >> return ForDevelopment] + data HaddockFlags = HaddockFlags { haddockProgramPaths :: [(String, FilePath)], haddockProgramArgs :: [(String, [String])], @@ -1825,16 +1832,7 @@ instance Parsec TestShowDetails where ident = P.munch1 (\c -> isAlpha c || c == '_' || c == '-') classify str = lookup (lowercase str) enumMap enumMap :: [(String, TestShowDetails)] - enumMap = [ (display x, x) - | x <- knownTestShowDetails ] - -instance Text TestShowDetails where - parse = maybe Parse.pfail return . classify =<< ident - where - ident = Parse.munch1 (\c -> isAlpha c || c == '_' || c == '-') - classify str = lookup (lowercase str) enumMap - enumMap :: [(String, TestShowDetails)] - enumMap = [ (display x, x) + enumMap = [ (prettyShow x, x) | x <- knownTestShowDetails ] --TODO: do we need this instance? @@ -1917,9 +1915,9 @@ testCommand = CommandUI (reqArg "FILTER" (parsecToReadE (\_ -> "--show-details flag expects one of " ++ intercalate ", " - (map display knownTestShowDetails)) + (map prettyShow knownTestShowDetails)) (fmap toFlag parsec)) - (flagToList . fmap display)) + (flagToList . fmap prettyShow)) , option [] ["keep-tix-files"] "keep .tix files for HPC between test runs" testKeepTix (\v flags -> flags { testKeepTix = v}) @@ -2211,7 +2209,7 @@ configureArgs bcHack flags where hc_flag = case (configHcFlavor flags, configHcPath flags) of (_, Flag hc_path) -> [hc_flag_name ++ hc_path] - (Flag hc, NoFlag) -> [hc_flag_name ++ display hc] + (Flag hc, NoFlag) -> [hc_flag_name ++ prettyShow hc] (NoFlag,NoFlag) -> [] hc_flag_name --TODO kill off thic bc hack when defaultUserHooks is removed. diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs index 88368dae7c9ae3115cd2ad9033bbae808349c337..0331dcd24fc7860b8209ad60cd468b81d842daa7 100644 --- a/Cabal/Distribution/Simple/SrcDist.hs +++ b/Cabal/Distribution/Simple/SrcDist.hs @@ -59,7 +59,7 @@ import Distribution.Simple.PreProcess import Distribution.Simple.LocalBuildInfo import Distribution.Simple.BuildPaths import Distribution.Simple.Program -import Distribution.Text +import Distribution.Pretty import Distribution.Types.ForeignLib import Distribution.Verbosity @@ -375,7 +375,7 @@ overwriteSnapshotPackageDesc verbosity pkg targetDir = do replaceVersion :: Version -> String -> String replaceVersion version line | "version:" `isPrefixOf` map toLower line - = "version: " ++ display version + = "version: " ++ prettyShow version | otherwise = line -- | Modifies a 'PackageDescription' by appending a snapshot number @@ -460,7 +460,7 @@ allSourcesBuildInfo verbosity bi pps modules = do nonEmpty x _ [] = x nonEmpty _ f xs = f xs suffixes = ppSuffixes pps ++ ["hs", "lhs", "hsig", "lhsig"] - notFound m = die' verbosity $ "Error: Could not find module: " ++ display m + notFound m = die' verbosity $ "Error: Could not find module: " ++ prettyShow m ++ " with any suffix: " ++ show suffixes ++ ". If the module " ++ "is autogenerated it should be added to 'autogen-modules'." @@ -490,7 +490,7 @@ printPackageProblems verbosity pkg_descr = do -- | The name of the tarball without extension -- tarBallName :: PackageDescription -> String -tarBallName = display . packageId +tarBallName = prettyShow . packageId mapAllBuildInfo :: (BuildInfo -> BuildInfo) -> (PackageDescription -> PackageDescription) diff --git a/Cabal/Distribution/Simple/Test.hs b/Cabal/Distribution/Simple/Test.hs index 50169ecbc23d44d2bd2df6191e9b6f3aebcbe324..5547c7379887773930ce821b5780d51f99087769 100644 --- a/Cabal/Distribution/Simple/Test.hs +++ b/Cabal/Distribution/Simple/Test.hs @@ -35,7 +35,7 @@ import qualified Distribution.Simple.Test.LibV09 as LibV09 import Distribution.Simple.Test.Log import Distribution.Simple.Utils import Distribution.TestSuite -import Distribution.Text +import Distribution.Pretty import System.Directory ( createDirectoryIfMissing, doesFileExist, getDirectoryContents @@ -75,7 +75,7 @@ test args pkg_descr lbi flags = do , testOptionsReturned = [] , testResult = Error $ "No support for running test suite type: " - ++ show (disp $ PD.testType suite) + ++ show (pretty $ PD.testType suite) } , logFile = "" } @@ -120,7 +120,7 @@ test args pkg_descr lbi flags = do writeFile packageLogFile $ show packageLog when (LBI.testCoverage lbi) $ - markupPackage verbosity lbi distPref (display $ PD.package pkg_descr) $ + markupPackage verbosity lbi distPref (prettyShow $ PD.package pkg_descr) $ map (fst . fst) testsToRun unless allOk exitFailure diff --git a/Cabal/Distribution/Simple/Test/ExeV10.hs b/Cabal/Distribution/Simple/Test/ExeV10.hs index 3f814feaee121203fb110a99c82188bf66dde50b..e67c019783f7f49d386a08838ca94387334a03a3 100644 --- a/Cabal/Distribution/Simple/Test/ExeV10.hs +++ b/Cabal/Distribution/Simple/Test/ExeV10.hs @@ -24,7 +24,7 @@ import Distribution.Simple.Test.Log import Distribution.Simple.Utils import Distribution.System import Distribution.TestSuite -import Distribution.Text +import Distribution.Pretty import Distribution.Verbosity import Control.Concurrent (forkIO) @@ -129,7 +129,7 @@ runTest pkg_descr lbi clbi flags suite = do notice verbosity $ summarizeSuiteFinish suiteLog when isCoverageEnabled $ - markupTest verbosity lbi distPref (display $ PD.package pkg_descr) suite + markupTest verbosity lbi distPref (prettyShow $ PD.package pkg_descr) suite return suiteLog where diff --git a/Cabal/Distribution/Simple/Test/LibV09.hs b/Cabal/Distribution/Simple/Test/LibV09.hs index b1d91c07871755ad1d30f81d0ea93b13daa37795..787990997ab378482839ff7f8e29a2027e724683 100644 --- a/Cabal/Distribution/Simple/Test/LibV09.hs +++ b/Cabal/Distribution/Simple/Test/LibV09.hs @@ -30,7 +30,7 @@ import Distribution.Simple.Test.Log import Distribution.Simple.Utils import Distribution.System import Distribution.TestSuite -import Distribution.Text +import Distribution.Pretty import Distribution.Verbosity import qualified Control.Exception as CE @@ -148,7 +148,7 @@ runTest pkg_descr lbi clbi flags suite = do notice verbosity $ summarizeSuiteFinish suiteLog when isCoverageEnabled $ - markupTest verbosity lbi distPref (display $ PD.package pkg_descr) suite + markupTest verbosity lbi distPref (prettyShow $ PD.package pkg_descr) suite return suiteLog where @@ -209,7 +209,7 @@ simpleTestStub :: ModuleName -> String simpleTestStub m = unlines [ "module Main ( main ) where" , "import Distribution.Simple.Test.LibV09 ( stubMain )" - , "import " ++ show (disp m) ++ " ( tests )" + , "import " ++ show (pretty m) ++ " ( tests )" , "main :: IO ()" , "main = stubMain tests" ] diff --git a/Cabal/Distribution/Simple/Test/Log.hs b/Cabal/Distribution/Simple/Test/Log.hs index 85d95a07916f29cf24f0907ba63acc35f42db41f..359bbcedbce80450866d707a7dcefa97851b2c65 100644 --- a/Cabal/Distribution/Simple/Test/Log.hs +++ b/Cabal/Distribution/Simple/Test/Log.hs @@ -28,7 +28,7 @@ import Distribution.Simple.Utils import Distribution.System import Distribution.TestSuite import Distribution.Verbosity -import Distribution.Text +import Distribution.Pretty -- | Logs all test results for a package, broken down first by test suite and -- then by test case. @@ -155,7 +155,7 @@ summarizeTest verbosity details t = -- output for certain verbosity or test filter levels. summarizeSuiteFinish :: TestSuiteLog -> String summarizeSuiteFinish testLog = unlines - [ "Test suite " ++ display (testSuiteName testLog) ++ ": " ++ resStr + [ "Test suite " ++ prettyShow (testSuiteName testLog) ++ ": " ++ resStr , "Test suite logged to: " ++ logFile testLog ] where resStr = map toUpper (resultString $ testLogs testLog) diff --git a/Cabal/Distribution/Simple/UHC.hs b/Cabal/Distribution/Simple/UHC.hs index 9d4c414e0737d1298250234c8ca00143a34384e5..7bcc508310d3434824d51f684d51162e9d0e05d5 100644 --- a/Cabal/Distribution/Simple/UHC.hs +++ b/Cabal/Distribution/Simple/UHC.hs @@ -24,8 +24,8 @@ module Distribution.Simple.UHC ( import Prelude () import Distribution.Compat.Prelude +import Data.Foldable (toList) -import Distribution.Compat.ReadP import Distribution.InstalledPackageInfo import Distribution.Package hiding (installedUnitId) import Distribution.PackageDescription @@ -35,7 +35,8 @@ import Distribution.Simple.LocalBuildInfo import Distribution.Simple.PackageIndex import Distribution.Simple.Program import Distribution.Simple.Utils -import Distribution.Text +import Distribution.Pretty +import Distribution.Parsec.Class import Distribution.Types.MungedPackageId import Distribution.Verbosity import Distribution.Version @@ -102,7 +103,7 @@ getInstalledPackages verbosity comp packagedbs progdb = do let pkgDirs = nub (concatMap (packageDbPaths userPkgDir systemPkgDir) packagedbs) -- putStrLn $ "pkgdirs: " ++ show pkgDirs pkgs <- liftM (map addBuiltinVersions . concat) $ - traverse (\ d -> getDirectoryContents d >>= filterM (isPkgDir (display compilerid) d)) + traverse (\ d -> getDirectoryContents d >>= filterM (isPkgDir (prettyShow compilerid) d)) pkgDirs -- putStrLn $ "pkgs: " ++ show pkgs let iPkgs = @@ -157,7 +158,7 @@ isPkgDir c dir xs = do doesFileExist (candidate </> installedPkgConfig) parsePackage :: String -> [PackageId] -parsePackage x = map fst (filter (\ (_,y) -> null y) (readP_to_S parse x)) +parsePackage = toList . simpleParsec -- | Create a trivial package info from a directory name. mkInstalledPackageInfo :: PackageId -> InstalledPackageInfo @@ -177,7 +178,7 @@ buildLib verbosity pkg_descr lbi lib clbi = do userPkgDir <- getUserPackageDir let runUhcProg = runDbProgram verbosity uhcProgram (withPrograms lbi) let uhcArgs = -- set package name - ["--pkg-build=" ++ display (packageId pkg_descr)] + ["--pkg-build=" ++ prettyShow (packageId pkg_descr)] -- common flags lib/exe ++ constructUHCCmdLine userPkgDir systemPkgDir lbi (libBuildInfo lib) clbi @@ -186,7 +187,7 @@ buildLib verbosity pkg_descr lbi lib clbi = do -- suboptimal: UHC does not understand module names, so -- we replace periods by path separators ++ map (map (\ c -> if c == '.' then pathSeparator else c)) - (map display (allLibModules lib clbi)) + (map prettyShow (allLibModules lib clbi)) runUhcProg uhcArgs @@ -203,7 +204,7 @@ buildExe verbosity _pkg_descr lbi exe clbi = do lbi (buildInfo exe) clbi (buildDir lbi) verbosity -- output file - ++ ["--output", buildDir lbi </> display (exeName exe)] + ++ ["--output", buildDir lbi </> prettyShow (exeName exe)] -- main source module ++ [modulePath exe] runUhcProg uhcArgs @@ -224,7 +225,7 @@ constructUHCCmdLine user system lbi bi clbi odir verbosity = ++ ["--hide-all-packages"] ++ uhcPackageDbOptions user system (withPackageDB lbi) ++ ["--package=uhcbase"] - ++ ["--package=" ++ display (mungedName pkgid) | (_, pkgid) <- componentPackageDeps clbi ] + ++ ["--package=" ++ prettyShow (mungedName pkgid) | (_, pkgid) <- componentPackageDeps clbi ] -- search paths ++ ["-i" ++ odir] ++ ["-i" ++ l | l <- nub (hsSourceDirs bi)] @@ -253,7 +254,7 @@ installLib :: Verbosity -> LocalBuildInfo installLib verbosity _lbi targetDir _dynlibTargetDir builtDir pkg _library _clbi = do -- putStrLn $ "dest: " ++ targetDir -- putStrLn $ "built: " ++ builtDir - installDirectoryContents verbosity (builtDir </> display (packageId pkg)) targetDir + installDirectoryContents verbosity (builtDir </> prettyShow (packageId pkg)) targetDir -- currently hard-coded UHC code generator and variant to use uhcTarget, uhcTargetVariant :: String @@ -281,7 +282,7 @@ registerPackage verbosity comp progdb packageDbs installedPkgInfo = do GlobalPackageDB -> getGlobalPackageDir verbosity progdb UserPackageDB -> getUserPackageDir SpecificPackageDB dir -> return dir - let pkgdir = dbdir </> uhcPackageDir (display pkgid) (display compilerid) + let pkgdir = dbdir </> uhcPackageDir (prettyShow pkgid) (prettyShow compilerid) createDirectoryIfMissingVerbose verbosity True pkgdir writeUTF8File (pkgdir </> installedPkgConfig) (showInstalledPackageInfo installedPkgInfo) diff --git a/Cabal/Distribution/Simple/Utils.hs b/Cabal/Distribution/Simple/Utils.hs index 871a3e952b1df38b20c8205ee8bca54dbdefca9c..54c8b4692c824c7c2b986e45beb4979b109ee45a 100644 --- a/Cabal/Distribution/Simple/Utils.hs +++ b/Cabal/Distribution/Simple/Utils.hs @@ -171,7 +171,6 @@ module Distribution.Simple.Utils ( import Prelude () import Distribution.Compat.Prelude -import Distribution.Text import Distribution.Utils.Generic import Distribution.Utils.IOData (IOData(..), IODataMode(..)) import qualified Distribution.Utils.IOData as IOData @@ -199,6 +198,9 @@ import Distribution.Types.PackageId import qualified Paths_Cabal (version) #endif +import Distribution.Pretty +import Distribution.Parsec.Class + import Control.Concurrent.MVar ( newEmptyMVar, putMVar, takeMVar ) import Data.Typeable @@ -490,7 +492,7 @@ noticeDoc verbosity msg = withFrozenCallStack $ do -- setupMessage :: Verbosity -> String -> PackageIdentifier -> IO () setupMessage verbosity msg pkgid = withFrozenCallStack $ do - noticeNoWrap verbosity (msg ++ ' ': display pkgid ++ "...") + noticeNoWrap verbosity (msg ++ ' ': prettyShow pkgid ++ "...") -- | More detail on the operation of some action. -- @@ -920,11 +922,11 @@ findProgramVersion versionArg selectVersion verbosity path = withFrozenCallStack `catchIO` (\_ -> return "") `catchExit` (\_ -> return "") let version :: Maybe Version - version = simpleParse (selectVersion str) + version = simpleParsec (selectVersion str) case version of Nothing -> warn verbosity $ "cannot determine version of " ++ path ++ " :\n" ++ show str - Just v -> debug verbosity $ path ++ " is version " ++ display v + Just v -> debug verbosity $ path ++ " is version " ++ prettyShow v return version @@ -1044,7 +1046,7 @@ findModuleFile searchPath extensions mod_name = =<< findFileWithExtension' extensions searchPath (ModuleName.toFilePath mod_name) where - notFound = die $ "Error: Could not find module: " ++ display mod_name + notFound = die $ "Error: Could not find module: " ++ prettyShow mod_name ++ " with any suffix: " ++ show extensions ++ " in the search path: " ++ show searchPath diff --git a/Cabal/Distribution/Types/PackageId.hs b/Cabal/Distribution/Types/PackageId.hs index 1f3374153394a4f60a2b8f9b803f0594ac8e00de..9ab3f3bbca588d49f0ed014730c47fc36c22ee60 100644 --- a/Cabal/Distribution/Types/PackageId.hs +++ b/Cabal/Distribution/Types/PackageId.hs @@ -1,26 +1,23 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} module Distribution.Types.PackageId ( PackageIdentifier(..) , PackageId ) where -import Prelude () import Distribution.Compat.Prelude +import Prelude () -import Distribution.Version - ( Version, nullVersion ) - -import qualified Distribution.Compat.ReadP as Parse -import qualified Distribution.Compat.CharParsing as P -import qualified Text.PrettyPrint as Disp import Distribution.Compat.ReadP -import Distribution.Text -import Distribution.Parsec.Class - ( Parsec(..) ) +import Distribution.Parsec.Class (Parsec (..), simpleParsec) import Distribution.Pretty +import Distribution.Text import Distribution.Types.PackageName +import Distribution.Version (Version, nullVersion) + +import qualified Distribution.Compat.CharParsing as P +import qualified Distribution.Compat.ReadP as Parse +import qualified Text.PrettyPrint as Disp -- | Type alias so we can use the shorter name PackageId. type PackageId = PackageIdentifier @@ -40,15 +37,61 @@ instance Pretty PackageIdentifier where | v == nullVersion = pretty n -- if no version, don't show version. | otherwise = pretty n <<>> Disp.char '-' <<>> pretty v +-- | +-- +-- >>> simpleParse "foo-bar-0" :: Maybe PackageIdentifier +-- Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion [0]}) +-- +-- >>> simpleParse "foo-bar" :: Maybe PackageIdentifier +-- Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion []}) +-- +-- /Note:/ Broken (too lenient, doesn't require full consumption) +-- +-- >>> simpleParse "foo-bar-0-0" :: Maybe PackageIdentifier +-- Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion [0]}) +-- +-- >>> simpleParse "foo-bar.0" :: Maybe PackageIdentifier +-- Nothing +-- +-- >>> simpleParse "foo-bar.4-2" :: Maybe PackageIdentifier +-- Nothing +-- instance Text PackageIdentifier where parse = do n <- parse v <- (Parse.char '-' >> parse) <++ return nullVersion return (PackageIdentifier n v) +-- | +-- +-- >>> simpleParsec "foo-bar-0" :: Maybe PackageIdentifier +-- Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion [0]}) +-- +-- >>> simpleParsec "foo-bar" :: Maybe PackageIdentifier +-- Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion []}) +-- +-- /Note:/ Stricter than 'Text' instance +-- +-- >>> simpleParsec "foo-bar-0-0" :: Maybe PackageIdentifier +-- Nothing +-- +-- >>> simpleParsec "foo-bar.0" :: Maybe PackageIdentifier +-- Nothing +-- +-- >>> simpleParsec "foo-bar.4-2" :: Maybe PackageIdentifier +-- Nothing +-- instance Parsec PackageIdentifier where - parsec = PackageIdentifier <$> - parsec <*> (P.char '-' *> parsec <|> pure nullVersion) + parsec = do + xs' <- P.sepBy1 component (P.char '-') + (v, xs) <- case simpleParsec (last xs') of + Nothing -> return (nullVersion, xs') -- all components are version + Just v -> return (v, init xs') + if all (\c -> all (/= '.') c && not (all isDigit c)) xs + then return $ PackageIdentifier (mkPackageName (intercalate "-" xs)) v + else fail "all digits or a dot in a portion of package name" + where + component = P.munch1 (\c -> isAlphaNum c || c == '.') instance NFData PackageIdentifier where rnf (PackageIdentifier name version) = rnf name `seq` rnf version