Skip to content

Commit d575601

Browse files
Ensure no-cabal-file has equivalent behavior to cabal-file-not-mention
1 parent 63751c1 commit d575601

File tree

4 files changed

+105
-132
lines changed

4 files changed

+105
-132
lines changed

app/Main.hs

Lines changed: 25 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -81,40 +81,40 @@ formatOne ::
8181
formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
8282
withPrettyOrmoluExceptions (cfgColorMode rawConfig) $ do
8383
let getCabalInfoForSourceFile' sourceFile = do
84-
cabalSearchResult <- getCabalInfoForSourceFile sourceFile
8584
let debugEnabled = cfgDebug rawConfig
86-
case cabalSearchResult of
87-
CabalNotFound -> do
85+
getCabalInfoForSourceFile sourceFile >>= \case
86+
Nothing -> do
8887
when debugEnabled $
8988
hPutStrLn stderr $
9089
"Could not find a .cabal file for " <> sourceFile
91-
return Nothing
92-
CabalDidNotMention cabalInfo -> do
93-
when debugEnabled $ do
94-
relativeCabalFile <-
95-
makeRelativeToCurrentDirectory (ciCabalFilePath cabalInfo)
96-
hPutStrLn stderr $
97-
"Found .cabal file "
98-
<> relativeCabalFile
99-
<> ", but it did not mention "
100-
<> sourceFile
101-
return (Just cabalInfo)
102-
CabalFound cabalInfo -> return (Just cabalInfo)
90+
return (Nothing, Nothing)
91+
Just CabalInfo {..} -> do
92+
mStanzaInfo <- lookupStanzaInfo sourceFile ciStanzaInfoMap
93+
case mStanzaInfo of
94+
Nothing | debugEnabled -> do
95+
relativeCabalFile <- makeRelativeToCurrentDirectory ciCabalFilePath
96+
hPutStrLn stderr $
97+
"Found .cabal file "
98+
<> relativeCabalFile
99+
<> ", but it did not mention "
100+
<> sourceFile
101+
_ -> pure ()
102+
return (Just ciPackageName, mStanzaInfo)
103103
getDotOrmoluForSourceFile' sourceFile = do
104104
if optDoNotUseDotOrmolu
105105
then return Nothing
106106
else Just <$> getDotOrmoluForSourceFile sourceFile
107107
case FP.normalise <$> mpath of
108108
-- input source = STDIN
109109
Nothing -> do
110-
mcabalInfo <- case (optStdinInputFile, optDoNotUseCabal) of
111-
(_, True) -> return Nothing
110+
(mPackageName, mStanzaInfo) <- case (optStdinInputFile, optDoNotUseCabal) of
111+
(_, True) -> return (Nothing, Nothing)
112112
(Nothing, False) -> throwIO OrmoluMissingStdinInputFile
113113
(Just inputFile, False) -> getCabalInfoForSourceFile' inputFile
114114
mdotOrmolu <- case optStdinInputFile of
115115
Nothing -> return Nothing
116116
Just inputFile -> getDotOrmoluForSourceFile' inputFile
117-
config <- patchConfig Nothing mcabalInfo mdotOrmolu
117+
config <- patchConfig Nothing mPackageName mStanzaInfo mdotOrmolu
118118
case mode of
119119
Stdout -> do
120120
ormoluStdin config >>= TIO.putStr
@@ -134,15 +134,16 @@ formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
134134
handleDiff originalInput formattedInput stdinRepr
135135
-- input source = a file
136136
Just inputFile -> do
137-
mcabalInfo <-
137+
(mPackageName, mStanzaInfo) <-
138138
if optDoNotUseCabal
139-
then return Nothing
139+
then return (Nothing, Nothing)
140140
else getCabalInfoForSourceFile' inputFile
141141
mdotOrmolu <- getDotOrmoluForSourceFile' inputFile
142142
config <-
143143
patchConfig
144144
(Just (detectSourceType inputFile))
145-
mcabalInfo
145+
mPackageName
146+
mStanzaInfo
146147
mdotOrmolu
147148
case mode of
148149
Stdout -> do
@@ -163,7 +164,7 @@ formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
163164
ormolu config inputFile originalInput
164165
handleDiff originalInput formattedInput inputFile
165166
where
166-
patchConfig mdetectedSourceType mcabalInfo mdotOrmolu = do
167+
patchConfig mdetectedSourceType mPackageName mStanzaInfo mdotOrmolu = do
167168
let sourceType =
168169
fromMaybe
169170
ModuleSource
@@ -173,7 +174,8 @@ formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
173174
return $
174175
refineConfig
175176
sourceType
176-
mcabalInfo
177+
mPackageName
178+
mStanzaInfo
177179
mfixityOverrides
178180
mmoduleReexports
179181
rawConfig

src/Ormolu.hs

Lines changed: 24 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,11 @@ module Ormolu
2020
DynOption (..),
2121

2222
-- * Cabal info
23-
CabalUtils.CabalSearchResult (..),
2423
CabalUtils.CabalInfo (..),
24+
CabalUtils.StanzaInfo (..),
25+
CabalUtils.defaultStanzaInfo,
26+
CabalUtils.StanzaInfoMap,
27+
CabalUtils.lookupStanzaInfo,
2528
CabalUtils.getCabalInfoForSourceFile,
2629

2730
-- * Fixity overrides and module re-exports
@@ -46,6 +49,7 @@ import Data.Set qualified as Set
4649
import Data.Text (Text)
4750
import Data.Text qualified as T
4851
import Debug.Trace
52+
import Distribution.PackageDescription (PackageName)
4953
import GHC.Driver.CmdLine qualified as GHC
5054
import GHC.Types.SrcLoc
5155
import Ormolu.Config
@@ -167,18 +171,20 @@ ormoluStdin ::
167171
ormoluStdin cfg =
168172
getContentsUtf8 >>= ormolu cfg "<stdin>"
169173

170-
-- | Refine a 'Config' by incorporating given 'SourceType', 'CabalInfo', and
171-
-- fixity overrides 'FixityMap'. You can use 'detectSourceType' to deduce
172-
-- 'SourceType' based on the file extension,
173-
-- 'CabalUtils.getCabalInfoForSourceFile' to obtain 'CabalInfo' and
174-
-- 'getFixityOverridesForSourceFile' for 'FixityMap'.
174+
-- | Refine a 'Config' by incorporating the given information.
175175
--
176-
-- @since 0.5.3.0
176+
-- You can use 'detectSourceType' to deduce 'SourceType' based on the file extension,
177+
-- 'CabalUtils.getCabalInfoForSourceFile' to obtain 'PackageName' and
178+
-- 'CabalUtils.StanzaInfo', and 'getFixityOverridesForSourceFile' for 'FixityMap'.
179+
--
180+
-- @since 0.8.0.0
177181
refineConfig ::
178182
-- | Source type to use
179183
SourceType ->
180-
-- | Cabal info for the file, if available
181-
Maybe CabalUtils.CabalInfo ->
184+
-- | Name of the package, if available
185+
Maybe PackageName ->
186+
-- | Stanza information for the source file, if available
187+
Maybe CabalUtils.StanzaInfo ->
182188
-- | Fixity overrides, if available
183189
Maybe FixityOverrides ->
184190
-- | Module re-exports, if available
@@ -187,7 +193,7 @@ refineConfig ::
187193
Config region ->
188194
-- | Refined 'Config'
189195
Config region
190-
refineConfig sourceType mcabalInfo mfixityOverrides mreexports rawConfig =
196+
refineConfig sourceType mPackageName mStanzaInfo mfixityOverrides mreexports rawConfig =
191197
rawConfig
192198
{ cfgDynOptions = cfgDynOptions rawConfig ++ dynOptsFromCabal,
193199
cfgFixityOverrides =
@@ -212,16 +218,14 @@ refineConfig sourceType mcabalInfo mfixityOverrides mreexports rawConfig =
212218
where
213219
fixityOverrides = fromMaybe defaultFixityOverrides mfixityOverrides
214220
reexports = fromMaybe defaultModuleReexports mreexports
215-
(dynOptsFromCabal, depsFromCabal) =
216-
case mcabalInfo of
217-
Nothing ->
218-
-- If no cabal info is provided, assume base as a dependency by
219-
-- default.
220-
([], defaultDependencies)
221-
Just CabalUtils.CabalInfo {..} ->
222-
-- It makes sense to take into account the operator info for the
223-
-- package itself if we know it, as if it were its own dependency.
224-
(ciDynOpts, Set.insert ciPackageName ciDependencies)
221+
CabalUtils.StanzaInfo {..} = fromMaybe CabalUtils.defaultStanzaInfo mStanzaInfo
222+
dynOptsFromCabal = siDynOpts
223+
depsFromCabal =
224+
case mPackageName of
225+
Nothing -> siDependencies
226+
-- It makes sense to take into account the operator info for the
227+
-- package itself if we know it, as if it were its own dependency.
228+
Just package -> Set.insert package siDependencies
225229

226230
----------------------------------------------------------------------------
227231
-- Helpers

src/Ormolu/Utils/Cabal.hs

Lines changed: 34 additions & 71 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,13 @@
1+
{-# LANGUAGE DuplicateRecordFields #-}
12
{-# LANGUAGE LambdaCase #-}
23
{-# LANGUAGE RecordWildCards #-}
34

45
module Ormolu.Utils.Cabal
5-
( CabalSearchResult (..),
6-
CabalInfo (..),
6+
( CabalInfo (..),
7+
StanzaInfo (..),
8+
defaultStanzaInfo,
9+
StanzaInfoMap,
10+
lookupStanzaInfo,
711
Extension (..),
812
getCabalInfoForSourceFile,
913
findCabalFile,
@@ -34,29 +38,14 @@ import System.Directory
3438
import System.FilePath
3539
import System.IO.Unsafe (unsafePerformIO)
3640

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-
5041
-- | Cabal information of interest to Ormolu.
5142
data CabalInfo = CabalInfo
5243
{ -- | Package name
5344
ciPackageName :: !PackageName,
54-
-- | Extension and language settings in the form of 'DynOption's
55-
ciDynOpts :: ![DynOption],
56-
-- | Direct dependencies
57-
ciDependencies :: !(Set PackageName),
5845
-- | 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
6049
}
6150
deriving (Eq, Show)
6251

@@ -67,11 +56,18 @@ data StanzaInfo = StanzaInfo
6756
-- | Direct dependencies
6857
siDependencies :: !(Set PackageName)
6958
}
70-
deriving (Show)
59+
deriving (Eq, Show)
60+
61+
defaultStanzaInfo :: StanzaInfo
62+
defaultStanzaInfo =
63+
StanzaInfo
64+
{ siDynOpts = [],
65+
siDependencies = defaultDependencies
66+
}
7167

7268
-- | Map from source files (absolute path without extensions) to the corresponding stanza information.
7369
newtype StanzaInfoMap = StanzaInfoMap (Map FilePath StanzaInfo)
74-
deriving (Show)
70+
deriving (Eq, Show)
7571

7672
-- | Look up the given source file in the 'StanzaInfoMap'.
7773
lookupStanzaInfo :: FilePath -> StanzaInfoMap -> IO (Maybe StanzaInfo)
@@ -86,17 +82,9 @@ getCabalInfoForSourceFile ::
8682
-- | Haskell source file
8783
FilePath ->
8884
-- | Extracted cabal info, if any
89-
m CabalSearchResult
85+
m (Maybe CabalInfo)
9086
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
10088

10189
-- | Find the path to an appropriate @.cabal@ file for a Haskell source
10290
-- file, if available.
@@ -109,16 +97,8 @@ findCabalFile ::
10997
findCabalFile = findClosestFileSatisfying $ \x ->
11098
takeExtension x == ".cabal"
11199

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)
122102
cacheRef = unsafePerformIO $ newIORef M.empty
123103
{-# NOINLINE cacheRef #-}
124104

@@ -127,37 +107,20 @@ parseCabalInfo ::
127107
(MonadIO m) =>
128108
-- | Location of the .cabal file
129109
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
136112
cabalFile <- makeAbsolute cabalFileAsGiven
137-
CachedCabalFile {..} <- withIORefCache cacheRef cabalFile $ do
113+
withIORefCache cacheRef cabalFile $ do
138114
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
161124

162125
-- | Get a map from Haskell source file paths (without any extensions) to
163126
-- the corresponding 'DynOption's and dependencies.

0 commit comments

Comments
 (0)