Skip to content

Commit 21ebfc1

Browse files
committed
elif support, maybe?
1 parent ec3763f commit 21ebfc1

File tree

1 file changed

+37
-27
lines changed
  • cabal-install/src/Distribution/Client/ProjectConfig

1 file changed

+37
-27
lines changed

cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs

+37-27
Original file line numberDiff line numberDiff line change
@@ -159,39 +159,55 @@ projectSkeletonImports = view traverseCondTreeC
159159
parseProjectSkeleton :: FilePath -> HttpTransport -> Verbosity -> FilePath -> BS.ByteString -> IO (ParseResult ProjectConfigSkeleton)
160160
parseProjectSkeleton cacheDir httpTransport verbosity source bs = (>>= sanityWalkPCS False) . runInnerParsers <$> linesToNode (BS.lines bs)
161161
where
162+
-- converts lines to a full tree node, recursively looping "go" to pull out conditional and import structure, then packing the whole thing up
162163
linesToNode :: [BS.ByteString] -> IO (CondTree BS.ByteString [ProjectConfigImport] [BS.ByteString])
163-
linesToNode ls = packResult . mconcat <$> go ls
164-
165-
packResult :: ([CondBranch BS.ByteString [ProjectConfigImport] [BS.ByteString]], [ProjectConfigImport], [BS.ByteString]) -> CondTree BS.ByteString [ProjectConfigImport] [BS.ByteString]
166-
packResult (branches, imps, ls) = CondNode ls imps branches
164+
linesToNode xs = (\(branches, imps, ls) -> CondNode ls imps branches) . mconcat <$> go xs
167165

166+
-- given a list of lines, pulls out the conditional and import structure
168167
go :: [BS.ByteString] -> IO [([CondBranch BS.ByteString [ProjectConfigImport] [BS.ByteString]], [ProjectConfigImport], [BS.ByteString])]
169168
go (l:ls)
170-
| Just condition <- Var <$> detectCond l =
171-
let (clause, rest) = splitTillIndented ls
172-
in case rest of
173-
(r:rs) | (BS.pack "else") `BS.isPrefixOf` r -> -- TODO handle elif
174-
let (elseClause, lastRest) = splitTillIndented rs
175-
in do
176-
c1 <- linesToNode clause
177-
c2 <- linesToNode elseClause
178-
(([condIfThenElse condition c1 c2], [], []) :) <$> go lastRest
179-
_ -> do
180-
c1 <- linesToNode clause
181-
(([condIfThen condition c1], [], []) :) <$> go rest
169+
| (BS.pack "if(") `BS.isPrefixOf` l =
170+
let (clause, rest) = splitWhileIndented ls
171+
172+
-- unpacks the results of loop into nested if else clauses
173+
constructNestedConds topCond topClause [] [] =
174+
do c1 <- linesToNode topClause
175+
pure $ condIfThen (Var topCond) c1
176+
constructNestedConds topCond topClause ((elifCond, elifClause):elifs) elseClause =
177+
do c1 <- linesToNode topClause
178+
condIfThenElse (Var topCond) c1 . CondNode [] [] . (:[]) <$> constructNestedConds elifCond elifClause elifs elseClause
179+
constructNestedConds topCond topClause [] elseClause =
180+
do c1 <- linesToNode topClause
181+
c2 <- linesToNode elseClause
182+
pure $ condIfThenElse (Var topCond) c1 c2
183+
184+
-- parse out the full list of if/else clauses
185+
loop acc rss =
186+
case rss of
187+
(r:rs)
188+
| BS.pack "elif" `BS.isPrefixOf` r ->
189+
let (elseClause, lastRest) = splitWhileIndented rs
190+
in loop ((r, elseClause):acc) lastRest
191+
| BS.pack "else" `BS.isPrefixOf` r ->
192+
let (elseClause, lastRest) = splitWhileIndented rs
193+
in constructNestedConds l clause (reverse acc) elseClause
194+
>>= (\c -> ((([c],[],[]) :) <$> go lastRest))
195+
_ -> constructNestedConds l clause (reverse acc) []
196+
>>= (\c -> ((([c],[],[]) :) <$> go rss))
197+
in loop [] rest
198+
182199
| Just imp <- parseImport l = do x <- go . BS.lines =<< fetchImportConfig imp
183200
((([], [imp], []) : x) ++) <$> go ls
201+
184202
| otherwise = (([], [], [l]) :) <$> go ls
185-
go [] = pure []
186203

187-
splitTillIndented = span ((BS.pack " ") `BS.isPrefixOf`)
204+
go [] = pure []
188205

189-
detectCond :: BS.ByteString -> Maybe BS.ByteString
190-
detectCond l | (BS.pack "if(") `BS.isPrefixOf` l = Just l
206+
splitWhileIndented = span ((BS.pack " ") `BS.isPrefixOf`)
191207

192-
| otherwise = Nothing
193208
parseImport l | (BS.pack "import ") `BS.isPrefixOf` l = Just . BS.unpack $ BS.drop (length "import ") l
194209
| otherwise = Nothing
210+
195211
runInnerParsers :: CondTree BS.ByteString [ProjectConfigImport] [BS.ByteString] -> ParseResult ProjectConfigSkeleton
196212
runInnerParsers = (runConditionParsers =<<) . traverse (fmap (addProvenance . convertLegacyProjectConfig) . parseLegacyProjectConfig source . BS.unlines)
197213

@@ -232,12 +248,6 @@ parseProjectSkeleton cacheDir httpTransport verbosity source bs = (>>= sanityWal
232248
BS.readFile fp
233249
Nothing -> BS.readFile pci
234250

235-
236-
{-
237-
-- TODO elif
238-
-- TODO handle merge semantics for constraints specially
239-
-}
240-
241251
------------------------------------------------------------------
242252
-- Representing the project config file in terms of legacy types
243253
--

0 commit comments

Comments
 (0)