1
+ {-# LANGUAGE DuplicateRecordFields #-}
1
2
{-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE RecordWildCards #-}
3
4
4
5
module Ormolu.Utils.Cabal
5
- ( CabalSearchResult (.. ),
6
- CabalInfo (.. ),
6
+ ( CabalInfo (.. ),
7
+ StanzaInfo (.. ),
8
+ defaultStanzaInfo ,
9
+ StanzaInfoMap ,
10
+ lookupStanzaInfo ,
7
11
Extension (.. ),
8
12
getCabalInfoForSourceFile ,
9
13
findCabalFile ,
@@ -34,29 +38,14 @@ import System.Directory
34
38
import System.FilePath
35
39
import System.IO.Unsafe (unsafePerformIO )
36
40
37
- -- | The result of searching for a @.cabal@ file.
38
- --
39
- -- @since 0.5.3.0
40
- data CabalSearchResult
41
- = -- | Cabal file could not be found
42
- CabalNotFound
43
- | -- | Cabal file was found, but it did not mention the source file in
44
- -- question
45
- CabalDidNotMention CabalInfo
46
- | -- | Cabal file was found and it mentions the source file in question
47
- CabalFound CabalInfo
48
- deriving (Eq , Show )
49
-
50
41
-- | Cabal information of interest to Ormolu.
51
42
data CabalInfo = CabalInfo
52
43
{ -- | Package name
53
44
ciPackageName :: ! PackageName ,
54
- -- | Extension and language settings in the form of 'DynOption's
55
- ciDynOpts :: ! [DynOption ],
56
- -- | Direct dependencies
57
- ciDependencies :: ! (Set PackageName ),
58
45
-- | Absolute path to the cabal file
59
- ciCabalFilePath :: ! FilePath
46
+ ciCabalFilePath :: ! FilePath ,
47
+ -- | Stanza information for all source files mentioned in the cabal file
48
+ ciStanzaInfoMap :: ! StanzaInfoMap
60
49
}
61
50
deriving (Eq , Show )
62
51
@@ -67,11 +56,18 @@ data StanzaInfo = StanzaInfo
67
56
-- | Direct dependencies
68
57
siDependencies :: ! (Set PackageName )
69
58
}
70
- deriving (Show )
59
+ deriving (Eq , Show )
60
+
61
+ defaultStanzaInfo :: StanzaInfo
62
+ defaultStanzaInfo =
63
+ StanzaInfo
64
+ { siDynOpts = [] ,
65
+ siDependencies = defaultDependencies
66
+ }
71
67
72
68
-- | Map from source files (absolute path without extensions) to the corresponding stanza information.
73
69
newtype StanzaInfoMap = StanzaInfoMap (Map FilePath StanzaInfo )
74
- deriving (Show )
70
+ deriving (Eq , Show )
75
71
76
72
-- | Look up the given source file in the 'StanzaInfoMap'.
77
73
lookupStanzaInfo :: FilePath -> StanzaInfoMap -> IO (Maybe StanzaInfo )
@@ -86,17 +82,9 @@ getCabalInfoForSourceFile ::
86
82
-- | Haskell source file
87
83
FilePath ->
88
84
-- | Extracted cabal info, if any
89
- m CabalSearchResult
85
+ m ( Maybe CabalInfo )
90
86
getCabalInfoForSourceFile sourceFile =
91
- liftIO (findCabalFile sourceFile) >>= \ case
92
- Just cabalFile -> do
93
- (mentioned, cabalInfo) <- parseCabalInfo cabalFile sourceFile
94
- return
95
- ( if mentioned
96
- then CabalFound cabalInfo
97
- else CabalDidNotMention cabalInfo
98
- )
99
- Nothing -> return CabalNotFound
87
+ liftIO (findCabalFile sourceFile) >>= traverse parseCabalInfo
100
88
101
89
-- | Find the path to an appropriate @.cabal@ file for a Haskell source
102
90
-- file, if available.
@@ -109,16 +97,8 @@ findCabalFile ::
109
97
findCabalFile = findClosestFileSatisfying $ \ x ->
110
98
takeExtension x == " .cabal"
111
99
112
- -- | Parsed cabal file information to be shared across multiple source files.
113
- data CachedCabalFile = CachedCabalFile
114
- { -- | Parsed generic package description.
115
- genericPackageDescription :: GenericPackageDescription ,
116
- stanzaInfoMap :: StanzaInfoMap
117
- }
118
- deriving (Show )
119
-
120
- -- | Cache ref that stores 'CachedCabalFile' per Cabal file.
121
- cacheRef :: IORef (Map FilePath CachedCabalFile )
100
+ -- | Cache ref that stores 'CabalInfo' per Cabal file path.
101
+ cacheRef :: IORef (Map FilePath CabalInfo )
122
102
cacheRef = unsafePerformIO $ newIORef M. empty
123
103
{-# NOINLINE cacheRef #-}
124
104
@@ -127,37 +107,20 @@ parseCabalInfo ::
127
107
(MonadIO m ) =>
128
108
-- | Location of the .cabal file
129
109
FilePath ->
130
- -- | Location of the source file we are formatting
131
- FilePath ->
132
- -- | Indication if the source file was mentioned in the Cabal file and the
133
- -- extracted 'CabalInfo'
134
- m (Bool , CabalInfo )
135
- parseCabalInfo cabalFileAsGiven sourceFileAsGiven = liftIO $ do
110
+ m CabalInfo
111
+ parseCabalInfo cabalFileAsGiven = liftIO $ do
136
112
cabalFile <- makeAbsolute cabalFileAsGiven
137
- CachedCabalFile { .. } <- withIORefCache cacheRef cabalFile $ do
113
+ withIORefCache cacheRef cabalFile $ do
138
114
cabalFileBs <- B. readFile cabalFile
139
- genericPackageDescription <-
140
- whenLeft (snd . runParseResult $ parseGenericPackageDescription cabalFileBs) $
141
- throwIO . OrmoluCabalFileParsingFailed cabalFile . snd
142
- let stanzaInfoMap = toStanzaInfoMap cabalFile genericPackageDescription
143
- pure CachedCabalFile {.. }
144
- (dynOpts, dependencies, mentioned) <-
145
- lookupStanzaInfo sourceFileAsGiven stanzaInfoMap >>= \ case
146
- Nothing -> pure ([] , defaultDependencies, False )
147
- Just StanzaInfo {.. } -> pure (siDynOpts, siDependencies, True )
148
- let pdesc = packageDescription genericPackageDescription
149
- return
150
- ( mentioned,
151
- CabalInfo
152
- { ciPackageName = pkgName (package pdesc),
153
- ciDynOpts = dynOpts,
154
- ciDependencies = dependencies,
155
- ciCabalFilePath = cabalFile
156
- }
157
- )
158
- where
159
- whenLeft :: (Applicative f ) => Either e a -> (e -> f a ) -> f a
160
- whenLeft eitha ma = either ma pure eitha
115
+ case snd . runParseResult . parseGenericPackageDescription $ cabalFileBs of
116
+ Right genericPackageDescription ->
117
+ pure
118
+ CabalInfo
119
+ { ciPackageName = pkgName . package . packageDescription $ genericPackageDescription,
120
+ ciCabalFilePath = cabalFile,
121
+ ciStanzaInfoMap = toStanzaInfoMap cabalFile genericPackageDescription
122
+ }
123
+ Left (_, e) -> throwIO $ OrmoluCabalFileParsingFailed cabalFile e
161
124
162
125
-- | Get a map from Haskell source file paths (without any extensions) to
163
126
-- the corresponding 'DynOption's and dependencies.
0 commit comments