Skip to content

Commit 4a0da1c

Browse files
committed
Use Cabal-syntax to parse cabal packages
1 parent fa0c5b2 commit 4a0da1c

File tree

2 files changed

+80
-138
lines changed

2 files changed

+80
-138
lines changed

implicit-hie.cabal

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,15 +46,16 @@ library
4646
hs-source-dirs: src
4747
ghc-options:
4848
-Wall -Wincomplete-record-updates -Wincomplete-uni-patterns
49-
-fno-warn-unused-imports -fno-warn-unused-binds
5049
-fno-warn-name-shadowing -fwarn-redundant-constraints
5150

5251
build-depends:
5352
attoparsec >=0.13
5453
, base >=4.7 && <5
54+
, bytestring
5555
, directory >=1.3
5656
, filepath >=1.4
5757
, filepattern >=0.1
58+
, Cabal-syntax >=3.8
5859
, text >=1.2
5960
, transformers >=0.5
6061
, yaml >=0.5
@@ -88,7 +89,7 @@ executable gen-hie
8889
, yaml
8990

9091
default-language: Haskell2010
91-
92+
9293
if !flag(executable)
9394
buildable: False
9495

src/Hie/Cabal/Parser.hs

Lines changed: 77 additions & 136 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,46 @@
1-
{-# LANGUAGE LambdaCase #-}
21
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE RecordWildCards #-}
3+
4+
module Hie.Cabal.Parser
5+
( Package(..)
6+
, Component(..)
7+
, CompType(..)
8+
, Name
9+
, extractPkgs
10+
, parsePackage'
11+
) where
12+
13+
import Control.Applicative
14+
import Control.Monad
15+
import Data.Attoparsec.Text
16+
import Data.Char
17+
import Data.Foldable (asum)
18+
import Data.Maybe (maybeToList, catMaybes)
19+
import Data.Text (Text)
20+
import qualified Data.Text as T
21+
import Data.Text.Encoding (encodeUtf8)
22+
import Distribution.ModuleName (ModuleName,
23+
toFilePath)
24+
import Distribution.Package (pkgName,
25+
unPackageName)
26+
import Distribution.PackageDescription (Benchmark (benchmarkBuildInfo, benchmarkName),
27+
Executable (buildInfo, exeName),
28+
ForeignLib (foreignLibBuildInfo, foreignLibName),
29+
Library (libBuildInfo, libName),
30+
LibraryName (..),
31+
benchmarkModules,
32+
exeModules,
33+
explicitLibModules,
34+
foreignLibModules)
35+
import Distribution.PackageDescription.Configuration
36+
import Distribution.PackageDescription.Parsec
37+
import Distribution.Types.BuildInfo
38+
import Distribution.Types.PackageDescription
39+
import Distribution.Types.TestSuite
40+
import Distribution.Types.UnqualComponentName
41+
import Distribution.Utils.Path (getSymbolicPath)
42+
import System.FilePath ((</>))
343

4-
module Hie.Cabal.Parser where
5-
6-
import Control.Applicative
7-
import Control.Monad
8-
import Data.Attoparsec.Text
9-
import Data.Char
10-
import Data.Functor
11-
import Data.Maybe
12-
import Data.Text (Text)
13-
import qualified Data.Text as T
14-
import System.FilePath.Posix ((</>))
1544

1645
type Name = Text
1746

@@ -29,83 +58,6 @@ data Component
2958
= Comp CompType Name Path
3059
deriving (Show, Eq, Ord)
3160

32-
parsePackage' :: Text -> Either String Package
33-
parsePackage' = parseOnly parsePackage
34-
35-
-- Skip over entire fields that are known to be free-form. Ensures lines that
36-
-- look like the beginning of sections/stanzas are not inadvertently intepreted
37-
-- as such.
38-
-- List gathered by searching "free text field" in:
39-
-- https://cabal.readthedocs.io/en/3.4/buildinfo-fields-reference.html
40-
-- May be subject to change across Cabal versions.
41-
skipFreeformField :: Parser ()
42-
skipFreeformField =
43-
choice $
44-
flip (field 0) skipBlock
45-
<$> [ "author",
46-
"bug-reports",
47-
"category",
48-
"copyright",
49-
"description",
50-
"homepage",
51-
"maintainer",
52-
"package-url",
53-
"stability",
54-
"synopsis"
55-
]
56-
57-
parsePackage :: Parser Package
58-
parsePackage =
59-
( do
60-
n <- field 0 "name" $ const parseString
61-
(Package _ t) <- parsePackage
62-
pure $ Package n t
63-
)
64-
<|> (skipFreeformField >> parsePackage)
65-
<|> ( do
66-
h <- parseComponent 0
67-
(Package n t) <- parsePackage
68-
pure $ Package n (h <> t)
69-
)
70-
<|> (skipToNextLine >> parsePackage)
71-
<|> pure (Package "" [])
72-
73-
componentHeader :: Indent -> Text -> Parser Name
74-
componentHeader i t = do
75-
_ <- indent i
76-
_ <- asciiCI t
77-
skipMany tabOrSpace
78-
n <- parseString <|> pure ""
79-
skipToNextLine
80-
pure n
81-
82-
parseComponent :: Indent -> Parser [Component]
83-
parseComponent i =
84-
parseExe i
85-
<|> parseLib i
86-
<|> parseBench i
87-
<|> parseTestSuite i
88-
89-
parseLib :: Indent -> Parser [Component]
90-
parseLib i =
91-
(parseSec i "library" $ Comp Lib)
92-
<|> (parseSec i "foreign-library" $ Comp Lib)
93-
94-
parseTestSuite :: Indent -> Parser [Component]
95-
parseTestSuite i = parseSec i "test-suite" $ Comp Test
96-
97-
parseExe :: Indent -> Parser [Component]
98-
parseExe = parseSecMain (Comp Exe) "executable"
99-
100-
parseBench :: Indent -> Parser [Component]
101-
parseBench = parseSecMain (Comp Bench) "benchmark"
102-
103-
parseSecMain :: (Name -> Path -> Component) -> Text -> Indent -> Parser [Component]
104-
parseSecMain c s i = do
105-
n <- componentHeader i s
106-
p <- pathMain (i + 1) ["./"] "" [] []
107-
pure $ map (c n) p
108-
10961
parseQuoted :: Parser Text
11062
parseQuoted = do
11163
q <- char '"' <|> char '\''
@@ -142,84 +94,73 @@ parseList i = many (nl <|> sl)
14294
skipMany com
14395
pure x
14496

145-
pathMain :: Indent -> [Text] -> Text -> [Text] -> [Text] -> Parser [Text]
146-
pathMain i p m o a =
147-
(hsSourceDir i >>= (\p' -> pathMain i p' m o a))
148-
<|> (field i "main-is" (const parseString) >>= (\m' -> pathMain i p m' o a))
149-
<|> (field i "other-modules" parseList >>= flip (pathMain i p m) a)
150-
<|> (field i "autogen-modules" parseList >>= pathMain i p m o)
151-
<|> (skipBlockLine i >> pathMain i p m o a)
152-
<|> pure
153-
( map (<//> m) p
154-
<> [ p' <//> (o'' <> ".hs")
155-
| p' <- p,
156-
o' <- filter (`notElem` a) o,
157-
let o'' = T.replace "." "/" o'
158-
]
159-
)
160-
161-
(<//>) :: Text -> Text -> Text
162-
a <//> b = T.pack (T.unpack a </> T.unpack b)
163-
164-
infixr 5 <//>
165-
166-
parseSec :: Indent -> Text -> (Name -> Path -> Component) -> Parser [Component]
167-
parseSec i compType compCon = do
168-
n <- componentHeader i compType
169-
p <- extractPath (i + 1) []
170-
let p' = if null p then ["./"] else p
171-
pure $ map (compCon n) p'
172-
17397
skipToNextLine :: Parser ()
17498
skipToNextLine = skipWhile (not . isEndOfLine) >> endOfLine
17599

176-
skipBlock :: Indent -> Parser ()
177-
skipBlock i = skipMany $ skipBlockLine i
178-
179100
comment :: Parser ()
180101
comment = skipMany tabOrSpace >> "--" >> skipToNextLine
181102

182-
skipBlockLine :: Indent -> Parser ()
183-
skipBlockLine i = (indent i >> skipToNextLine) <|> emptyOrComLine
184-
185103
emptyOrComLine :: Parser ()
186104
emptyOrComLine = (skipMany tabOrSpace >> endOfLine) <|> comment
187105

188106
tabOrSpace :: Parser Char
189107
tabOrSpace = char ' ' <|> char '\t'
190108

191-
hsSourceDir :: Indent -> Parser [Text]
192-
hsSourceDir i = field i "hs-source-dirs" parseList
193-
194109
-- field :: Indent -> Text -> Parser Text
195110
field ::
196111
Indent ->
197-
Text ->
112+
[Text] ->
198113
(Indent -> Parser a) ->
199114
Parser a
200115
field i f p =
201116
do
202117
i' <- indent i
203-
_ <- asciiCI f
118+
_ <- asum $ map asciiCI f
204119
skipMany tabOrSpace
205120
_ <- char ':'
206121
skipMany tabOrSpace
207122
p' <- p $ i' + 1
208123
skipToNextLine
209124
pure p'
210125

211-
extractPath :: Indent -> [Path] -> Parser [Path]
212-
extractPath i ps =
213-
(field i "hs-source-dirs" parseList >>= (\p -> extractPath i $ ps <> p))
214-
<|> (skipBlockLine i >> extractPath i ps)
215-
<|> (comment >> extractPath i ps)
216-
<|> pure ps
217-
218126
-- | Skip at least n spaces
219127
indent :: Indent -> Parser Int
220128
indent i = do
221129
c <- length <$> many' tabOrSpace
222130
if c >= i then pure c else fail "insufficient indent"
223131

224132
extractPkgs :: Parser [T.Text]
225-
extractPkgs = join . catMaybes <$> many' (Just <$> field 0 "packages" parseList <|> (skipToNextLine >> pure Nothing))
133+
extractPkgs = join . catMaybes <$> many' (Just <$> field 0 ["packages"] parseList <|> (skipToNextLine >> pure Nothing))
134+
135+
parsePackage' :: T.Text -> Either String Package
136+
parsePackage' t = do
137+
let bytes = encodeUtf8 t
138+
case runParseResult (parseGenericPackageDescription bytes) of
139+
(_warnings, Left err) ->
140+
error $ "Cannot parse Cabal file: " <> show err
141+
(_warnings, Right res) -> do
142+
let pkg = flattenPackageDescription res
143+
Right $ extractPackage pkg
144+
145+
extractPackage :: PackageDescription -> Package
146+
extractPackage PackageDescription{..} = Package n cc where
147+
n = T.pack . unPackageName $ pkgName package
148+
149+
cc = concat $
150+
[mkComp Test (unqName $ testName t) (testBuildInfo t) (testModules t) | t <- testSuites] ++
151+
[mkComp Bench (unqName $ benchmarkName b) (benchmarkBuildInfo b) (benchmarkModules b) | b <- benchmarks] ++
152+
[mkComp Exe (unqName $ exeName e) (buildInfo e) (exeModules e) | e <- executables] ++
153+
[mkComp Lib (libName' l) (libBuildInfo l) (explicitLibModules l) | l <- maybeToList library ++ subLibraries ] ++
154+
[mkComp Lib (unqName $ foreignLibName f) (foreignLibBuildInfo f) (foreignLibModules f) | f <- foreignLibs]
155+
156+
mkComp :: CompType -> T.Text -> BuildInfo -> [ModuleName] -> [Component]
157+
mkComp typ name bi mods =
158+
[Comp typ name (T.pack $ srcDir </> m)
159+
| m <- map toFilePath mods
160+
, srcDir <- map getSymbolicPath $ hsSourceDirs bi
161+
]
162+
163+
unqName = T.pack . unUnqualComponentName
164+
libName' x = case libName x of
165+
LMainLibName -> ""
166+
LSubLibName u -> unqName u

0 commit comments

Comments
 (0)