cabal-fix-0.0.0.2: Fix for cabal files.
Safe HaskellSafe-Inferred
LanguageGHC2021

CabalFix

Description

Tools to print, parse and fix cabal files, ByteString and Field lists.

Synopsis

Usage

>>> :set -XOverloadedStrings
>>> :set -XOverloadedLabels
>>> import CabalFix
>>> import Optics.Extra
>>> import Data.ByteString.Char8 qualified as C
>>> import CabalFix.Patch
>>> bs = minimalExampleBS
>>> cfg = defaultConfig
>>> (Just cf) = preview (cabalFields' cfg) bs
>>> fs = cf & view (#fields % fieldList')
>>> printCabalFields cfg (cf & over (#fields % fieldList') (take 4)) & C.putStr
cabal-version: 3.0
name: minimal
version: 0.1.0.0
license: BSD-2-Clause

Configuration

data Config Source #

Configuration values for various aspects of (re)rendering a cabal file.

Constructors

Config 

Fields

Instances

Instances details
Generic Config Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

Read Config Source # 
Instance details

Defined in CabalFix

Show Config Source # 
Instance details

Defined in CabalFix

Eq Config Source # 
Instance details

Defined in CabalFix

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

type Rep Config Source # 
Instance details

Defined in CabalFix

type Rep Config = D1 ('MetaData "Config" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "Config" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "freeTexts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ByteString]) :*: S1 ('MetaSel ('Just "fieldRemovals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ByteString])) :*: (S1 ('MetaSel ('Just "preferredDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, ByteString)]) :*: S1 ('MetaSel ('Just "addFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, ByteString, AddPolicy)]))) :*: ((S1 ('MetaSel ('Just "fixCommas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, CommaStyle, CommaTrail)]) :*: S1 ('MetaSel ('Just "sortFieldLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ByteString])) :*: (S1 ('MetaSel ('Just "doSortFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "fieldOrdering") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, Double)])))) :*: (((S1 ('MetaSel ('Just "doFixBuildDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "depAlignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DepAlignment)) :*: (S1 ('MetaSel ('Just "removeBlankFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "valueAligned") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValueAlignment))) :*: ((S1 ('MetaSel ('Just "valueAlignGap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "sectionMargin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Margin)) :*: (S1 ('MetaSel ('Just "commentMargin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Margin) :*: (S1 ('MetaSel ('Just "narrowN") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "indentN") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))))

defaultConfig :: Config Source #

An opinionated configuration for formatting cabal files.

Some opinions (that can be configured):

>>> fixCommas defaultConfig
[("extra-doc-files",NoCommas,NoTrailer),("build-depends",PrefixCommas,Trailer)]

PrefixCommas are better for the dependency list as dependency ranges are already noisy enough without a comma thrown in. Trailer (which means leading comma for prefixed commas) is neater and easier to prepend to, append to & sort.

If a field list doesn't need commas, then they should be removed.

>>> preferredDeps defaultConfig
[("base",">=4.14 && <5")]

Standard practice compared with the much tighter eg base ^>=4.17.2.1

>>> sortFieldLines defaultConfig
["build-depends","exposed-modules","default-extensions","ghc-options","extra-doc-files","tested-with"]

Sort all the things, but especially the module list.

>>> valueAligned defaultConfig
ValueUnaligned

Adding an extra, long-named field to the cabal file means we have to re-align all the value parts in all the other fields.

>>> depAlignment defaultConfig
DepAligned

build-depends is so busy, however, the extra alignment becomes more important.

>>> doSortFields defaultConfig
True

Whatever the order, fields should have the same order within each section.

data AddPolicy Source #

Policy for Fields listed in addFields

Constructors

AddReplace

Replace existing values

AddAppend

Append after existing values

AddIfNotExisting

Add only of the Field doesn't exist

Instances

Instances details
Generic AddPolicy Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep AddPolicy :: Type -> Type #

Read AddPolicy Source # 
Instance details

Defined in CabalFix

Show AddPolicy Source # 
Instance details

Defined in CabalFix

Eq AddPolicy Source # 
Instance details

Defined in CabalFix

type Rep AddPolicy Source # 
Instance details

Defined in CabalFix

type Rep AddPolicy = D1 ('MetaData "AddPolicy" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "AddReplace" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AddAppend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AddIfNotExisting" 'PrefixI 'False) (U1 :: Type -> Type)))

data CommaStyle Source #

The style for comma-separated values

Constructors

PrefixCommas

commas before values

PostfixCommas

commas after values

FreeformCommas

comma freedom

NoCommas

remove commas (allowed for some fields)

Instances

Instances details
Generic CommaStyle Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep CommaStyle :: Type -> Type #

Read CommaStyle Source # 
Instance details

Defined in CabalFix

Show CommaStyle Source # 
Instance details

Defined in CabalFix

Eq CommaStyle Source # 
Instance details

Defined in CabalFix

type Rep CommaStyle Source # 
Instance details

Defined in CabalFix

type Rep CommaStyle = D1 ('MetaData "CommaStyle" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) ((C1 ('MetaCons "PrefixCommas" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostfixCommas" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FreeformCommas" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoCommas" 'PrefixI 'False) (U1 :: Type -> Type)))

data CommaTrail Source #

Include a trailing (or leading) comma, after the last value (or before the first value.)

Constructors

Trailer 
NoTrailer 

Instances

Instances details
Generic CommaTrail Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep CommaTrail :: Type -> Type #

Read CommaTrail Source # 
Instance details

Defined in CabalFix

Show CommaTrail Source # 
Instance details

Defined in CabalFix

Eq CommaTrail Source # 
Instance details

Defined in CabalFix

type Rep CommaTrail Source # 
Instance details

Defined in CabalFix

type Rep CommaTrail = D1 ('MetaData "CommaTrail" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "Trailer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoTrailer" 'PrefixI 'False) (U1 :: Type -> Type))

data DepAlignment Source #

Whether the range part of the dependency list should be vertically aligned on a column.

Constructors

DepAligned 
DepUnaligned 

Instances

Instances details
Read DepAlignment Source # 
Instance details

Defined in CabalFix

Show DepAlignment Source # 
Instance details

Defined in CabalFix

Eq DepAlignment Source # 
Instance details

Defined in CabalFix

data ValueAlignment Source #

Whether the value part of each field should be vertically aligned on a column.

Instances

Instances details
Generic ValueAlignment Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep ValueAlignment :: Type -> Type #

Read ValueAlignment Source # 
Instance details

Defined in CabalFix

Show ValueAlignment Source # 
Instance details

Defined in CabalFix

Eq ValueAlignment Source # 
Instance details

Defined in CabalFix

type Rep ValueAlignment Source # 
Instance details

Defined in CabalFix

type Rep ValueAlignment = D1 ('MetaData "ValueAlignment" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "ValueAligned" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueUnaligned" 'PrefixI 'False) (U1 :: Type -> Type))

data Margin Source #

A margin tracker for combining sections.

Constructors

Margin 
NoMargin 

Instances

Instances details
Semigroup Margin Source #

Collapse margins, any margin = margin

Instance details

Defined in CabalFix

Generic Margin Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep Margin :: Type -> Type #

Methods

from :: Margin -> Rep Margin x #

to :: Rep Margin x -> Margin #

Read Margin Source # 
Instance details

Defined in CabalFix

Show Margin Source # 
Instance details

Defined in CabalFix

Eq Margin Source # 
Instance details

Defined in CabalFix

Methods

(==) :: Margin -> Margin -> Bool #

(/=) :: Margin -> Margin -> Bool #

type Rep Margin Source # 
Instance details

Defined in CabalFix

type Rep Margin = D1 ('MetaData "Margin" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "Margin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoMargin" 'PrefixI 'False) (U1 :: Type -> Type))

CabalFields

type Comment = [ByteString] Source #

Note that cabal does not have multi-line comments

data CabalFields Source #

Field list annotated with a Comment

Note that this type does not contain any position information.

The construction assumes that comments relate to fields below, so there is potential for an end comment unrelated to any particular field.

Constructors

CabalFields 

Instances

Instances details
Monoid CabalFields Source # 
Instance details

Defined in CabalFix

Semigroup CabalFields Source # 
Instance details

Defined in CabalFix

Generic CabalFields Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep CabalFields :: Type -> Type #

Show CabalFields Source # 
Instance details

Defined in CabalFix

Eq CabalFields Source # 
Instance details

Defined in CabalFix

ToExpr CabalFields Source # 
Instance details

Defined in CabalFix

type Rep CabalFields Source # 
Instance details

Defined in CabalFix

type Rep CabalFields = D1 ('MetaData "CabalFields" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "CabalFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (Field Comment))) :*: S1 ('MetaSel ('Just "endComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment)))

cabalFields' :: Config -> Prism' ByteString CabalFields Source #

A Prism betwixt a ByteString and a CabalFields.

>>> cf & over (#fields % fieldList') (take 2) & review (cabalFields' cfg) & C.putStr
cabal-version: 3.0
name: minimal

fieldList' :: Iso' (Vector (Field Comment)) [Field Comment] Source #

iso to flip between vectors and lists easily.

>>> cf & view (#fields % fieldList') & take 2
[Field (Name [] "cabal-version") [FieldLine [] "3.0"],Field (Name [] "name") [FieldLine [] "minimal"]]

Lenses

Lensing into Field is tricky.

A Field is a sum type of a field constructor or a section constructor, and a section contains fields.

Sometimes you only want to modify a field (and not a section). Other times you want to access a section but not a field. Sometimes you want to modify either a field or a section, and the fields within sections. It can be difficult to remember which lens is which.

The use of a list is also problematic; it is hard to safely delete a field, and invalid cabals are easily represented. A list can easily contain two name fields say, which is an invalid state. It can contain no name which is also invalid. It is difficult, however, to switch to a map because sections contain lists of fields (and not maps of fields).

Most useful are lenses that lens into named fields.

topfield' :: FieldName -> Lens' CabalFields (Maybe (Field Comment)) Source #

A lens that doesn't descend into sections. It will lens the first-encountered named field, if any.

>>> view (topfield' "name") cf
Just (Field (Name [] "name") [FieldLine [] "minimal"])
>>> view (topfield' "build-depends") cf
Nothing

field' :: FieldName -> Getter [Field Comment] [Field Comment] Source #

A lens by name into a field (but not a section).

>>> fs & view (field' "version")
[Field (Name [] "version") [FieldLine [] "0.1.0.0"]]

subfield' :: FieldName -> Getter (Field Comment) [Field Comment] Source #

A getter by name into a field (including within sections)

>>> fs & toListOf (each % subfield' "default-language")
[[],[],[],[],[],[],[],[],[Field (Name [] "default-language") [FieldLine [] "GHC2021"]],[Field (Name [] "default-language") [FieldLine [] "GHC2021"]]]

section' :: FieldName -> Getter [Field ann] [Field ann] Source #

A getter of a section (not a field)

>>> fs & foldOf (section' "library" % each % secFields' % field' "exposed-modules")
[Field (Name [] "exposed-modules") [FieldLine [] "MyLib"]]

secFields' :: Lens' (Field ann) [Field ann] Source #

A getter of section fields

fieldOrSection' :: FieldName -> Getter [Field ann] [Field ann] Source #

A getter by name of a field or section.

overField :: (Field ann -> Field ann) -> Field ann -> Field ann Source #

A mapping into the field structure, operating on field lists in sections as well as the field itself.

overFields :: ([Field ann] -> [Field ann]) -> [Field ann] -> [Field ann] Source #

A mapping into the field structure, operating on field lists in sections as well as field lists themselves.

pname :: CabalFields -> ByteString Source #

Project name. Errors if the field is missing.

>>> pname cf
"minimal"

fieldLines' :: Lens' (Field ann) [FieldLine ann] Source #

Lens into field lines

>>> fs & foldOf (section' "test-suite" % each % secFields' % field' "build-depends" % each % fieldLines')
[FieldLine [] "base ^>=4.17.2.1,",FieldLine [] "minimal"]

fieldName' :: Lens' (Field ann) ByteString Source #

Name of (field or section).

>>> head fs & view fieldName'
"cabal-version"

secArgs' :: Lens' (Field ann) [SectionArg ann] Source #

lens into SectionArg part of a section.

Errors if you actually have a field.

>>> fs & foldOf (section' "test-suite" % each % secArgs')
[SecArgName [] "minimal-test"]

secArgBS' :: Lens' (SectionArg ann) (ByteString, ByteString) Source #

secArg lens into a ByteString representation

>>> fs & foldOf (section' "test-suite" % each % secArgs' % each % secArgBS')
("name","minimal-test")

fieldLine' :: Lens' (FieldLine ann) ByteString Source #

lens into field line contents.

>>> fs & toListOf (section' "test-suite" % each % secFields' % field' "build-depends" % each % fieldLines' % each % fieldLine')
["base ^>=4.17.2.1,","minimal"]

fieldValues' :: FieldName -> Optic A_Fold '[Int, Int] [Field Comment] [Field Comment] ByteString ByteString Source #

A fold of a field list into a ByteString.

Parsing

parseCabalFields :: Config -> ByteString -> Either ByteString CabalFields Source #

Parse a ByteString into a CabalFields. Failure is possible.

>>> bs & C.lines & take 4 & C.unlines & parseCabalFields cfg
Right (CabalFields {fields = [Field (Name [] "cabal-version") [FieldLine [] "3.0"],Field (Name [] "name") [FieldLine [] "minimal"],Field (Name [] "version") [FieldLine [] "0.1.0.0"],Field (Name [] "license") [FieldLine [] "BSD-2-Clause"]], endComment = []})

Printing

printCabalFields :: Config -> CabalFields -> ByteString Source #

Printing

Convert a CabalFields to a ByteString

>>> printCabalFields cfg (cf & over (#fields % fieldList') (take 4)) & C.putStr
cabal-version: 3.0
name: minimal
version: 0.1.0.0
license: BSD-2-Clause

Fixes

fixCabalFields :: Config -> CabalFields -> CabalFields Source #

fix order:

  • removes fields
  • removes blank fields
  • fixes commas
  • adds Fields
  • fix build dependencies
  • sort field lines
  • sort fields

fixCabalFile :: FilePath -> Config -> IO Bool Source #

Fix a cabal file in-place

fixesCommas :: Config -> Field ann -> Field ann Source #

Fix the comma usage in a field list

>>> fs & toListOf (section' "test-suite" % each % secFields' % field' "build-depends" % each) & fmap (fixesCommas cfg)
[Field (Name [] "build-depends") [FieldLine [] ", base ^>=4.17.2.1",FieldLine [] ", minimal"]]

addsFields :: Config -> [Field Comment] -> [Field Comment] Source #

add fields

>>> addsFields (cfg & set #addFields [("description", "added by addsFields", AddReplace)]) []
[Field (Name [] "description") [FieldLine [] "added by addsFields"]]

addField :: AddPolicy -> Field ann -> [Field ann] -> [Field ann] Source #

Add a field according to an AddPolicy.

fixBuildDeps :: Config -> FieldName -> Field ann -> Field ann Source #

Align dependencies (if depAlignment is DepAligned), remove ranges for any self-dependency, and substitute preferred dependency ranges.

>>> fs & toListOf (section' "test-suite" % each % secFields' % field' "build-depends" % each) & fmap (fixBuildDeps cfg "minimal")
[Field (Name [] "build-depends") [FieldLine [] ", base    >=4.14 && <5",FieldLine [] ", minimal"]]

Dependency

data Dep Source #

Split of a dependency FieldLine into the dependency name and the range.

Constructors

Dep 

Instances

Instances details
Generic Dep Source # 
Instance details

Defined in CabalFix

Associated Types

type Rep Dep :: Type -> Type #

Methods

from :: Dep -> Rep Dep x #

to :: Rep Dep x -> Dep #

Show Dep Source # 
Instance details

Defined in CabalFix

Methods

showsPrec :: Int -> Dep -> ShowS #

show :: Dep -> String #

showList :: [Dep] -> ShowS #

Eq Dep Source # 
Instance details

Defined in CabalFix

Methods

(==) :: Dep -> Dep -> Bool #

(/=) :: Dep -> Dep -> Bool #

Ord Dep Source # 
Instance details

Defined in CabalFix

Methods

compare :: Dep -> Dep -> Ordering #

(<) :: Dep -> Dep -> Bool #

(<=) :: Dep -> Dep -> Bool #

(>) :: Dep -> Dep -> Bool #

(>=) :: Dep -> Dep -> Bool #

max :: Dep -> Dep -> Dep #

min :: Dep -> Dep -> Dep #

type Rep Dep Source # 
Instance details

Defined in CabalFix

type Rep Dep = D1 ('MetaData "Dep" "CabalFix" "cabal-fix-0.0.0.2-GueGPKFkv7p1skPCP5Ed4H" 'False) (C1 ('MetaCons "Dep" 'PrefixI 'True) (S1 ('MetaSel ('Just "dep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "depRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Examples

minimalExampleBS :: ByteString Source #

Minimal cabal file contents for testing purposes. Originally created via:

mkdir minimal && cd minimal && cabal init --minimal --simple --overwrite --lib --tests --language=GHC2021 --license=BSD-2-Clause  -p minimal

minimalConfig :: Config Source #

A config close to the cabal init styles.

Orphan instances

ToExpr (Field Comment) Source # 
Instance details

ToExpr (FieldLine Comment) Source # 
Instance details

ToExpr (Name Comment) Source # 
Instance details

ToExpr (SectionArg Comment) Source # 
Instance details