summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorSean Whitton <spwhitton@spwhitton.name>2017-11-17 13:46:35 -0700
committerSean Whitton <spwhitton@spwhitton.name>2017-11-17 13:46:35 -0700
commit20bd09d3cd6f46d34979eb8433831993d2b9352b (patch)
tree7385df9ea619b3087b641a390f40ee9d1ac8bece
parentc510f1f377bc3cd454c7d16841e7f0d1e82c4c55 (diff)
parentdc3a73e82c19ff97a1544840dac8f7f4568b24bc (diff)
downloadstylish-haskell-20bd09d3cd6f46d34979eb8433831993d2b9352b.tar.gz
Merge tag '0.8.1.0'
0.8.1.0
-rw-r--r--CHANGELOG19
-rw-r--r--README.markdown64
-rw-r--r--data/stylish-haskell.yaml43
-rw-r--r--doc/release.md28
-rw-r--r--lib/Language/Haskell/Stylish/Config.hs4
-rw-r--r--lib/Language/Haskell/Stylish/Parse.hs1
-rw-r--r--lib/Language/Haskell/Stylish/Step/Imports.hs144
-rw-r--r--lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs2
-rw-r--r--stack.yaml6
-rw-r--r--stylish-haskell.cabal18
-rw-r--r--tests/Language/Haskell/Stylish/Parse/Tests.hs6
-rw-r--r--tests/Language/Haskell/Stylish/Step/Imports/Tests.hs162
-rw-r--r--tests/Language/Haskell/Stylish/Step/LanguagePragmas/Tests.hs30
13 files changed, 441 insertions, 86 deletions
diff --git a/CHANGELOG b/CHANGELOG
index 0d4d986..5a550bd 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -1,5 +1,24 @@
# CHANGELOG
+- 0.8.1.0 (2017-06-19)
+ * Add `pad_module_names` option (by Yuriy Syrovetskiy)
+ * Add `space_surround` option to import styling (by Linus Arver)
+ * Bump `optparse-applicative` to 0.14
+
+- 0.8.0.0
+ * Remove `MagicHash` from whitelisted language extensions, since it was
+ causing parsing errors (by Artyom Kazak)
+ * Don't leave a `#-}` hanging on the next line when `language_pragmas`
+ is set to `compact` and the `#-}` doesn't fit into character limit
+ (by Artyom Kazak)
+ * Deduplicate import specs (i.e. `import Foo (a, a, b)` becomes
+ `import Foo (a, b)`) (by Artyom Kazak)
+ * Take package imports into account when prettifying imports
+ (by Artyom Kazak)
+ * Bump `aeson` to 1.2
+ * Bump `syb` to 0.7
+ * Bump `HUnit` to 1.6
+
- 0.7.1.0
* Keep `safe` and `{-# SOURCE #-}` import annotations (by Moritz Drexl)
diff --git a/README.markdown b/README.markdown
index d271b4c..335d8c6 100644
--- a/README.markdown
+++ b/README.markdown
@@ -17,6 +17,8 @@ Features
- Groups and wraps `{-# LANGUAGE #-}` pragmas, can remove (some) redundant
pragmas
- Removes trailing whitespace
+- Aligns branches in `case` and fields in records
+- Converts line endings (customizable)
- Replaces tabs by four spaces (turned off by default)
- Replaces some ASCII sequences by their Unicode equivalents (turned off by
default)
@@ -30,43 +32,46 @@ Example
Turns:
- {-# LANGUAGE ViewPatterns, TemplateHaskell #-}
- {-# LANGUAGE GeneralizedNewtypeDeriving,
- ViewPatterns,
- ScopedTypeVariables #-}
+```haskell
+{-# LANGUAGE ViewPatterns, TemplateHaskell #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving,
+ ViewPatterns,
+ ScopedTypeVariables #-}
- module Bad where
+module Bad where
- import Control.Applicative ((<$>))
- import System.Directory (doesFileExist)
+import Control.Applicative ((<$>))
+import System.Directory (doesFileExist)
- import qualified Data.Map as M
- import Data.Map ((!), keys, Map)
+import qualified Data.Map as M
+import Data.Map ((!), keys, Map)
- data Point = Point
- { pointX, pointY :: Double
- , pointName :: String
- } deriving (Show)
+data Point = Point
+ { pointX, pointY :: Double
+ , pointName :: String
+ } deriving (Show)
+```
into:
- {-# LANGUAGE GeneralizedNewtypeDeriving #-}
- {-# LANGUAGE ScopedTypeVariables #-}
- {-# LANGUAGE TemplateHaskell #-}
+```haskell
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TemplateHaskell #-}
- module Bad where
+module Bad where
- import Control.Applicative ((<$>))
- import System.Directory (doesFileExist)
+import Control.Applicative ((<$>))
+import System.Directory (doesFileExist)
- import Data.Map (Map, keys, (!))
- import qualified Data.Map as M
-
- data Point = Point
- { pointX, pointY :: Double
- , pointName :: String
- } deriving (Show)
+import Data.Map (Map, keys, (!))
+import qualified Data.Map as M
+data Point = Point
+ { pointX, pointY :: Double
+ , pointName :: String
+ } deriving (Show)
+```
Configuration
-------------
@@ -111,11 +116,12 @@ automatically when you save a Haskell file.
Emacs integration
-----------------
-[haskell-mode] for Emacs supports `stylish-haskell`. For configuration, see
-[Emacs/Formatting] on the HaskellWiki.
+[haskell-mode] for Emacs supports `stylish-haskell`. For configuration,
+see [the “Using external formatters” section][haskell-mode/format] of the
+haskell-mode manual.
[haskell-mode]: https://github.com/haskell/haskell-mode
-[Emacs/Formatting]: http://wiki.haskell.org/Emacs/Formatting
+[haskell-mode/format]: http://haskell.github.io/haskell-mode/manual/latest/Autoformating.html
Atom integration
----------------
diff --git a/data/stylish-haskell.yaml b/data/stylish-haskell.yaml
index 3bed473..10301be 100644
--- a/data/stylish-haskell.yaml
+++ b/data/stylish-haskell.yaml
@@ -41,7 +41,7 @@ steps:
# Default: global.
align: global
- # Folowing options affect only import list alignment.
+ # The following options affect only import list alignment.
#
# List align has following options:
#
@@ -64,6 +64,25 @@ steps:
# Default: after_alias
list_align: after_alias
+ # Right-pad the module names to align imports in a group:
+ #
+ # - true: a little more readable
+ #
+ # > import qualified Data.List as List (concat, foldl, foldr,
+ # > init, last, length)
+ # > import qualified Data.List.Extra as List (concat, foldl, foldr,
+ # > init, last, length)
+ #
+ # - false: diff-safe
+ #
+ # > import qualified Data.List as List (concat, foldl, foldr, init,
+ # > last, length)
+ # > import qualified Data.List.Extra as List (concat, foldl, foldr,
+ # > init, last, length)
+ #
+ # Default: true
+ pad_module_names: true
+
# Long list align style takes effect when import is too long. This is
# determined by 'columns' setting.
#
@@ -75,7 +94,7 @@ steps:
# short enough to fit to single line. Otherwise it'll be multiline.
#
# - multiline: One line per import list entry.
- # Type with contructor list acts like single import.
+ # Type with constructor list acts like single import.
#
# > import qualified Data.Map as M
# > ( empty
@@ -109,7 +128,7 @@ steps:
# Useful for 'file' and 'group' align settings.
list_padding: 4
- # Separate lists option affects formating of import list for type
+ # Separate lists option affects formatting of import list for type
# or class. The only difference is single space between type and list
# of constructors, selectors and class functions.
#
@@ -126,6 +145,22 @@ steps:
# Default: true
separate_lists: true
+ # Space surround option affects formatting of import lists on a single
+ # line. The only difference is single space after the initial
+ # parenthesis and a single space before the terminal parenthesis.
+ #
+ # - true: There is single space associated with the enclosing
+ # parenthesis.
+ #
+ # > import Data.Foo ( foo )
+ #
+ # - false: There is no space associated with the enclosing parenthesis
+ #
+ # > import Data.Foo (foo)
+ #
+ # Default: false
+ space_surround: false
+
# Language pragmas
- language_pragmas:
# We can generate different styles of language pragma lists.
@@ -142,7 +177,7 @@ steps:
# Align affects alignment of closing pragma brackets.
#
- # - true: Brackets are aligned in same collumn.
+ # - true: Brackets are aligned in same column.
#
# - false: Brackets are not aligned together. There is only one space
# between actual import and closing bracket.
diff --git a/doc/release.md b/doc/release.md
new file mode 100644
index 0000000..3c010f8
--- /dev/null
+++ b/doc/release.md
@@ -0,0 +1,28 @@
+# Release checklist
+
+1. First check if we can build against against all the newest dependencies. If
+ that's not the case, it's probably a good idea to first make a separate
+ commit to bump the dependency upper bounds (and test it).
+
+2. Write up the `CHANGELOG`. You can inspect the log of what changed by doing
+ something like:
+
+ git log A.B.C.D..
+
+ Where `A.B.C.D` is the old version.
+
+3. Now figure out whether this is a minor or major version bump. Follow the
+ [PVP](https://pvp.haskell.org/) guidelines. Assume the new version is
+ `E.F.G.H`.
+
+4. Create a commit with the message `Bump version to E.F.G.H`. This commit
+ should only change two things:
+
+ - The version number in the `.cabal` file
+ - The top of the `CHANGELOG`
+
+4. Create a tarball using `cabal sdist` and upload this to Hackage. If the
+ upload succeeds, create an annotated git tag:
+
+ git tag -am E.F.G.H{,}
+ git push --tags
diff --git a/lib/Language/Haskell/Stylish/Config.hs b/lib/Language/Haskell/Stylish/Config.hs
index b83cf3a..9fddbb5 100644
--- a/lib/Language/Haskell/Stylish/Config.hs
+++ b/lib/Language/Haskell/Stylish/Config.hs
@@ -184,13 +184,15 @@ parseImports config o = Imports.step
<*> (Imports.Options
<$> (o A..:? "align" >>= parseEnum aligns (def Imports.importAlign))
<*> (o A..:? "list_align" >>= parseEnum listAligns (def Imports.listAlign))
+ <*> (o A..:? "pad_module_names" A..!= def Imports.padModuleNames)
<*> (o A..:? "long_list_align"
>>= parseEnum longListAligns (def Imports.longListAlign))
-- Note that padding has to be at least 1. Default is 4.
<*> (o A..:? "empty_list_align"
>>= parseEnum emptyListAligns (def Imports.emptyListAlign))
<*> o A..:? "list_padding" A..!= (def Imports.listPadding)
- <*> o A..:? "separate_lists" A..!= (def Imports.separateLists))
+ <*> o A..:? "separate_lists" A..!= (def Imports.separateLists)
+ <*> o A..:? "space_surround" A..!= (def Imports.spaceSurround))
where
def f = f Imports.defaultOptions
diff --git a/lib/Language/Haskell/Stylish/Parse.hs b/lib/Language/Haskell/Stylish/Parse.hs
index 596bccb..724ebe2 100644
--- a/lib/Language/Haskell/Stylish/Parse.hs
+++ b/lib/Language/Haskell/Stylish/Parse.hs
@@ -24,7 +24,6 @@ defaultExtensions = map H.EnableExtension
[ H.GADTs
, H.HereDocuments
, H.KindSignatures
- , H.MagicHash
, H.NewQualifiedOperators
, H.PatternGuards
, H.StandaloneDeriving
diff --git a/lib/Language/Haskell/Stylish/Step/Imports.hs b/lib/Language/Haskell/Stylish/Step/Imports.hs
index 29b8cc2..2284f3d 100644
--- a/lib/Language/Haskell/Stylish/Step/Imports.hs
+++ b/lib/Language/Haskell/Stylish/Step/Imports.hs
@@ -1,5 +1,5 @@
-{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
--------------------------------------------------------------------------------
module Language.Haskell.Stylish.Step.Imports
( Options (..)
@@ -16,13 +16,16 @@ module Language.Haskell.Stylish.Step.Imports
--------------------------------------------------------------------------------
import Control.Arrow ((&&&))
import Control.Monad (void)
+import qualified Data.Aeson as A
+import qualified Data.Aeson.Types as A
import Data.Char (toLower)
import Data.List (intercalate, sortBy)
+import qualified Data.Map as M
import Data.Maybe (isJust, maybeToList)
+import Data.Monoid ((<>))
import Data.Ord (comparing)
+import qualified Data.Set as S
import qualified Language.Haskell.Exts as H
-import qualified Data.Aeson as A
-import qualified Data.Aeson.Types as A
--------------------------------------------------------------------------------
@@ -35,20 +38,24 @@ import Language.Haskell.Stylish.Util
data Options = Options
{ importAlign :: ImportAlign
, listAlign :: ListAlign
+ , padModuleNames :: Bool
, longListAlign :: LongListAlign
, emptyListAlign :: EmptyListAlign
, listPadding :: ListPadding
, separateLists :: Bool
+ , spaceSurround :: Bool
} deriving (Eq, Show)
defaultOptions :: Options
defaultOptions = Options
{ importAlign = Global
, listAlign = AfterAlias
+ , padModuleNames = True
, longListAlign = Inline
, emptyListAlign = Inherit
, listPadding = LPConstant 4
, separateLists = True
+ , spaceSurround = False
}
data ListPadding
@@ -81,6 +88,16 @@ data LongListAlign
| Multiline
deriving (Eq, Show)
+
+--------------------------------------------------------------------------------
+
+modifyImportSpecs :: ([H.ImportSpec l] -> [H.ImportSpec l])
+ -> H.ImportDecl l -> H.ImportDecl l
+modifyImportSpecs f imp = imp {H.importSpecs = f' <$> H.importSpecs imp}
+ where
+ f' (H.ImportSpecList l h specs) = H.ImportSpecList l h (f specs)
+
+
--------------------------------------------------------------------------------
imports :: H.Module l -> [H.ImportDecl l]
imports (H.Module _ _ _ is _) = is
@@ -91,16 +108,94 @@ imports _ = []
importName :: H.ImportDecl l -> String
importName i = let (H.ModuleName _ n) = H.importModule i in n
+importPackage :: H.ImportDecl l -> Maybe String
+importPackage i = H.importPkg i
+
+
+--------------------------------------------------------------------------------
+-- | A "compound import name" is import's name and package (if present). For
+-- instance, if you have an import @Foo.Bar@ from package @foobar@, the full
+-- name will be @"foobar" Foo.Bar@.
+compoundImportName :: H.ImportDecl l -> String
+compoundImportName i =
+ case importPackage i of
+ Nothing -> importName i
+ Just pkg -> show pkg ++ " " ++ importName i
+
--------------------------------------------------------------------------------
longestImport :: [H.ImportDecl l] -> Int
-longestImport = maximum . map (length . importName)
+longestImport = maximum . map (length . compoundImportName)
--------------------------------------------------------------------------------
-- | Compare imports for ordering
compareImports :: H.ImportDecl l -> H.ImportDecl l -> Ordering
-compareImports = comparing (map toLower . importName &&& H.importQualified)
+compareImports =
+ comparing (map toLower . importName &&&
+ fmap (map toLower) . importPackage &&&
+ H.importQualified)
+
+
+--------------------------------------------------------------------------------
+-- | Remove (or merge) duplicated import specs.
+--
+-- * When something is mentioned twice, it's removed: @A, A@ -> A
+-- * More general forms take priority: @A, A(..)@ -> @A(..)@
+-- * Sometimes we have to combine imports: @A(x), A(y)@ -> @A(x, y)@
+--
+-- Import specs are always sorted by subsequent steps so we don't have to care
+-- about preserving order.
+deduplicateImportSpecs :: Ord l => H.ImportDecl l -> H.ImportDecl l
+deduplicateImportSpecs =
+ modifyImportSpecs $
+ map recomposeImportSpec .
+ M.toList . M.fromListWith (<>) .
+ map decomposeImportSpec
+
+-- | What we are importing (variable, class, etc)
+data ImportEntity l
+ -- | A variable
+ = ImportVar l (H.Name l)
+ -- | Something that can be imported partially
+ | ImportClassOrData l (H.Name l)
+ -- | Something else ('H.IAbs')
+ | ImportOther l (H.Namespace l) (H.Name l)
+ deriving (Eq, Ord)
+
+-- | What we are importing from an 'ImportClassOrData'
+data ImportPortion l
+ = ImportSome [H.CName l] -- ^ @A(x, y, z)@
+ | ImportAll -- ^ @A(..)@
+
+instance Ord l => Monoid (ImportPortion l) where
+ mempty = ImportSome []
+ mappend (ImportSome a) (ImportSome b) = ImportSome (setUnion a b)
+ mappend _ _ = ImportAll
+
+-- | O(n log n) union.
+setUnion :: Ord a => [a] -> [a] -> [a]
+setUnion a b = S.toList (S.fromList a `S.union` S.fromList b)
+
+decomposeImportSpec :: H.ImportSpec l -> (ImportEntity l, ImportPortion l)
+decomposeImportSpec x = case x of
+ -- I checked and it looks like namespace's 'l' is always equal to x's 'l'
+ H.IAbs l space n -> case space of
+ H.NoNamespace _ -> (ImportClassOrData l n, ImportSome [])
+ H.TypeNamespace _ -> (ImportOther l space n, ImportSome [])
+ H.PatternNamespace _ -> (ImportOther l space n, ImportSome [])
+ H.IVar l n -> (ImportVar l n, ImportSome [])
+ H.IThingAll l n -> (ImportClassOrData l n, ImportAll)
+ H.IThingWith l n names -> (ImportClassOrData l n, ImportSome names)
+
+recomposeImportSpec :: (ImportEntity l, ImportPortion l) -> H.ImportSpec l
+recomposeImportSpec (e, p) = case e of
+ ImportClassOrData l n -> case p of
+ ImportSome [] -> H.IAbs l (H.NoNamespace l) n
+ ImportSome names -> H.IThingWith l n names
+ ImportAll -> H.IThingAll l n
+ ImportVar l n -> H.IVar l n
+ ImportOther l space n -> H.IAbs l space n
--------------------------------------------------------------------------------
@@ -119,10 +214,7 @@ compareImportSpecs = comparing key
--------------------------------------------------------------------------------
-- | Sort the input spec list inside an 'H.ImportDecl'
sortImportSpecs :: H.ImportDecl l -> H.ImportDecl l
-sortImportSpecs imp = imp {H.importSpecs = sort' <$> H.importSpecs imp}
- where
- sort' (H.ImportSpecList l h specs) = H.ImportSpecList l h $
- sortBy compareImportSpecs specs
+sortImportSpecs = modifyImportSpecs (sortBy compareImportSpecs)
--------------------------------------------------------------------------------
@@ -186,27 +278,27 @@ prettyImport columns Options{..} padQualified padName longest imp
| otherwise = shortWrap
emptyWrap = case emptyListAlign of
- Inherit -> inlineWrap
+ Inherit -> inlineWrap
RightAfter -> [paddedNoSpecBase ++ " ()"]
inlineWrap = inlineWrapper
$ mapSpecs
$ withInit (++ ",")
- . withHead ("(" ++)
- . withLast (++ ")")
+ . withHead (("(" ++ maybeSpace) ++)
+ . withLast (++ (maybeSpace ++ ")"))
inlineWrapper = case listAlign of
NewLine -> (paddedNoSpecBase :) . wrapRest columns listPadding'
WithAlias -> wrap columns paddedBase (inlineBaseLength + 1)
-- Add 1 extra space to ensure same padding as in original code.
- AfterAlias -> withTail (' ' :)
+ AfterAlias -> withTail ((' ' : maybeSpace) ++)
. wrap columns paddedBase (afterAliasBaseLength + 1)
inlineWithBreakWrap = paddedNoSpecBase : wrapRest columns listPadding'
( mapSpecs
$ withInit (++ ",")
- . withHead ("(" ++)
- . withLast (++ ")"))
+ . withHead (("(" ++ maybeSpace) ++)
+ . withLast (++ (maybeSpace ++ ")")))
inlineToMultilineWrap
| length inlineWithBreakWrap > 2
@@ -221,9 +313,9 @@ prettyImport columns Options{..} padQualified padName longest imp
. withTail (", " ++))
++ [")"])
- paddedBase = base $ padImport $ importName imp
+ paddedBase = base $ padImport $ compoundImportName imp
- paddedNoSpecBase = base $ padImportNoSpec $ importName imp
+ paddedNoSpecBase = base $ padImportNoSpec $ compoundImportName imp
padImport = if hasExtras && padName
then padRight longest
@@ -233,12 +325,11 @@ prettyImport columns Options{..} padQualified padName longest imp
then padRight longest
else id
- base' baseName importAs hasHiding' = unwords $ concat $ filter (not . null)
+ base' baseName importAs hasHiding' = unwords $ concat $
[ ["import"]
, source
, safe
, qualified
- , show <$> maybeToList (H.importPkg imp)
, [baseName]
, importAs
, hasHiding'
@@ -248,9 +339,10 @@ prettyImport columns Options{..} padQualified padName longest imp
["as " ++ as | H.ModuleName _ as <- maybeToList $ H.importAs imp]
["hiding" | hasHiding]
- inlineBaseLength = length $ base' (padImport $ importName imp) [] []
+ inlineBaseLength = length $
+ base' (padImport $ compoundImportName imp) [] []
- afterAliasBaseLength = length $ base' (padImport $ importName imp)
+ afterAliasBaseLength = length $ base' (padImport $ compoundImportName imp)
["as " ++ as | H.ModuleName _ as <- maybeToList $ H.importAs imp] []
(hasHiding, importSpecs) = case H.importSpecs imp of
@@ -282,6 +374,10 @@ prettyImport columns Options{..} padQualified padName longest imp
Just [] -> ["()"] -- Instance only imports
Just is -> f $ map (prettyImportSpec separateLists) is
+ maybeSpace = case spaceSurround of
+ True -> " "
+ False -> ""
+
--------------------------------------------------------------------------------
prettyImportGroup :: Int -> Options -> Bool -> Int
@@ -292,12 +388,13 @@ prettyImportGroup columns align fileAlign longest imps =
sortBy compareImports imps
where
align' = importAlign align
+ padModuleNames' = padModuleNames align
longest' = case align' of
Group -> longestImport imps
_ -> longest
- padName = align' /= None
+ padName = align' /= None && padModuleNames'
padQual = case align' of
Global -> True
@@ -320,7 +417,8 @@ step' columns align ls (module', _) = applyChanges
]
ls
where
- imps = map sortImportSpecs $ imports $ fmap linesFromSrcSpan module'
+ imps = map (sortImportSpecs . deduplicateImportSpecs) $
+ imports $ fmap linesFromSrcSpan module'
longest = longestImport imps
groups = groupAdjacent [(H.ann i, i) | i <- imps]
diff --git a/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs b/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs
index c63d90a..cdedfa8 100644
--- a/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs
+++ b/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs
@@ -56,7 +56,7 @@ verticalPragmas longest align pragmas' =
--------------------------------------------------------------------------------
compactPragmas :: Int -> [String] -> Lines
compactPragmas columns pragmas' = wrap columns "{-# LANGUAGE" 13 $
- map (++ ",") (init pragmas') ++ [last pragmas', "#-}"]
+ map (++ ",") (init pragmas') ++ [last pragmas' ++ " #-}"]
--------------------------------------------------------------------------------
diff --git a/stack.yaml b/stack.yaml
index 8f26efa..ae1019c 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -2,8 +2,8 @@ flags: {}
packages:
- '.'
extra-deps:
-- 'haskell-src-exts-1.18.2'
-- 'optparse-applicative-0.13.0.0'
-resolver: lts-6.10
+- 'optparse-applicative-0.14.0.0'
+resolver: 'nightly-2017-06-19'
install-ghc: true
system-ghc: false
+allow-newer: true
diff --git a/stylish-haskell.cabal b/stylish-haskell.cabal
index e8e6bb7..aef50e4 100644
--- a/stylish-haskell.cabal
+++ b/stylish-haskell.cabal
@@ -1,5 +1,5 @@
Name: stylish-haskell
-Version: 0.7.1.0
+Version: 0.8.1.0
Synopsis: Haskell code prettifier
Homepage: https://github.com/jaspervdj/stylish-haskell
License: BSD3
@@ -49,7 +49,7 @@ Library
Paths_stylish_haskell
Build-depends:
- aeson >= 0.6 && < 1.2,
+ aeson >= 0.6 && < 1.3,
base >= 4.8 && < 5,
bytestring >= 0.9 && < 0.11,
containers >= 0.3 && < 0.6,
@@ -57,7 +57,7 @@ Library
filepath >= 1.1 && < 1.5,
haskell-src-exts >= 1.18 && < 1.20,
mtl >= 2.0 && < 2.3,
- syb >= 0.3 && < 0.7,
+ syb >= 0.3 && < 0.8,
yaml >= 0.7 && < 0.9
Executable stylish-haskell
@@ -68,9 +68,9 @@ Executable stylish-haskell
Build-depends:
stylish-haskell,
strict >= 0.3 && < 0.4,
- optparse-applicative >= 0.12 && < 0.14,
+ optparse-applicative >= 0.12 && < 0.15,
-- Copied from regular dependencies...
- aeson >= 0.6 && < 1.2,
+ aeson >= 0.6 && < 1.3,
base >= 4.8 && < 5,
bytestring >= 0.9 && < 0.11,
containers >= 0.3 && < 0.6,
@@ -78,7 +78,7 @@ Executable stylish-haskell
filepath >= 1.1 && < 1.5,
haskell-src-exts >= 1.18 && < 1.20,
mtl >= 2.0 && < 2.3,
- syb >= 0.3 && < 0.7,
+ syb >= 0.3 && < 0.8,
yaml >= 0.7 && < 0.9
Test-suite stylish-haskell-tests
@@ -112,11 +112,11 @@ Test-suite stylish-haskell-tests
Language.Haskell.Stylish.Verbose
Build-depends:
- HUnit >= 1.2 && < 1.6,
+ HUnit >= 1.2 && < 1.7,
test-framework >= 0.4 && < 0.9,
test-framework-hunit >= 0.2 && < 0.4,
-- Copied from regular dependencies...
- aeson >= 0.6 && < 1.2,
+ aeson >= 0.6 && < 1.3,
base >= 4.8 && < 5,
bytestring >= 0.9 && < 0.11,
containers >= 0.3 && < 0.6,
@@ -124,7 +124,7 @@ Test-suite stylish-haskell-tests
filepath >= 1.1 && < 1.5,
haskell-src-exts >= 1.18 && < 1.20,
mtl >= 2.0 && < 2.3,
- syb >= 0.3 && < 0.7,
+ syb >= 0.3 && < 0.8,
yaml >= 0.7 && < 0.9
Source-repository head
diff --git a/tests/Language/Haskell/Stylish/Parse/Tests.hs b/tests/Language/Haskell/Stylish/Parse/Tests.hs
index 3f2d4a7..9806be2 100644
--- a/tests/Language/Haskell/Stylish/Parse/Tests.hs
+++ b/tests/Language/Haskell/Stylish/Parse/Tests.hs
@@ -27,6 +27,7 @@ tests = testGroup "Language.Haskell.Stylish.Parse"
, testCase "StandalonDeriving extension" testStandaloneDeriving
, testCase "UnicodeSyntax extension" testUnicodeSyntax
, testCase "XmlSyntax regression" testXmlSyntaxRegression
+ , testCase "MagicHash regression" testMagicHashRegression
]
--------------------------------------------------------------------------------
@@ -120,6 +121,11 @@ testXmlSyntaxRegression = assert $ isRight $ parseModule [] Nothing $ unlines
[ "smaller a b = a <b"
]
+testMagicHashRegression :: Assertion
+testMagicHashRegression = assert $ isRight $ parseModule [] Nothing $ unlines
+ [ "xs = \"foo\"#|1#|'a'#|bar#|Nil"
+ ]
+
--------------------------------------------------------------------------------
isRight :: Either a b -> Bool
isRight (Right _) = True
diff --git a/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs b/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
index c3178ac..bc6772c 100644
--- a/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
+++ b/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
@@ -47,6 +47,11 @@ tests = testGroup "Language.Haskell.Stylish.Step.Imports.Tests"
, testCase "case 19d" case19c
, testCase "case 19d" case19d
, testCase "case 20" case20
+ , testCase "case 21" case21
+ , testCase "case 22" case22
+ , testCase "case 23" case23
+ , testCase "case 24" case24
+ , testCase "case 25" case25
]
@@ -186,7 +191,7 @@ case07 = expected @=? testStep (step 80 $ fromImportAlign File) input'
--------------------------------------------------------------------------------
case08 :: Assertion
case08 = expected
- @=? testStep (step 80 $ Options Global WithAlias Inline Inherit (LPConstant 4) True) input
+ @=? testStep (step 80 $ Options Global WithAlias True Inline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -209,7 +214,7 @@ case08 = expected
--------------------------------------------------------------------------------
case09 :: Assertion
case09 = expected
- @=? testStep (step 80 $ Options Global WithAlias Multiline Inherit (LPConstant 4) True) input
+ @=? testStep (step 80 $ Options Global WithAlias True Multiline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -243,7 +248,7 @@ case09 = expected
--------------------------------------------------------------------------------
case10 :: Assertion
case10 = expected
- @=? testStep (step 40 $ Options Group WithAlias Multiline Inherit (LPConstant 4) True) input
+ @=? testStep (step 40 $ Options Group WithAlias True Multiline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -282,7 +287,7 @@ case10 = expected
--------------------------------------------------------------------------------
case11 :: Assertion
case11 = expected
- @=? testStep (step 80 $ Options Group NewLine Inline Inherit (LPConstant 4) True) input
+ @=? testStep (step 80 $ Options Group NewLine True Inline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -310,7 +315,7 @@ case11 = expected
--------------------------------------------------------------------------------
case12 :: Assertion
case12 = expected
- @=? testStep (step 80 $ Options Group NewLine Inline Inherit (LPConstant 2) True) input'
+ @=? testStep (step 80 $ Options Group NewLine True Inline Inherit (LPConstant 2) True False) input'
where
input' = unlines
[ "import Data.List (map)"
@@ -325,7 +330,7 @@ case12 = expected
--------------------------------------------------------------------------------
case13 :: Assertion
case13 = expected
- @=? testStep (step 80 $ Options None WithAlias InlineWithBreak Inherit (LPConstant 4) True) input'
+ @=? testStep (step 80 $ Options None WithAlias True InlineWithBreak Inherit (LPConstant 4) True False) input'
where
input' = unlines
[ "import qualified Data.List as List (concat, foldl, foldr, head, init,"
@@ -343,7 +348,7 @@ case13 = expected
case14 :: Assertion
case14 = expected
@=? testStep
- (step 80 $ Options None WithAlias InlineWithBreak Inherit (LPConstant 10) True) expected
+ (step 80 $ Options None WithAlias True InlineWithBreak Inherit (LPConstant 10) True False) expected
where
expected = unlines
[ "import qualified Data.List as List (concat, map, null, reverse, tail, (++))"
@@ -353,7 +358,7 @@ case14 = expected
--------------------------------------------------------------------------------
case15 :: Assertion
case15 = expected
- @=? testStep (step 80 $ Options None AfterAlias Multiline Inherit (LPConstant 4) True) input'
+ @=? testStep (step 80 $ Options None AfterAlias True Multiline Inherit (LPConstant 4) True False) input'
where
expected = unlines
[ "import Data.Acid (AcidState)"
@@ -379,7 +384,7 @@ case15 = expected
--------------------------------------------------------------------------------
case16 :: Assertion
case16 = expected
- @=? testStep (step 80 $ Options None AfterAlias Multiline Inherit (LPConstant 4) False) input'
+ @=? testStep (step 80 $ Options None AfterAlias True Multiline Inherit (LPConstant 4) False False) input'
where
expected = unlines
[ "import Data.Acid (AcidState)"
@@ -403,7 +408,7 @@ case16 = expected
--------------------------------------------------------------------------------
case17 :: Assertion
case17 = expected
- @=? testStep (step 80 $ Options None AfterAlias Multiline Inherit (LPConstant 4) True) input'
+ @=? testStep (step 80 $ Options None AfterAlias True Multiline Inherit (LPConstant 4) True False) input'
where
expected = unlines
[ "import Control.Applicative (Applicative (pure, (<*>)))"
@@ -421,7 +426,7 @@ case17 = expected
--------------------------------------------------------------------------------
case18 :: Assertion
case18 = expected @=? testStep
- (step 40 $ Options None AfterAlias InlineToMultiline Inherit (LPConstant 4) True) input'
+ (step 40 $ Options None AfterAlias True InlineToMultiline Inherit (LPConstant 4) True False) input'
where
expected = unlines
----------------------------------------
@@ -448,7 +453,7 @@ case18 = expected @=? testStep
--------------------------------------------------------------------------------
case19 :: Assertion
case19 = expected @=? testStep
- (step 40 $ Options Global NewLine InlineWithBreak RightAfter (LPConstant 17) True) case19input
+ (step 40 $ Options Global NewLine True InlineWithBreak RightAfter (LPConstant 17) True False) case19input
where
expected = unlines
----------------------------------------
@@ -463,7 +468,7 @@ case19 = expected @=? testStep
case19b :: Assertion
case19b = expected @=? testStep
- (step 40 $ Options File NewLine InlineWithBreak RightAfter (LPConstant 17) True) case19input
+ (step 40 $ Options File NewLine True InlineWithBreak RightAfter (LPConstant 17) True False) case19input
where
expected = unlines
----------------------------------------
@@ -478,7 +483,7 @@ case19b = expected @=? testStep
case19c :: Assertion
case19c = expected @=? testStep
- (step 40 $ Options File NewLine InlineWithBreak RightAfter LPModuleName True) case19input
+ (step 40 $ Options File NewLine True InlineWithBreak RightAfter LPModuleName True False) case19input
where
expected = unlines
----------------------------------------
@@ -493,7 +498,7 @@ case19c = expected @=? testStep
case19d :: Assertion
case19d = expected @=? testStep
- (step 40 $ Options Global NewLine InlineWithBreak RightAfter LPModuleName True) case19input
+ (step 40 $ Options Global NewLine True InlineWithBreak RightAfter LPModuleName True False) case19input
where
expected = unlines
----------------------------------------
@@ -531,3 +536,130 @@ case20 = expected
, "import qualified Data.Map as Map"
, "import Data.Set (empty)"
]
+
+--------------------------------------------------------------------------------
+case21 :: Assertion
+case21 = expected
+ @=? testStep (step 80 defaultOptions) input'
+ where
+ expected = unlines
+ [ "{-# LANGUAGE ExplicitNamespaces #-}"
+ , "import X1 (A, B, C)"
+ , "import X2 (A, B, C)"
+ , "import X3 (A (..))"
+ , "import X4 (A (..))"
+ , "import X5 (A (..))"
+ , "import X6 (A (a, b, c), B (m, n, o))"
+ , "import X7 (a, b, c)"
+ , "import X8 (type (+), (+))"
+ , "import X9 hiding (x, y, z)"
+ ]
+ input' = unlines
+ [ "{-# LANGUAGE ExplicitNamespaces #-}"
+ , "import X1 (A, B, A, C, A, B, A)"
+ , "import X2 (C(), B(), A())"
+ , "import X3 (A(..))"
+ , "import X4 (A, A(..))"
+ , "import X5 (A(..), A(x))"
+ , "import X6 (A(a,b), B(m,n), A(c), B(o))"
+ , "import X7 (a, b, a, c)"
+ , "import X8 (type (+), (+))"
+ , "import X9 hiding (x, y, z, x)"
+ ]
+
+--------------------------------------------------------------------------------
+case22 :: Assertion
+case22 = expected
+ @=? testStep (step 80 defaultOptions) input'
+ where
+ expected = unlines
+ [ "{-# LANGUAGE PackageImports #-}"
+ , "import A"
+ , "import \"blah\" A"
+ , "import \"foo\" A"
+ , "import qualified \"foo\" A as X"
+ , "import \"foo\" B (shortName, someLongName, someLongerName,"
+ , " theLongestNameYet)"
+ ]
+ input' = unlines
+ [ "{-# LANGUAGE PackageImports #-}"
+ , "import A"
+ , "import \"foo\" A"
+ , "import \"blah\" A"
+ , "import qualified \"foo\" A as X"
+ -- this import fits into 80 chats without "foo",
+ -- but doesn't fit when "foo" is included into the calculation
+ , "import \"foo\" B (someLongName, someLongerName, " ++
+ "theLongestNameYet, shortName)"
+ ]
+
+--------------------------------------------------------------------------------
+case23 :: Assertion
+case23 = expected
+ @=? testStep (step 40 $ Options None AfterAlias False Inline Inherit (LPConstant 4) True True) input'
+ where
+ expected = unlines
+ [ "import Data.Acid ( AcidState )"
+ , "import Data.Default.Class ( Default (def) )"
+ , ""
+ , "import Data.Monoid ( (<>) )"
+ , ""
+ , "import Data.ALongName.Foo ( Boo, Foo,"
+ , " Goo )"
+ ]
+
+ input' = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.Monoid ((<>) )"
+ , ""
+ , "import Data.ALongName.Foo (Foo, Goo, Boo)"
+ ]
+
+--------------------------------------------------------------------------------
+case24 :: Assertion
+case24 = expected
+ @=? testStep (step 40 $ Options None AfterAlias False InlineWithBreak Inherit (LPConstant 4) True True) input'
+ where
+ expected = unlines
+ [ "import Data.Acid ( AcidState )"
+ , "import Data.Default.Class"
+ , " ( Default (def) )"
+ , ""
+ , "import Data.ALongName.Foo"
+ , " ( BooReallyLong, FooReallyLong,"
+ , " GooReallyLong )"
+ ]
+
+ input' = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.ALongName.Foo (FooReallyLong, " ++
+ "GooReallyLong, BooReallyLong)"
+ ]
+
+--------------------------------------------------------------------------------
+case25 :: Assertion
+case25 = expected
+ @=? testStep (step 80 $ Options Group AfterAlias False Multiline Inherit (LPConstant 4) False False) input'
+ where
+ expected = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.Maybe (Maybe(Just, Nothing))"
+ , "import qualified Data.Maybe.Extra (Maybe(Just, Nothing))"
+ , ""
+ , "import Data.Foo (Foo(Bar, Foo), Goo(Goo))"
+ ]
+ input' = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.Maybe (Maybe (Just, Nothing))"
+ , "import qualified Data.Maybe.Extra (Maybe(Just, Nothing))"
+ , ""
+ , "import Data.Foo (Foo (Foo,Bar), Goo(Goo))"
+ ]
diff --git a/tests/Language/Haskell/Stylish/Step/LanguagePragmas/Tests.hs b/tests/Language/Haskell/Stylish/Step/LanguagePragmas/Tests.hs
index fe889e4..2d74813 100644
--- a/tests/Language/Haskell/Stylish/Step/LanguagePragmas/Tests.hs
+++ b/tests/Language/Haskell/Stylish/Step/LanguagePragmas/Tests.hs
@@ -26,6 +26,8 @@ tests = testGroup "Language.Haskell.Stylish.Step.LanguagePragmas.Tests"
, testCase "case 06" case06
, testCase "case 07" case07
, testCase "case 08" case08
+ , testCase "case 09" case09
+ , testCase "case 10" case10
]
@@ -167,3 +169,31 @@ case08 = expected @=? testStep (step 80 CompactLine False False) input
"TemplateHaskell #-}"
, "{-# LANGUAGE TypeOperators, ViewPatterns #-}"
]
+
+
+--------------------------------------------------------------------------------
+case09 :: Assertion
+case09 = expected @=? testStep (step 80 Compact True False) input
+ where
+ input = unlines
+ [ "{-# LANGUAGE DefaultSignatures, FlexibleInstances, LambdaCase, " ++
+ "TypeApplications"
+ , " #-}"
+ ]
+ expected = unlines
+ [ "{-# LANGUAGE DefaultSignatures, FlexibleInstances, LambdaCase,"
+ , " TypeApplications #-}"
+ ]
+
+--------------------------------------------------------------------------------
+case10 :: Assertion
+case10 = expected @=? testStep (step 80 Compact True False) input
+ where
+ input = unlines
+ [ "{-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables,"
+ , " TypeApplications #-}"
+ ]
+ expected = unlines
+ [ "{-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables, " ++
+ "TypeApplications #-}"
+ ]