Skip to content

Commit

Permalink
Fix removal of empty lines in free text fields
Browse files Browse the repository at this point in the history
... like `description`

With cabal-version: 3.0 one doesn't need to use single dot lines
to indicate empty lines, but cabal-fmt removed completely empty lines
squashing paragraphs together

We now treat free text fields specially (as does `Cabal-fmt`),
by not parsing&prettyprinting them
  • Loading branch information
phadej committed Jan 14, 2024
1 parent 5041142 commit 324c8a1
Show file tree
Hide file tree
Showing 14 changed files with 241 additions and 59 deletions.
5 changes: 5 additions & 0 deletions Changelog.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
# 0.1.10

- Fix removal of empty lines in free text fields (like `description`)
when using `cabal-version: 3.0` (where you can use empty lines)

# 0.1.9

- Change how version ranges with carets are formatted once again.
Expand Down
8 changes: 6 additions & 2 deletions cabal-fmt.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 2.2
name: cabal-fmt
version: 0.1.9
version: 0.1.10
synopsis: Format .cabal files
category: Development
description:
Expand Down Expand Up @@ -56,6 +56,9 @@ library cabal-fmt-internal
, parsec ^>=3.1.13.0
, pretty ^>=1.1.3.6

if impl(ghc <8.10)
build-depends: base-orphans >=0.9.1

-- our version interval normalisation
build-depends: version-interval

Expand All @@ -70,6 +73,7 @@ library cabal-fmt-internal
CabalFmt.Fields.Modules
CabalFmt.Fields.SourceFiles
CabalFmt.Fields.TestedWith
CabalFmt.FreeText
CabalFmt.Glob
CabalFmt.Monad
CabalFmt.Options
Expand Down Expand Up @@ -114,7 +118,7 @@ test-suite golden
type: exitcode-stdio-1.0
default-language: Haskell2010
hs-source-dirs: tests
main-is: Golden.hs
main-is: golden.hs

-- dependencies in library
build-depends:
Expand Down
22 changes: 22 additions & 0 deletions fixtures/issue29.cabal
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
cabal-version: 3.0
name: issue29
version: 0
description:
First Paragraph





Second Paragraph

library
default-language: Haskell2010
hs-source-dirs: src
build-depends:
base >=4.3 && <4.18

exposed-modules:
Data.Bifunctor.Assoc
Data.Bifunctor.Swap

15 changes: 15 additions & 0 deletions fixtures/issue29.format
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
cabal-version: 3.0
name: issue29
version: 0
description:
First Paragraph

Second Paragraph

library
default-language: Haskell2010
hs-source-dirs: src
build-depends: base >=4.3 && <4.18
exposed-modules:
Data.Bifunctor.Assoc
Data.Bifunctor.Swap
59 changes: 38 additions & 21 deletions src/CabalFmt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ import CabalFmt.Comments
import CabalFmt.Fields
import CabalFmt.Fields.BuildDepends
import CabalFmt.Fields.Extensions
import CabalFmt.FreeText
import CabalFmt.Fields.Modules
import CabalFmt.Fields.SourceFiles
import CabalFmt.Fields.TestedWith
Expand All @@ -49,11 +50,20 @@ import CabalFmt.Refactoring

cabalFmt :: MonadCabalFmt r m => FilePath -> BS.ByteString -> m String
cabalFmt filepath contents = do
-- determine cabal-version
cabalFile <- asks (optCabalFile . view options)
csv <- case cabalFile of
False -> return C.cabalSpecLatest
True -> do
gpd <- parseGpd filepath contents
return $ C.specVersion
$ C.packageDescription gpd

inputFields' <- parseFields contents
let (inputFieldsC, endComments) = attachComments contents inputFields'

-- parse pragmas
let parse c = case parsePragmas c of (ws, ps) -> traverse_ displayWarning ws *> return (c, ps)
let parse (pos, c) = case parsePragmas c of (ws, ps) -> traverse_ displayWarning ws *> return (pos, c, ps)
inputFieldsP' <- traverse (traverse parse) inputFieldsC
endCommentsPragmas <- case parsePragmas endComments of
(ws, ps) -> traverse_ displayWarning ws *> return ps
Expand All @@ -67,49 +77,56 @@ cabalFmt filepath contents = do
-- options morphisms
let pragmas :: [GlobalPragma]
pragmas = fst $ partitionPragmas $
foldMap (foldMap snd) inputFieldsP' <> endCommentsPragmas
foldMap (foldMap trdOf3) inputFieldsP' <> endCommentsPragmas

optsEndo :: OptionsMorphism
optsEndo = foldMap pragmaToOM pragmas

cabalFile <- asks (optCabalFile . view options)
csv <- case cabalFile of
False -> return C.cabalSpecLatest
True -> do
gpd <- parseGpd filepath contents
return $ C.specVersion
$ C.packageDescription gpd

local (over options $ \o -> runOptionsMorphism optsEndo $ o { optSpecVersion = csv }) $ do
indentWith <- asks (optIndent . view options)
let inputFields = fmap (fmap fst) inputFieldsR
let inputFields = inputFieldsR

outputPrettyFields <- C.genericFromParsecFields
prettyFieldLines
outputPrettyFields <- genericFromParsecFields
(\n ann -> prettyFieldLines n (fstOf3 ann))
prettySectionArgs
inputFields

return $ C.showFields' fromComments (const id) indentWith outputPrettyFields
return $ C.showFields' (fromComments . sndOf3) (const id) indentWith outputPrettyFields
& if nullComments endComments then id else
(++ unlines ("" : [ C.fromUTF8BS c | c <- unComments endComments ]))

fromComments :: Comments -> C.CommentPosition
fromComments (Comments []) = C.NoComment
fromComments (Comments bss) = C.CommentBefore (map C.fromUTF8BS bss)

genericFromParsecFields
:: Applicative f
=> (C.FieldName -> ann -> [C.FieldLine ann] -> f PP.Doc) -- ^ transform field contents
-> (C.FieldName -> [C.SectionArg ann] -> f [PP.Doc]) -- ^ transform section arguments
-> [C.Field ann]
-> f [C.PrettyField ann]
genericFromParsecFields f g = goMany where
goMany = traverse go

go (C.Field (C.Name ann name) fls) = C.PrettyField ann name <$> f name ann fls
go (C.Section (C.Name ann name) secargs fs) = C.PrettySection ann name <$> g name secargs <*> goMany fs

-------------------------------------------------------------------------------
-- Field prettyfying
-------------------------------------------------------------------------------

prettyFieldLines :: MonadCabalFmt r m => C.FieldName -> [C.FieldLine ann] -> m PP.Doc
prettyFieldLines fn fls =
fromMaybe (C.prettyFieldLines fn fls) <$> knownField fn fls
prettyFieldLines :: MonadCabalFmt r m => C.FieldName -> C.Position -> [C.FieldLine CommentsPragmas] -> m PP.Doc
prettyFieldLines fn pos fls =
fromMaybe (C.prettyFieldLines fn fls) <$> knownField fn pos fls

knownField :: MonadCabalFmt r m => C.FieldName -> [C.FieldLine ann] -> m (Maybe PP.Doc)
knownField fn fls = do
knownField :: MonadCabalFmt r m => C.FieldName -> C.Position -> [C.FieldLine CommentsPragmas] -> m (Maybe PP.Doc)
knownField fn pos fls = do
opts <- asks (view options)
let v = optSpecVersion opts
return $ join $ fieldDescrLookup (fieldDescrs opts) fn $ \p pp ->
let v = optSpecVersion opts
let ft = fieldlinesToFreeText v pos (fmap (fmap fstOf3) fls)
let ft' = showFreeText v ft

return $ join $ fieldDescrLookup (fieldDescrs opts) fn (Just ft') $ \p pp ->
case C.runParsecParser' v p "<input>" (C.fieldLinesToStream fls) of
Right x -> Just (pp x)
Left _ -> Nothing
Expand Down
25 changes: 15 additions & 10 deletions src/CabalFmt/Comments.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@ import qualified Distribution.Parsec as C

import CabalFmt.Prelude

import Debug.Trace

Check warning on line 20 in src/CabalFmt/Comments.hs

View workflow job for this annotation

GitHub Actions / Simple: GHC 9.2 on macos-latest

The import of ‘Debug.Trace’ is redundant

Check warning on line 20 in src/CabalFmt/Comments.hs

View workflow job for this annotation

GitHub Actions / Simple: GHC 9.2 on windows-latest

The import of ‘Debug.Trace’ is redundant

-------------------------------------------------------------------------------
-- Comments wrapper
-------------------------------------------------------------------------------
Expand Down Expand Up @@ -44,9 +46,9 @@ nullComments (Comments cs) = null cs
attachComments
:: BS.ByteString -- ^ source with comments
-> [C.Field C.Position] -- ^ parsed source fields
-> ([C.Field Comments], Comments)
-> ([C.Field (C.Position, Comments)], Comments)
attachComments input inputFields =
(overAnn attach inputFields, endComments)
(overAnn attach attach' inputFields, endComments)
where
inputFieldsU :: [(FieldPath, C.Field C.Position)]
inputFieldsU = fieldUniverseN inputFields
Expand All @@ -68,27 +70,30 @@ attachComments input inputFields =
, isNothing (findPath C.fieldAnn l inputFieldsU)
]

attach :: FieldPath -> C.Position -> Comments
attach fp _pos = fromMaybe mempty (Map.lookup fp comments')
attach :: FieldPath -> C.Position -> (C.Position, Comments)
attach fp pos = (pos, fromMaybe mempty (Map.lookup fp comments'))

attach' :: C.Position -> (C.Position, Comments)
attach' pos = (pos, mempty)

overAnn :: forall a b. (FieldPath -> a -> b) -> [C.Field a] -> [C.Field b]
overAnn f = go' id where
overAnn :: forall a b. (FieldPath -> a -> b) -> (a -> b) -> [C.Field a] -> [C.Field b]
overAnn f h = go' id where
go :: (FieldPath -> FieldPath) -> Int -> C.Field a -> C.Field b
go g i (C.Field (C.Name a name) fls) =
C.Field (C.Name b name) (b <$$ fls)
C.Field (C.Name b name) (h <$$> fls)
where
b = f (g (Nth i End)) a

go g i (C.Section (C.Name a name) args fls) =
C.Section (C.Name b name) (b <$$ args) (go' (g . Nth i) fls)
C.Section (C.Name b name) (h <$$> args) (go' (g . Nth i) fls)
where
b = f (g (Nth i End)) a

go' :: (FieldPath -> FieldPath) -> [C.Field a] -> [C.Field b]
go' g xs = zipWith (go g) [0..] xs

(<$$) :: (Functor f, Functor g) => x -> f (g y) -> f (g x)
x <$$ y = (x <$) <$> y
(<$$>) :: (Functor f, Functor g) => (x -> y) -> f (g x) -> f (g y)
x <$$> y = (x <$>) <$> y

-------------------------------------------------------------------------------
-- Find comments in the input
Expand Down
31 changes: 14 additions & 17 deletions src/CabalFmt/Fields.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
Expand All @@ -15,7 +16,6 @@ module CabalFmt.Fields (
) where

import qualified Data.Map.Strict as Map
import qualified Distribution.Compat.CharParsing as C
import qualified Distribution.FieldGrammar as C
import qualified Distribution.Fields.Field as C
import qualified Distribution.Parsec as C
Expand All @@ -24,15 +24,18 @@ import qualified Text.PrettyPrint as PP

import CabalFmt.Prelude

import Debug.Trace

Check warning on line 27 in src/CabalFmt/Fields.hs

View workflow job for this annotation

GitHub Actions / Simple: GHC 9.2 on macos-latest

The import of ‘Debug.Trace’ is redundant

Check warning on line 27 in src/CabalFmt/Fields.hs

View workflow job for this annotation

GitHub Actions / Simple: GHC 9.2 on windows-latest

The import of ‘Debug.Trace’ is redundant

-------------------------------------------------------------------------------
-- FieldDescr variant
-------------------------------------------------------------------------------

-- strict pair
data SP = forall f. SP
{ _pPretty :: !(f -> PP.Doc)
, _pParse :: !(forall m. C.CabalParsing m => m f)
}
data SP where
FreeText :: SP
SP :: !(f -> PP.Doc)
-> !(forall m. C.CabalParsing m => m f)
-> SP

-- | Lookup both pretty-printer and value parser.
--
Expand All @@ -42,10 +45,12 @@ fieldDescrLookup
:: C.CabalParsing m
=> FieldDescrs s a
-> C.FieldName
-> r -- field is freetext
-> (forall f. m f -> (f -> PP.Doc) -> r)
-> Maybe r
fieldDescrLookup (F m) fn kont = kont' <$> Map.lookup fn m where
fieldDescrLookup (F m) fn ft kont = kont' <$> Map.lookup fn m where
kont' (SP a b) = kont b a
kont' FreeText = ft

-- | A collection field parsers and pretty-printers.
newtype FieldDescrs s a = F { runF :: Map.Map C.FieldName SP }
Expand Down Expand Up @@ -94,17 +99,9 @@ instance C.FieldGrammar PrettyParsec FieldDescrs where
monoidalFieldAla fn _pack _ =
singletonF fn (C.pretty . pack' _pack) (unpack' _pack <$> C.parsec)

freeTextField fn _ = singletonF fn
PP.text
(C.munch $ const True)

freeTextFieldDef fn _ = singletonF fn
PP.text
(C.munch $ const True)

freeTextFieldDefST fn _ = singletonF fn
PP.text
(C.munch $ const True)
freeTextField fn _ = F $ Map.singleton fn FreeText
freeTextFieldDef fn _ = F $ Map.singleton fn FreeText
freeTextFieldDefST fn _ = F $ Map.singleton fn FreeText

prefixedFields _fnPfx _l = F mempty
knownField _ = pure ()
Expand Down
Loading

0 comments on commit 324c8a1

Please sign in to comment.