Git Product home page Git Product logo

brittany's Introduction

brittany Hackage version Stackage version Build Status

⚠️ This project is effectively unmaintained! I (@tfausak) would recommend switching to another formatter. At time of writing (2022-11-11), I would suggest Ormolu. Or if you prefer some configuration, I would suggest Fourmolu.

haskell source code formatter

Output sample

(see more examples and comparisons)

This project's goals roughly are to:

  • Always retain the semantics of the source being transformed;
  • Be idempotent;
  • Support the full GHC-haskell syntax including syntactic extensions (but excluding -XCPP which is too hard);
  • Retain newlines and comments unmodified;
  • Be clever about using the available horizontal space while not overflowing the column maximum unless it cannot be avoided;
  • Be clever about aligning things horizontally (this can be turned off completely however);
  • Have linear complexity in the size of the input.

In theory, the core algorithm inside brittany reaches these goals. It is rather clever about making use of horizontal space while still being linear in the size of the input (although the constant factor is not small). See these examples of clever layouting.

But brittany is not finished yet, and there are some open issues that yet require fixing:

  • only the module header (imports/exports), type-signatures and function/value bindings are processed; other module elements (data-decls, classes, instances, etc.) are not transformed in any way; this extends to e.g. bindings inside class instance definitions - they won't be touched (yet).
  • By using ghc-exactprint as the parser, brittany supports full GHC including extensions, but some of the less common syntactic elements (even of 2010 haskell) are not handled.
  • There are some known issues regarding handling of in-source comments. There are cases where comments are not copied to the output (this will be detected and the user will get an error); there are other cases where comments are moved slightly; there are also cases where comments result in wonky newline insertion (although this should be a purely aesthetic issue.)

Try without Installing

You can paste haskell code over here to test how it gets formatted by brittany. (Rg. privacy: the server does log the size of the input, but not the full input/output of requests.)

Other usage notes

  • Supports GHC version 9.0.x.
  • included in stackage with lts>=10.0 (or nightlies dating to >=2017-11-15)
  • config (file) documentation is lacking.
  • some config values can not be configured via commandline yet.
  • uses/creates user config file in ~/.config/brittany/config.yaml; also reads (the first) brittany.yaml found in current or parent directories.

Installation

  • via stack

    stack install brittany # --resolver lts-16.31

    If you use an lts that includes brittany this should just work; otherwise you may want to clone the repo and try again.

  • via cabal

    Due to constant changes to the cabal UI, I have given up on making sure these instructions work before releases. Please do not expect these instructions to be up-to-date; they may produce incomprehensible error messages, they may be broken otherwise, they may work now but break with the next cabal release. Thanks for your understanding, and feel free to open issues for any problems you encounter. -- lennart

    If you are using cabal-3.0, using cabal install brittany --installdir=$HOME/.cabal/bin might work. Keep in mind that cabal merely puts a symlink to the "store" into the installdir, so you have to re-install if you ever clean your store. On cabal-2.4, try cabal v2-install brittany. On cabal-2.2 or earlier you might be succesful using cabal new-build exe:brittany; cp `find dist-newstyle/ -name brittany -type f | xargs -x ls -t | head -n1` $HOME/.cabal/bin/. Alternatively, you can also use the v1-approach with sandboxes as cabal v1-sandbox init; cabal v1-install brittany --bindir=$HOME/.cabal/bin.

    (TODO: These instructions are more confusing than helpful. I am inclined to just remove them.)

  • on ArchLinux:

    pacman -S haskell-brittany

Development tips

Editor Integration

Sublime text

In this gist I have described a haskell setup that includes a shortcut to run brittany formatting.

VSCode

This extension connects commandline brittany to VSCode formatting API. Thanks to @MaxGabriel.

Via HLS

haskell-language-server includes a brittany plugin that directly uses the brittany library. Relevant for any editors that properly support the language-server-protocol.

Neovim / Vim 8

The Neoformat plugin comes with support for brittany built in.

Atom

Atom Beautify supports brittany as a formatter for Haskell. Since the default formatter is set to hindent, you will need to change this setting to brittany, after installing the extension.

Emacs

format-all support brittany as the default formatter for Haskell.

Usage

  • Default mode of operation: Transform a single module, from stdin to stdout. Can pass one or multiple files as input, and there is a flag to override them in place instead of using stdout (since 0.9.0.0). So:

    brittany                           # stdin -> stdout
    brittany mysource.hs               # ./mysource.hs -> stdout
    brittany --write-mode=inplace *.hs # apply formatting to all ./*.hs inplace
  • For stdin/stdout usage it makes sense to enable certain syntactic extensions by default, i.e. to add something like this to your ~/.config/brittany/config.yaml (execute brittany once to create default):

    conf_forward:
      options_ghc:
      - -XLambdaCase
      - -XMultiWayIf
      - -XGADTs
      - -XPatternGuards
      - -XViewPatterns
      - -XRecursiveDo
      - -XTupleSections
      - -XExplicitForAll
      - -XImplicitParams
      - -XQuasiQuotes
      - -XTemplateHaskell
      - -XBangPatterns
    

Feature Requests, Contribution, Documentation

For a long time this project has had a single maintainer, and as a consequence there have been some mildly large delays for reacting to feature requests and even PRs.

Sorry about that.

The good news is that this project is getting sponsored by PRODA LTD, and two previous contributors, Evan Borden and Taylor Fausak, have agreed on helping with organisational aspects. Thanks!

Still, this project has a long queue of very sensible feature requests, so it may take some time until new ones get our attention. But with the help of the co-maintainers, at least the reaction-times on PRs and the frequency of releases should improve significantly.

If you are interested in making your own contributions, there is a good amount of high-level documentation at

the documentation index

License

Copyright (C) 2016-2019 Lennart Spitzner
Copyright (C) 2019 PRODA LTD

This program is free software: you can redistribute it and/or modify it under the terms of the GNU Affero General Public License, version 3, as published by the Free Software Foundation.

This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more details.

You should have received a copy of the GNU Affero General Public License along with this program. If not, see http://www.gnu.org/licenses/.

brittany's People

Contributors

alanz avatar alexeyraga avatar bergmark avatar bsima avatar chickenprop avatar chreekat avatar damienflament avatar eborden avatar eschnett avatar expipiplus1 avatar felixonmars avatar fendor avatar infinity0 avatar jneira avatar lspitzner avatar lukel97 avatar maralorn avatar matt-noonan avatar maxgabriel avatar ndmitchell avatar pepeiborra avatar raoulhc avatar robx avatar ruhatch avatar sergv avatar sniperrifle2004 avatar soareschen avatar symbiont-matthew-piziak avatar tchajed avatar tfausak avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

brittany's Issues

Arrow notation

Brittany currently fails for the entire file whenever it encounters arrow notation.

ERROR: brittany pretty printer returned syntactically invalid result.
ERROR: encountered unknown syntactical constructs:
HsProc{}

Incorrect comment placement after formatting a multiline list.

It looks like if you have a comment on the penultimate line of a multi-line list, the comment gets pushed outside the list:

 -- | Predicates for the various autocheck functions.
 autocheckCases :: Eq a => [(String, Predicate a)]
 autocheckCases =
-  [ ("Never Deadlocks",   representative deadlocksNever)
-  , ("No Exceptions",     representative exceptionsNever)
-  , ("Consistent Result", alwaysSame) -- already representative
-  ]
+  [ ("Never Deadlocks", representative deadlocksNever)
+  , ("No Exceptions", representative exceptionsNever)
+  , ("Consistent Result", alwaysSame)
+  ] -- already representative

Enable common syntactic extensions by default

Brittany often fails to parse fragments of files due to the usage of GHC extensions. I propose enabling common syntactic extensions like LambdaCase, ExplicitForall, TupleSections, TypeApplications etc. by default to handle this.

RecordWildCards are not supported

Input:

{-# LANGUAGE RecordWildCards #-}
v = A {a = 1, ..} where b = 2

Error:

ERROR: brittany pretty printer returned syntactically invalid result.
ERROR: encountered unknown syntactical constructs:
RecordCon with puns

Quadratic run-time behaviour in size of input

Symptoms are run-times in the order of seconds for largish modules. Noticable starting at ~500 loc; a simple testcase consists of a sequence of foo$i :: Int; foo$i = $i for $i in 1..1000. The runtime for this testcase seems to grow in quadratic fashion.

Profiling shows that filterAnns is likely the cuplrit.

	total time  =       21.29 secs   (21288 ticks @ 1000 us, 1 processor)
	total alloc = 3,394,268,880 bytes  (excludes profiling overheads)

COST CENTRE                       MODULE                                                 SRC                                                                            %time %alloc

filterAnns                        Language.Haskell.Brittany.Internal.LayouterBasics      src/Language/Haskell/Brittany/Internal/LayouterBasics.hs:(240,1)-(241,67)       76.2    0.1
runMemoStateT                     Control.Monad.Trans.Memo.State                         Control/Monad/Trans/Memo/State.hs:(56,1)-(58,23)                                 5.9   26.1
everything                        Data.Generics.Schemes                                  src/Data/Generics/Schemes.hs:104:1-59                                            3.0   10.2
censor                            Control.Monad.Writer.Class                             Control/Monad/Writer/Class.hs:(99,1)-(101,17)                                    2.6   11.7
transformAlts                     Language.Haskell.Brittany.Internal.Transformations.Alt src/Language/Haskell/Brittany/Internal/Transformations/Alt.hs:(75,1)-(364,59)    1.7   13.3
...

I have not looked into what exactly makes it quadratic; the use of everything from uniplate in foldedAnnKeys looks suspicious though. Solution is either to stop filtering (filtering serves a "sandboxing" purpose mostly, at least for the per-declaration use of the function) or to make the function more efficient.

Non idempotent spaces in type applications.

foo.hs:

{-# LANGUAGE TypeApplications #-}
foo = bar @Baz

After applying brittany once:

{-# LANGUAGE TypeApplications #-}
foo =  bar @Baz

Twice:

{-# LANGUAGE TypeApplications #-}
foo =   bar @Baz

Thrice:

{-# LANGUAGE TypeApplications #-}
foo =    bar @Baz

dollar/lambda expression layouting

foldrDesc f z = unSwitchQueue $ \q ->
  switch (Min.foldrDesc (f . unTaggedF) z q) (Min.foldrAsc (f . unTaggedF) z q)

currently is layouted as

foldrDesc f z =
  unSwitchQueue
    $ \q ->
        switch (Min.foldrDesc (f . unTaggedF) z q)
               (Min.foldrAsc (f . unTaggedF) z q)

Misplaced where clause

The following input has where block positioned way off after indentation with indent step 2 and 80 columns.

Input:

foo :: a ->b->c
foo a b = g a b -- fooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo
 where
  g a b = b + b * a

Current output:

foo :: a -> b -> c
foo a b = g a b -- fooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo
                where g a b = b + b * a

I'd expect at least something like:

foo :: a -> b -> c
foo a b = g a b -- fooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo
  where g a b = b + b * a

Support (layouting) config inline/pragma-style

In some cases I noticed that per-file config is desirable, or even more fine-grained control ("leave this function/block alone" etc.)

This is mildly easy to implement, but I could use feedback regarding the interface design: What kind of pragma to use. I see the following options:

  1. Use real pragma

    {-# OPTIONS_BRITTANY --columns=80 #-}

    This pretends to be a real pragma, and ghc will promptly warn about it being unknown.
    Can be disabled, but its annoying and I dislike this option.

    Note that haddock uses these, due to haddock being wired into ghc, as I understand
    it.

  2. Use fake pragma

    {- # OPTIONS_BRITTANY --columns=80 # -}

    As I have gathered from the archives Haddock used this option earlier.

  3. Use ANN feature

    module .. where
    {-# ANN module "Brittany: --columns=80" #-}
    {-# ANN myFunction "Brittany: ignore" #-}

    This is a "proper" approach to annotating the whole module or single functions.
    While this option is closer to "standard" syntax for the purpose, it has some annoying
    downside: The above pragma can not be placed as freely as one might think (and the
    errors you get are rather confusing). For example, you cannot move it above the header
    ("module Foo where"), below any LANGUAGE pragmas.

  4. Use something based on raw comments, like

    {- BRITTANY --columns=80 -}
    -- BRITTANY --columns=80

Opinions/Arguments?

"Emergency" linebreaks can easily be syntactically invalid

foo = Reflex.runSpiderHost $ ReflexHost.hostApp $ do
  (inputEvent :: Reflex.Event Reflex.Spider String, inputFire :: String -> IO Bool)
    <- ReflexHost.newExternalEvent
  liftIO . forkIO . forever $ getLine >>= inputFire
  ReflexHost.performEvent_ $ fmap (liftIO . putStrLn) inputEvent

More graceful error handling

I've opened two issues today about GHC features that Brittany doesn't support. When encountered, Brittany will error. Would it be possible to handle these cases more gracefully? Perhaps by simply ignoring them and giving back the original source for that line / code block?

View Patterns

I've come to really like view patterns, but Brittany won't even try to format a file with them. I imagine this shouldn't be too difficult, since view patterns are necessarily contained within parentheses.

publish on Hackage

ToDos:

  • publish butcher on hackage;
  • publish data-tree-print on hackage;
  • publish czipwith on hackage and use it for config (replace local CZip);
  • consider replacing lens with some micro variant remove lens dependency;
  • add bounds for all deps;
  • fill metadata (synopsis, description, copyright etc.)
  • update changelog
  • choose/add license
  • prepare announcement

Instance methods don't seem to be formatted

data Test = Test

instance Show Test where
  show Test = "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test" ++ "Test"

Doesn't seem to be reformatted at all.

Stylish-haskell style import and record formatting

Stylish-haskell and Brittany usually get along fine. But there are rare occasions where they disagree (case statements with guards are the only one I know of). So if the user wants the features of both, they have to give precedence to one of the tools.

I personally only use stylish-haskell because of the formatting of imports and of record types. If Brittany did these things, I would just drop stylish-haskell altogether.

(PS: Sorry for bombarding you with 4 issues today =P I've been using Brittany for a little while now, and I'm starting to want to make some changes / fixes, so I'm documenting them in the form of issues. We'll see if I have the time to get to any of them myself.)

Option to value consistent layouting over minimal line count

data General =
  General
    { suspended    :: Maybe UTCTime
   , text1 :: Text
     , text2 :: Text
    , word :: Word
    }

e.g. hindent make it like:

data General = General
  { suspended :: Maybe UTCTime
  , text1 :: Text
  , text2 :: Text
  , word :: Word
  }

and stylish-haskell only:

data General =
  General
    { suspended :: Maybe UTCTime
   , text1      :: Text
     , text2    :: Text
    , word      :: Word
    }

But brittany just do nothing unless boilerplate take more than 80 chars in string.

Undesired(?) extra spacing around a '.' in a type signature

Should this space be added? It's not a style I think I've seen before.

runTest
  :: Predicate a
   -- ^ The predicate to check
-  -> (forall t. ConcST t a)
+  -> (forall t . ConcST t a)
   -- ^ The computation to test
   -> Result a
runTest test conc = runST (runTestM test conc)

Internal refactoring: Use "trees that grow" for BriDoc

See Trees that Grow paper by Najd, Jones.

This approach can merge BriDocFInt and BriDoc without adding any by adding minimal (source-text) overhead in any functions that use these types. (There will be some overhead in the representation of BriDoc nodes, but I don't think that general performance will suffer much.)

Unfortunately syb/uniplate are not very compatible with this approach, as far as I can see. E.g. we would not be able to use uniplate in its current form to express a transformation BriDoc StageOne -> BriDoc StageTwo. This is rather sad, as it would have allowed us to restrict which constructors exist in which stages, so we could statically ensure things instead of having ugly stuff such as BDAlt{} -> error "briDocLineLength BDAlt" around (see Backend.hs).

Aditional configuration request

I'm trying out brittany and really like it, I think it has the potential to beat hindent through configuration capabilities; The latest hindent version completely removes the styles mechanism and is fixed to the "Johan Tibell" one with no more configuration other than indentation size and line length, Johan Tibell's style is pretty good but I'm not always necessarily happy with every way it changes the code.

As I try brittany I found out a couple things that bothers me and that I would like to be able to configure on ~/.brittany/config.yaml. Not to say that the default behavior is bad though:

Guards

Have/Want:

isValidPosition :: Position -> Maybe Position
isValidPosition position
    | validX && validY = Just position
    | otherwise = Nothing

Get:

isValidPosition :: Position -> Maybe Position
isValidPosition position
    | validX && validY
    = Just position
    | otherwise
    = Nothing

Case

Have/Want:

dropTile :: Board -> Position -> Board
dropTile board position =
    case cell of
        Just (Tile _) -> board'
        _ -> board

Get:

dropTile :: Board -> Position -> Board
dropTile board position = case cell of
    Just (Tile _) -> board'
    _ -> board

non-idempotency with comments inside monad/listcomps

func =
  [ abc x y
  | _ <- aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
         -- comment
  , x <- bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb
  , y <- ccccccccccccccccccccccccccccccccccc
  ]

Each roundtrip through brittany will decrease the indentation of the comment.

Currently I cannot think of an easy fix on brittany's end for this because the ghc-exactprint interface is a bit unfortunate for this usecase. I have raised alanz/ghc-exactprint#53.

Improve performance - low hanging stuff?

Even with the fix for the quadratic performance issue, brittany easily takes in the magnitude of seconds on large (1k+ loc) inputs. I think there is room for improvement.

Testing on a 1800loc module, I see the following stats:

+RTS -s output:

   3,307,514,304 bytes allocated in the heap
   1,105,201,976 bytes copied during GC
     124,529,352 bytes maximum residency (18 sample(s))
         513,336 bytes maximum slop
             295 MB total memory in use (0 MB lost due to fragmentation)

                                     Tot time (elapsed)  Avg pause  Max pause
  Gen  0      3041 colls,     0 par    1.480s   1.479s     0.0005s    0.1567s
  Gen  1        18 colls,     0 par    0.003s   0.008s     0.0005s    0.0015s

  INIT    time    0.000s  (  0.000s elapsed)
  MUT     time    3.097s  (  3.268s elapsed)
  GC      time    1.483s  (  1.488s elapsed)
  RP      time    0.000s  (  0.000s elapsed)
  PROF    time    0.000s  (  0.000s elapsed)
  EXIT    time    0.003s  (  0.013s elapsed)
  Total   time    4.583s  (  4.769s elapsed)

  %GC     time      32.4%  (31.2% elapsed)

  Alloc rate    1,068,089,845 bytes per MUT second

  Productivity  67.6% of total user, 68.8% of total elapsed

Max residency is a bit high, but productivity still looks fine. Looking at the prof output:


	total time  =        3.17 secs   (3165 ticks @ 1000 us, 1 processor)
	total alloc = 1,929,655,872 bytes  (excludes profiling overheads)

COST CENTRE                       MODULE                                             SRC                                                                         %time %alloc

filterAnns                        Language.Haskell.Brittany.Internal.LayouterBasics  src/Language/Haskell/Brittany/Internal/LayouterBasics.hs:(229,1)-(230,67)    23.3    0.3
everything                        Data.Generics.Schemes                              src/Data/Generics/Schemes.hs:104:1-59                                        16.0   24.1
censor                            Control.Monad.Writer.Class                         Control/Monad/Writer/Class.hs:(99,1)-(101,17)                                13.9   19.9
runMemoStateT                     Control.Monad.Trans.Memo.State                     Control/Monad/Trans/Memo/State.hs:(56,1)-(58,23)                              9.9   12.4
iterTM                            Control.Monad.Trans.Free                           src/Control/Monad/Trans/Free.hs:(317,1)-(321,21)                              3.3    5.3
<&>                               Language.Haskell.Brittany.Internal.PreludeUtils    src/Language/Haskell/Brittany/Internal/PreludeUtils.hs:61:1-17                3.2    2.6
parseModuleApiAnnsWithCppInternal Language.Haskell.GHC.ExactPrint.Parsers            src/Language/Haskell/GHC/ExactPrint/Parsers.hs:(232,1)-(252,58)               3.0    4.1
…

filterAnns still is high up - probably via hasAnyCommentsBelow. I think that part can definitely be improved. For a different input (with 1000 one-line type-sig + one-line function) it looks like:

	total time  =        1.49 secs   (1493 ticks @ 1000 us, 1 processor)
	total alloc = 999,113,800 bytes  (excludes profiling overheads)

COST CENTRE                       MODULE                                             SRC                                                                         %time %alloc

everything                        Data.Generics.Schemes                              src/Data/Generics/Schemes.hs:104:1-59                                        18.6   21.9
runMemoStateT                     Control.Monad.Trans.Memo.State                     Control/Monad/Trans/Memo/State.hs:(56,1)-(58,23)                             15.3   13.5
censor                            Control.Monad.Writer.Class                         Control/Monad/Writer/Class.hs:(99,1)-(101,17)                                14.7   16.8
layoutBriDocM                     Language.Haskell.Brittany.Internal.Backend         src/Language/Haskell/Brittany/Internal/Backend.hs:(75,1)-(258,20)             3.9    2.8
parseModuleApiAnnsWithCppInternal Language.Haskell.GHC.ExactPrint.Parsers            src/Language/Haskell/GHC/ExactPrint/Parsers.hs:(232,1)-(252,58)               3.1    4.1
…

We use monad-memo in the most basic way, but unfortunately the interface of that package does not allow us to switch to a more efficient backend (e.g. vector-based) easily, afaict. And if we start refactoring, we may as well run our own memoization and remove the monad-memo dep (see #2).

censor is called via ghc-exactprint, so I suspect out of scope. Still might be worth investigating that one at some point.

Also, parallelization - the top-level module elements can be processed independently. I don't like fighting for constant factors before I have to, but then it could be relatively easy here.

support for consistent braces-plus-semicolon-style

e.g. see this nice example (shortened):

module Data.Graph.Inductive.Graphviz
       (Orient(..), graphviz, graphviz') where
{ import Data.Graph.Inductive.Graph;
   
  data Orient = Portrait
              | Landscape
              deriving (Eq, Show);
   
  graphviz ::
           (Graph g, Show a, Show b) =>
             g a b ->
               String -> (Double, Double) -> (Int, Int) -> Orient -> String;
  graphviz g t (w, h) p@(pw', ph') o
    = let { n = labNodes g;
            e = labEdges g}
        in
        "digraph " ++ t ++ " {\n" ++ "\tmargin = \"0\"\n" ++ "\tpage = \""}

haskell-ide-engine integration

Just an idea, would be cool if there was a haskell-ide-engine plugin for this. That way, all the editors integrating with hie could benefit from this project.

Consider adding `--inplace` option

Usage:

brittany --inplace **/*.hs

And since input files can already be specified as positional arguments, the -i parameter could be reassigned as shortcut for --inplace...

(My current workaround: ls **/*.hs | xargs -I{} brittany -i {} -o {})

Brittany can't cope with `-XTupleSections`

Config:


conf_forward:
  options_ghc:
    - -XLambdaCase
    - -XMultiWayIf
    - -XGADTs
    - -XPatternGuards
    - -XViewPatterns
    - -XRecursiveDo
    - -XTupleSections
    - -XExplicitForAll
    - -XImplicitParams
    - -XQuasiQuotes
    - -XTemplateHaskell
    - -XBangPatterns

Input:

foo = fmap (, ())

Error:

ERROR: encountered unknown syntactical constructs:
ExplicitTuple|..

Add a short help flag

The first thing I tried to do with brittany was brittany -h :)

$ brittany -h
-h: openBinaryFile: does not exist (No such file or directory)

Alignment of <-s is really aggressive

When aligning things by hand, I usually decide not to if it would introduce "too much" spacing (where "too much" is some fuzzy thing based on gut feeling).

This is definitely too much:

   (finalCtx, trace, finalAction) <- runThreads sched memtype ref ctx
-  out <- readRef ref
+  out                            <- readRef ref

Perhaps there could be a configurable maximum number of spaces, with alignment not done if it would introduce more than that many?

How to make brittany format data declarations?

I'm thinking of what it would take to make brittany format data declarations as well. I've looked at the high-level descriptions and have skimmed the source code.

The source code is a bit difficult to navigate since I don't know which files or directories have what function. There also don't seem to be comments indicating which file / function / case branch relates to what kind of language elements.

My first attempt at extending brittany would be to copy-past some existing code, re-using e.g. let or case expressions to format data statements, and making this work in simple cases. The errors and misfortunes I'd encounter would help me learn more about brittany, in the best traditions of cargo-cult programming. Would this stand some chance of success?

Turn off all context sensitive alignment in Brittany.

Hey @lspitzner, I think brittany is a fantastic project, but I'm having trouble getting it to behave the way I'd like. I was able to disable most context sensitive alignment, but I can't seem to rid the world of it. My config is:

conf_debug:
  dconf_dump_bridoc_simpl_par: false
  dconf_dump_ast_unknown: false
  dconf_dump_bridoc_simpl_floating: false
  dconf_dump_config: false
  dconf_dump_bridoc_raw: false
  dconf_dump_bridoc_final: false
  dconf_dump_bridoc_simpl_alt: false
  dconf_dump_bridoc_simpl_indent: false
  dconf_dump_annotations: false
  dconf_dump_bridoc_simpl_columns: false
  dconf_dump_ast_full: false
conf_forward:
  options_ghc: []
conf_errorHandling:
  econf_ExactPrintFallback: ExactPrintFallbackModeInline
  econf_Werror: false
  econf_omit_output_valid_check: false
  econf_CPPMode: CPPModeAbort
  econf_produceOutputOnErrors: false
conf_layout:
  lconfig_altChooser:
    tag: AltChooserBoundedSearch
    contents: 3
  lconfig_importColumn: 60
  lconfig_alignmentLimit: 1
  lconfig_indentListSpecial: true
  lconfig_indentAmount: 2
  lconfig_alignmentBreakOnMultiline: false
  lconfig_cols: 120
  lconfig_indentPolicy: IndentPolicyLeft
  lconfig_indentWhereSpecial: true
  lconfig_columnAlignMode:
    tag: ColumnAlignModeDisabled
    contents: []

But I still get code like this:

+    socialStudiesReadingAssignmentSessions <- getEntities socialStudiesProducts
+                                                          SocialStudiesProductReading
+                                                          getSocialStudiesReadingAssignmentSessions
+    socialStudiesWritingAssignmentSessions <- getEntities socialStudiesProducts
+                                                          SocialStudiesProductWriting
+                                                          getSocialStudiesWritingAssignmentSessions

Is there any way to turn this off completely?

unnecessary newline insertion

isModuleInterpreted mod_summary = withSession $ \hsc_env ->
  case lookupUFM (hsc_HPT hsc_env) (ms_mod_name mod_summary) of
        Nothing       -> panic "missing linkable"
        Just mod_info -> return $ case hm_linkable mod_info of
          Nothing -> True
          Just linkable -> not (isObjectLinkable linkable)

per-project brittany.yaml

It's a feature request: let brittany look up to parent directories until find configuration file to let customize it per-project.

Format region

It'd be great if you could ask Brittany to format only a region of a file. I often only want to format one function or something like that without touching the rest of the file. Currently this requires you supply the list of extensions you need, even though they're right at the top of the file. It'd be better if Brittany saw the whole file, but only attempted to format the smallest subtree that fully encompasses a specified region.

unprocessed comments in tuples

foo =
  ( a
  , -- comment1
    b
    -- comment2
  , c
  )
> clipread | brittany
Error: detected unprocessed comments. The transformation output will most likely not contain certain of the comments present in the input haskell source file.
Affected are the following comments:
(Comment "-- comment1" stdin:3:5-15 Nothing)
(Comment "-- comment2" stdin:5:5-15 Nothing)

Nonoptimal layouting in complex expression with default config

This sample code:

ugebe gdac _ekaz (NtizUbq sysn cekoed gagwwau, FdrnAqsAmnu njiuZqanacpoYbx) =
  M.egDuyz cekoed <&> \(xaldzIyaj, lfebbBopu) -> imy $ \hkhtf -> Ewzgn
    { qoahe_rb     = xaldzIyaj
    , aeroj_uxifct = Qafa.vnij "NtizUbq"
    , quzou_tgalzq = BDvkjte.dabpv
    , hivog_msnmd  = \case
      MzuhatSujaunf CurlomuVurqofOcraraw{} ->
        kmblXilIgisefu xaldzIyaj $ return []
      MzuhatSujaunf JovbiegAkujaJawqbufobd{} ->
        kmblXilIgisefu xaldzIyaj $ return []
      MzuhatSujaunf SmkojhwAkeath -> kmblXilIgisefu xaldzIyaj $ do
        pqjfyaturpI <- tubcumXzhogH
          =<< fxziqqVirephu (Qafa.vnij "vhincupedamiji")
        pure $ M.egDuyz gagwwau <&> \(iungeRyrr, lcotQjs) ->
          OJaufn iungeRyrr $ M.egDuyz lcotQjs <&> \(pAumcAweb, vdauyXuf) ->
            JItwocAfye pAumcAweb
              $   M.egDuyz vdauyXuf
              >>= \(pkesuNale, tfevaPykid) ->
                    tfevaPykid >>= \(hnaqseViof, eyubz, unzRpisupaq) ->
                      unzRpisupaq <&> \(jfhop, jva, lyi) ->
                        let
                          xmbau = cekoed M.! hnaqseViof
                          kauvx = S.tmolOobf $ case xmbau of
                            SQBokknXqazk (FUIghuGuodo _ kauvx) ->
                              [ WIwuv porp nnehajNovin []
                              | (s, e, _, _) <- kauvx
                              , let f'     = sdfmenaLodi pqjfyaturpI s
                              , let g'     = sdfmenaLodi pqjfyaturpI e
                              , let uwamm' = sdfmenaLodi pqjfyaturpI jfhop
                              , let xde'   = sdfmenaLodi pqjfyaturpI jva
                              , let nnehajNovin =
                                      yvpKwgiaQbeyxtmv $ g' `amoOB` f'
                              , uwamm' <= f'
                              , f' <= xde'
                              ]
                            UMOyumoTumoibAsvqp{} -> []
                        in
                          PYifebdruthMjob (Fsnu pkesuNale)
                                          eyubz
                                          (QEvavFipiv lyi kauvx)
    }

requires config

  lconfig_altChooser:
    tag: AltChooserBoundedSearch
    contents: 5

with the default of 3 (instead of 5) brittany reformats the above to the non-optimal:

ugebe gdac _ekaz (NtizUbq sysn cekoed gagwwau, FdrnAqsAmnu njiuZqanacpoYbx) =
  M.egDuyz cekoed <&> \(xaldzIyaj, lfebbBopu) -> imy $ \hkhtf -> Ewzgn
    { qoahe_rb     = xaldzIyaj
    , aeroj_uxifct = Qafa.vnij "NtizUbq"
    , quzou_tgalzq = BDvkjte.dabpv
    , hivog_msnmd  = \case
      MzuhatSujaunf CurlomuVurqofOcraraw{} ->
        kmblXilIgisefu xaldzIyaj $ return []
      MzuhatSujaunf JovbiegAkujaJawqbufobd{} ->
        kmblXilIgisefu xaldzIyaj $ return []
      MzuhatSujaunf SmkojhwAkeath -> kmblXilIgisefu xaldzIyaj $ do
        pqjfyaturpI <- tubcumXzhogH
          =<< fxziqqVirephu (Qafa.vnij "vhincupedamiji")
        pure $ M.egDuyz gagwwau <&> \(iungeRyrr, lcotQjs) ->
          OJaufn iungeRyrr $ M.egDuyz lcotQjs <&> \(pAumcAweb, vdauyXuf) ->
            JItwocAfye pAumcAweb
              $   M.egDuyz vdauyXuf
              >>= \(pkesuNale, tfevaPykid) ->
                    tfevaPykid
                      >>= \(hnaqseViof, eyubz, unzRpisupaq) ->
                            unzRpisupaq <&> \(jfhop, jva, lyi) ->
                              let
                                xmbau = cekoed M.! hnaqseViof
                                kauvx = S.tmolOobf $ case xmbau of
                                  SQBokknXqazk (FUIghuGuodo _ kauvx) ->
                                    [ WIwuv porp nnehajNovin []
                                    | (s, e, _, _) <- kauvx
                                    , let f' = sdfmenaLodi pqjfyaturpI s
                                    , let g' = sdfmenaLodi pqjfyaturpI e
                                    , let uwamm' =
                                            sdfmenaLodi pqjfyaturpI jfhop
                                    , let xde' = sdfmenaLodi pqjfyaturpI jva
                                    , let nnehajNovin =
                                            yvpKwgiaQbeyxtmv $ g' `amoOB` f'
                                    , uwamm' <= f'
                                    , f' <= xde'
                                    ]
                                  UMOyumoTumoibAsvqp{} -> []
                              in
                                PYifebdruthMjob (Fsnu pkesuNale)
                                                eyubz
                                                (QEvavFipiv lyi kauvx)
    }

I cannot spot any particular bug in the layouting code here and it is certainly possible that pruning to 5 instead of 3 is necessary for examples of certain complexity.

Maybe the default config should be changed? Relevant questions:

  • How big is the impact on performance for some average brittany usage when reducing the "pruning-agressiveness" from 3 to 5?
  • How often are these non-optimal cases encountered?
  • Why don't we just use a list-comprehension there? It avoids tons of nesting.. (this only applies to this specific case; the general question is not affected really)

Some weird preceding printing occurring

Simple test case:

-- Test.hs
module Test where

data X = X

Output:

$ brittany Test.hs
["","","data X = X"]
-- Test.hs
module Test where

data X = X

Not sure what that's about...

Type applications

Birttany does not currently support GHC 8's new TypeApplications.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.