Skip to content

Commit

Permalink
Merge pull request #4235 from phadej/cabal-install-parsec-2
Browse files Browse the repository at this point in the history
parsec for cabal-install
  • Loading branch information
phadej authored Jan 26, 2017
2 parents 4d08a8a + b27aa25 commit c621a78
Show file tree
Hide file tree
Showing 18 changed files with 167 additions and 52 deletions.
22 changes: 17 additions & 5 deletions Cabal/Distribution/PackageDescription/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,10 @@

module Distribution.PackageDescription.Parse (
-- * Package descriptions
readGenericPackageDescription,
parseGenericPackageDescription,

-- ** Deprecated names
readPackageDescription,
parsePackageDescription,

Expand Down Expand Up @@ -592,10 +596,14 @@ readHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfo
readHookedBuildInfo =
readAndParseFile withFileContents parseHookedBuildInfo

-- |Parse the given package file.
readPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription
readPackageDescription =
readAndParseFile withUTF8FileContents parsePackageDescription
readPackageDescription = readGenericPackageDescription
{-# DEPRECATED readPackageDescription "Use readGenericPackageDescription, old name is missleading." #-}

-- | Parse the given package file.
readGenericPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription
readGenericPackageDescription =
readAndParseFile withUTF8FileContents parseGenericPackageDescription

stanzas :: [Field] -> [[Field]]
stanzas [] = []
Expand Down Expand Up @@ -713,12 +721,16 @@ skipField = modify tail
--FIXME: this should take a ByteString, not a String. We have to be able to
-- decode UTF8 and handle the BOM.

parsePackageDescription :: String -> ParseResult GenericPackageDescription
parsePackageDescription = parseGenericPackageDescription
{-# DEPRECATED parsePackageDescription "Use parseGenericPackageDescription, old name is missleading" #-}

-- | Parses the given file into a 'GenericPackageDescription'.
--
-- In Cabal 1.2 the syntax for package descriptions was changed to a format
-- with sections and possibly indented property descriptions.
parsePackageDescription :: String -> ParseResult GenericPackageDescription
parsePackageDescription file = do
parseGenericPackageDescription :: String -> ParseResult GenericPackageDescription
parseGenericPackageDescription file = do

-- This function is quite complex because it needs to be able to parse
-- both pre-Cabal-1.2 and post-Cabal-1.2 files. Additionally, it contains
Expand Down
9 changes: 9 additions & 0 deletions Cabal/Distribution/PackageDescription/Parsec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,11 @@ module Distribution.PackageDescription.Parsec (
-- * Package descriptions
readGenericPackageDescription,
parseGenericPackageDescription,
parseGenericPackageDescriptionMaybe,

-- ** Parsing
ParseResult,
runParseResult,

-- ** Supplementary build information
-- readHookedBuildInfo,
Expand Down Expand Up @@ -105,6 +107,13 @@ parseGenericPackageDescription bs = case readFields' bs of
-- TODO: better marshalling of errors
Left perr -> parseFatalFailure (Position 0 0) (show perr)

-- | 'Maybe' variant of 'parseGenericPackageDescription'
parseGenericPackageDescriptionMaybe :: BS.ByteString -> Maybe GenericPackageDescription
parseGenericPackageDescriptionMaybe =
trdOf3 . runParseResult . parseGenericPackageDescription
where
trdOf3 (_, _, x) = x

runFieldParser :: FieldParser a -> [FieldLine Position] -> ParseResult a
runFieldParser p ls = runFieldParser' pos p =<< fieldlinesToString pos ls
where
Expand Down
4 changes: 1 addition & 3 deletions Cabal/Distribution/Simple.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,10 +237,8 @@ confPkgDescr hooks verbosity mb_path = do
Just path -> return path
#ifdef CABAL_PARSEC
info verbosity "Using Parsec parser"
descr <- readGenericPackageDescription verbosity pdfile
#else
descr <- readPackageDescription verbosity pdfile
#endif
descr <- readGenericPackageDescription verbosity pdfile
return (Just pdfile, descr)

buildAction :: UserHooks -> BuildFlags -> Args -> IO ()
Expand Down
5 changes: 2 additions & 3 deletions Cabal/tests/ParserHackageTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ import qualified Distribution.PackageDescription.Parse as ReadP
import qualified Distribution.PackageDescription.Parsec as Parsec
import qualified Distribution.Parsec.Parser as Parsec
import qualified Distribution.Parsec.Types.Common as Parsec
import qualified Distribution.Parsec.Types.ParseResult as Parsec
import qualified Distribution.ParseUtils as ReadP
import qualified Distribution.Compat.DList as DList

Expand Down Expand Up @@ -97,7 +96,7 @@ compareTest pfx fpath bsl
let str = ignoreBOM $ fromUTF8LBS bsl

putStrLn $ "::: " ++ fpath
(readp, readpWarnings) <- case ReadP.parsePackageDescription str of
(readp, readpWarnings) <- case ReadP.parseGenericPackageDescription str of
ReadP.ParseOk ws x -> return (x, ws)
ReadP.ParseFailed err -> print err >> exitFailure
traverse_ (putStrLn . ReadP.showPWarning fpath) readpWarnings
Expand Down Expand Up @@ -155,7 +154,7 @@ compareTest pfx fpath bsl
parseReadpTest :: FilePath -> BSL.ByteString -> IO ()
parseReadpTest fpath bsl = when (not $ any ($ fpath) problematicFiles) $ do
let str = fromUTF8LBS bsl
case ReadP.parsePackageDescription str of
case ReadP.parseGenericPackageDescription str of
ReadP.ParseOk _ _ -> return ()
ReadP.ParseFailed err -> print err >> exitFailure

Expand Down
11 changes: 8 additions & 3 deletions cabal-install/Distribution/Client/Check.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Client.Check
Expand All @@ -17,8 +18,12 @@ module Distribution.Client.Check (

import Control.Monad ( when, unless )

import Distribution.PackageDescription.Parse
( readPackageDescription )
#ifdef CABAL_PARSEC
import Distribution.PackageDescription.Parsec ( readGenericPackageDescription )
#else
import Distribution.PackageDescription.Parse ( readGenericPackageDescription )
#endif

import Distribution.PackageDescription.Check
import Distribution.PackageDescription.Configuration
( flattenPackageDescription )
Expand All @@ -30,7 +35,7 @@ import Distribution.Simple.Utils
check :: Verbosity -> IO Bool
check verbosity = do
pdfile <- defaultPackageDesc verbosity
ppd <- readPackageDescription verbosity pdfile
ppd <- readGenericPackageDescription verbosity pdfile
-- flatten the generic package description into a regular package
-- description
-- TODO: this may give more warnings than it should give;
Expand Down
10 changes: 8 additions & 2 deletions cabal-install/Distribution/Client/Configure.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Client.Configure
Expand Down Expand Up @@ -67,8 +68,13 @@ import Distribution.Package
import Distribution.Types.Dependency
( Dependency(..), thisPackageVersion )
import qualified Distribution.PackageDescription as PkgDesc
#ifdef CABAL_PARSEC
import Distribution.PackageDescription.Parsec
( readGenericPackageDescription )
#else
import Distribution.PackageDescription.Parse
( readPackageDescription )
( readGenericPackageDescription )
#endif
import Distribution.PackageDescription.Configuration
( finalizePD )
import Distribution.Version
Expand Down Expand Up @@ -296,7 +302,7 @@ planLocalPackage :: Verbosity -> Compiler
-> IO (Progress String String SolverInstallPlan)
planLocalPackage verbosity comp platform configFlags configExFlags
installedPkgIndex (SourcePackageDb _ packagePrefs) pkgConfigDb = do
pkg <- readPackageDescription verbosity =<<
pkg <- readGenericPackageDescription verbosity =<<
case flagToMaybe (configCabalFilePath configFlags) of
Nothing -> defaultPackageDesc verbosity
Just fp -> return fp
Expand Down
10 changes: 8 additions & 2 deletions cabal-install/Distribution/Client/GenBounds.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Client.GenBounds
Expand Down Expand Up @@ -28,8 +29,13 @@ import Distribution.PackageDescription
( buildDepends )
import Distribution.PackageDescription.Configuration
( finalizePD )
#ifdef CABAL_PARSEC
import Distribution.PackageDescription.Parsec
( readGenericPackageDescription )
#else
import Distribution.PackageDescription.Parse
( readPackageDescription )
( readGenericPackageDescription )
#endif
import Distribution.Types.ComponentRequestedSpec
( defaultComponentRequestedSpec )
import Distribution.Types.Dependency
Expand Down Expand Up @@ -109,7 +115,7 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo

cwd <- getCurrentDirectory
path <- tryFindPackageDesc cwd
gpd <- readPackageDescription verbosity path
gpd <- readGenericPackageDescription verbosity path
-- NB: We don't enable tests or benchmarks, since often they
-- don't really have useful bounds.
let epd = finalizePD [] defaultComponentRequestedSpec
Expand Down
44 changes: 34 additions & 10 deletions cabal-install/Distribution/Client/IndexUtils.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE BangPatterns #-}
Expand Down Expand Up @@ -51,30 +52,39 @@ import Distribution.Package
, Package(..), packageVersion, packageName )
import Distribution.Types.Dependency
import Distribution.Simple.PackageIndex (InstalledPackageIndex)
import qualified Distribution.PackageDescription.Parse as PackageDesc.Parse
import Distribution.PackageDescription
( GenericPackageDescription )
import Distribution.PackageDescription.Parse
( parsePackageDescription )
import Distribution.Simple.Compiler
( Compiler, PackageDBStack )
import Distribution.Simple.Program
( ProgramDb )
import qualified Distribution.Simple.Configure as Configure
( getInstalledPackages, getInstalledPackagesMonitorFiles )
import Distribution.ParseUtils
( ParseResult(..) )
import Distribution.Version
( mkVersion, intersectVersionRanges )
import Distribution.Text
( display, simpleParse )
import Distribution.Verbosity
( Verbosity, normal, lessVerbose )
import Distribution.Simple.Utils
( die, warn, info, fromUTF8, ignoreBOM )
( die, warn, info )
import Distribution.Client.Setup
( RepoContext(..) )

#ifdef CABAL_PARSEC
import Distribution.PackageDescription.Parsec
( parseGenericPackageDescriptionMaybe )
import qualified Distribution.PackageDescription.Parsec as PackageDesc.Parse
#else
import Distribution.ParseUtils
( ParseResult(..) )
import Distribution.PackageDescription.Parse
( parseGenericPackageDescription )
import Distribution.Simple.Utils
( fromUTF8, ignoreBOM )
import qualified Distribution.PackageDescription.Parse as PackageDesc.Parse
#endif

import Distribution.Solver.Types.PackageIndex (PackageIndex)
import qualified Distribution.Solver.Types.PackageIndex as PackageIndex
import Distribution.Solver.Types.SourcePackage
Expand Down Expand Up @@ -434,12 +444,20 @@ extractPkg entry blockNo = case Tar.entryContent entry of
Just ver -> Just . return $ Just (NormalPackage pkgid descr content blockNo)
where
pkgid = PackageIdentifier (mkPackageName pkgname) ver
parsed = parsePackageDescription . ignoreBOM . fromUTF8 . BS.Char8.unpack
#ifdef CABAL_PARSEC
parsed = parseGenericPackageDescriptionMaybe (BS.toStrict content)
descr = case parsed of
Just d -> d
Nothing -> error $ "Couldn't read cabal file "
++ show fileName
#else
parsed = parseGenericPackageDescription . ignoreBOM . fromUTF8 . BS.Char8.unpack
$ content
descr = case parsed of
ParseOk _ d -> d
_ -> error $ "Couldn't read cabal file "
++ show fileName
#endif
_ -> Nothing
_ -> Nothing

Expand All @@ -451,7 +469,7 @@ extractPkg entry blockNo = case Tar.entryContent entry of
result <- if not dirExists then return Nothing
else do
cabalFile <- tryFindAddSourcePackageDesc path "Error reading package index."
descr <- PackageDesc.Parse.readPackageDescription normal cabalFile
descr <- PackageDesc.Parse.readGenericPackageDescription normal cabalFile
return . Just $ BuildTreeRef (refTypeFromTypeCode typeCode) (packageId descr)
descr path blockNo
return result
Expand Down Expand Up @@ -674,7 +692,7 @@ packageListFromCache mkPkg hnd Cache{..} mode = accum mempty [] mempty cacheEntr
path <- liftM byteStringToFilePath . getEntryContent $ blockno
pkg <- do let err = "Error reading package index from cache."
file <- tryFindAddSourcePackageDesc path err
PackageDesc.Parse.readPackageDescription normal file
PackageDesc.Parse.readGenericPackageDescription normal file
let srcpkg = mkPkg (BuildTreeRef refType (packageId pkg) pkg path blockno)
accum srcpkgs (srcpkg:btrs) prefs entries

Expand All @@ -693,9 +711,15 @@ packageListFromCache mkPkg hnd Cache{..} mode = accum mempty [] mempty cacheEntr

readPackageDescription :: ByteString -> IO GenericPackageDescription
readPackageDescription content =
case parsePackageDescription . ignoreBOM . fromUTF8 . BS.Char8.unpack $ content of
#ifdef CABAL_PARSEC
case parseGenericPackageDescriptionMaybe (BS.toStrict content) of
Just gpd -> return gpd
Nothing -> interror "failed to parse .cabal file"
#else
case parseGenericPackageDescription . ignoreBOM . fromUTF8 . BS.Char8.unpack $ content of
ParseOk _ d -> return d
_ -> interror "failed to parse .cabal file"
#endif

interror msg = die $ "internal error when reading package index: " ++ msg
++ "The package index or index cache is probably "
Expand Down
12 changes: 9 additions & 3 deletions cabal-install/Distribution/Client/Outdated.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Client.Outdated
Expand Down Expand Up @@ -28,8 +29,6 @@ import Distribution.Client.Sandbox.PackageEnvironment
import Distribution.Package (PackageName, packageVersion)
import Distribution.PackageDescription (buildDepends)
import Distribution.PackageDescription.Configuration (finalizePD)
import Distribution.PackageDescription.Parse
(readPackageDescription)
import Distribution.Simple.Compiler (Compiler, compilerInfo)
import Distribution.Simple.Setup (fromFlagOrDefault)
import Distribution.Simple.Utils
Expand All @@ -43,6 +42,13 @@ import Distribution.Verbosity (Verbosity, silent)
import Distribution.Version
(Version, LowerBound(..), UpperBound(..)
,asVersionIntervals, majorBoundVersion)
#ifdef CABAL_PARSEC
import Distribution.PackageDescription.Parsec
(readGenericPackageDescription)
#else
import Distribution.PackageDescription.Parse
(readGenericPackageDescription)
#endif

import qualified Data.Set as S
import System.Directory (getCurrentDirectory)
Expand Down Expand Up @@ -134,7 +140,7 @@ depsFromPkgDesc :: Verbosity -> Compiler -> Platform -> IO [Dependency]
depsFromPkgDesc verbosity comp platform = do
cwd <- getCurrentDirectory
path <- tryFindPackageDesc cwd
gpd <- readPackageDescription verbosity path
gpd <- readGenericPackageDescription verbosity path
let cinfo = compilerInfo comp
epd = finalizePD [] (ComponentRequestedSpec True True)
(const True) platform cinfo [] gpd
Expand Down
9 changes: 7 additions & 2 deletions cabal-install/Distribution/Client/ProjectConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,8 +76,13 @@ import Distribution.System
( Platform )
import Distribution.PackageDescription
( SourceRepo(..) )
#if CABAL_PARSEC
import Distribution.PackageDescription.Parsec
( readGenericPackageDescription )
#else
import Distribution.PackageDescription.Parse
( readPackageDescription )
( readGenericPackageDescription )
#endif
import Distribution.Simple.Compiler
( Compiler, compilerInfo )
import Distribution.Simple.Program
Expand Down Expand Up @@ -867,7 +872,7 @@ readSourcePackage verbosity (ProjectPackageLocalCabalFile cabalFile) =
readSourcePackage verbosity (ProjectPackageLocalDirectory dir cabalFile) = do
monitorFiles [monitorFileHashed cabalFile]
root <- askRoot
pkgdesc <- liftIO $ readPackageDescription verbosity (root </> cabalFile)
pkgdesc <- liftIO $ readGenericPackageDescription verbosity (root </> cabalFile)
return SourcePackage {
packageInfoId = packageId pkgdesc,
packageDescription = pkgdesc,
Expand Down
Loading

0 comments on commit c621a78

Please sign in to comment.