1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
4 {-# LANGUAGE LambdaCase #-}
5 {-# LANGUAGE RankNTypes #-}
6 {-# LANGUAGE RecordWildCards #-}
8 module Distribution
.Simple
.GHC
.EnvironmentParser
(parseGhcEnvironmentFile
, readGhcEnvironmentFile
, ParseErrorExc
(..)) where
10 import Distribution
.Compat
.Prelude
13 import Distribution
.Simple
.Compiler
14 import Distribution
.Simple
.GHC
.Internal
15 ( GhcEnvironmentFileEntry
(..)
17 import Distribution
.Types
.UnitId
21 import qualified Text
.Parsec
as P
22 import Text
.Parsec
.String
27 parseEnvironmentFileLine
:: Parser
(GhcEnvironmentFileEntry
FilePath)
28 parseEnvironmentFileLine
=
29 GhcEnvFileComment
<$> comment
30 <|
> GhcEnvFilePackageId
<$> unitId
31 <|
> GhcEnvFilePackageDb
<$> packageDb
32 <|
> pure GhcEnvFileClearPackageDbStack
<* clearDb
34 comment
= P
.string "--" *> P
.many
(P
.noneOf
"\r\n")
39 *> (mkUnitId
<$> P
.many1
(P
.satisfy
$ \c
-> isAlphaNum c || c `
elem`
"-_.+"))
41 (P
.string "global-package-db" *> pure GlobalPackageDB
)
42 <|
> (P
.string "user-package-db" *> pure UserPackageDB
)
43 <|
> (P
.string "package-db" *> P
.spaces
*> (SpecificPackageDB
<$> P
.many1
(P
.noneOf
"\r\n") <* P
.lookAhead P
.endOfLine
))
44 clearDb
= P
.string "clear-package-db"
46 newtype ParseErrorExc
= ParseErrorExc P
.ParseError
47 deriving (Show, Typeable
)
49 instance Exception ParseErrorExc
51 parseGhcEnvironmentFile
:: Parser
[GhcEnvironmentFileEntry
FilePath]
52 parseGhcEnvironmentFile
= parseEnvironmentFileLine `P
.sepEndBy` P
.endOfLine
<* P
.eof
54 readGhcEnvironmentFile
:: FilePath -> IO [GhcEnvironmentFileEntry
FilePath]
55 readGhcEnvironmentFile path
=
56 either (throwIO
. ParseErrorExc
) return
57 =<< parseFromFile parseGhcEnvironmentFile path