summaryrefslogtreecommitdiffhomepage
path: root/lib/Language/Haskell
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Language/Haskell')
-rw-r--r--lib/Language/Haskell/Stylish.hs62
-rw-r--r--lib/Language/Haskell/Stylish/Align.hs13
-rw-r--r--lib/Language/Haskell/Stylish/Config.hs68
-rw-r--r--lib/Language/Haskell/Stylish/Editor.hs11
-rw-r--r--lib/Language/Haskell/Stylish/Step/Data.hs126
-rw-r--r--lib/Language/Haskell/Stylish/Step/Imports.hs27
-rw-r--r--lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs54
-rw-r--r--lib/Language/Haskell/Stylish/Step/SimpleAlign.hs2
-rw-r--r--lib/Language/Haskell/Stylish/Step/UnicodeSyntax.hs14
-rw-r--r--lib/Language/Haskell/Stylish/Util.hs46
10 files changed, 347 insertions, 76 deletions
diff --git a/lib/Language/Haskell/Stylish.hs b/lib/Language/Haskell/Stylish.hs
index 46543ec..c50db4d 100644
--- a/lib/Language/Haskell/Stylish.hs
+++ b/lib/Language/Haskell/Stylish.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
--------------------------------------------------------------------------------
module Language.Haskell.Stylish
( -- * Run
@@ -10,12 +11,15 @@ module Language.Haskell.Stylish
, trailingWhitespace
, unicodeSyntax
-- ** Helpers
+ , findHaskellFiles
, stepName
-- * Config
, module Language.Haskell.Stylish.Config
-- * Misc
, module Language.Haskell.Stylish.Verbose
, version
+ , format
+ , ConfigPath(..)
, Lines
, Step
) where
@@ -23,7 +27,11 @@ module Language.Haskell.Stylish
--------------------------------------------------------------------------------
import Control.Monad (foldM)
-
+import System.Directory (doesDirectoryExist,
+ doesFileExist,
+ listDirectory)
+import System.FilePath (takeExtension,
+ (</>))
--------------------------------------------------------------------------------
import Language.Haskell.Stylish.Config
@@ -40,24 +48,25 @@ import Paths_stylish_haskell (version)
--------------------------------------------------------------------------------
-simpleAlign :: Int -- ^ Columns
+simpleAlign :: Maybe Int -- ^ Columns
-> SimpleAlign.Config
-> Step
simpleAlign = SimpleAlign.step
--------------------------------------------------------------------------------
-imports :: Int -- ^ columns
+imports :: Maybe Int -- ^ columns
-> Imports.Options
-> Step
imports = Imports.step
--------------------------------------------------------------------------------
-languagePragmas :: Int -- ^ columns
+languagePragmas :: Maybe Int -- ^ columns
-> LanguagePragmas.Style
-> Bool -- ^ Pad to same length in vertical mode?
-> Bool -- ^ remove redundant?
+ -> String -- ^ language prefix
-> Step
languagePragmas = LanguagePragmas.step
@@ -75,6 +84,7 @@ trailingWhitespace = TrailingWhitespace.step
--------------------------------------------------------------------------------
unicodeSyntax :: Bool -- ^ add language pragma?
+ -> String -- ^ language prefix
-> Step
unicodeSyntax = UnicodeSyntax.step
@@ -89,3 +99,47 @@ runStep exts mfp ls step =
runSteps :: Extensions -> Maybe FilePath -> [Step] -> Lines
-> Either String Lines
runSteps exts mfp steps ls = foldM (runStep exts mfp) ls steps
+
+newtype ConfigPath = ConfigPath { unConfigPath :: FilePath }
+
+-- |Formats given contents optionally using the config provided as first param.
+-- The second file path is the location from which the contents were read.
+-- If provided, it's going to be printed out in the error message.
+format :: Maybe ConfigPath -> Maybe FilePath -> String -> IO (Either String Lines)
+format maybeConfigPath maybeFilePath contents = do
+ conf <- loadConfig (makeVerbose True) (fmap unConfigPath maybeConfigPath)
+ pure $ runSteps (configLanguageExtensions conf) maybeFilePath (configSteps conf) $ lines contents
+
+
+--------------------------------------------------------------------------------
+-- | Searches Haskell source files in any given folder recursively.
+findHaskellFiles :: Bool -> [FilePath] -> IO [FilePath]
+findHaskellFiles v fs = mapM (findFilesR v) fs >>= return . concat
+
+
+--------------------------------------------------------------------------------
+findFilesR :: Bool -> FilePath -> IO [FilePath]
+findFilesR _ [] = return []
+findFilesR v path = do
+ doesFileExist path >>= \case
+ True -> return [path]
+ _ -> doesDirectoryExist path >>= \case
+ True -> findFilesRecursive path >>=
+ return . filter (\x -> takeExtension x == ".hs")
+ False -> do
+ makeVerbose v ("Input folder does not exists: " <> path)
+ findFilesR v []
+ where
+ findFilesRecursive :: FilePath -> IO [FilePath]
+ findFilesRecursive = listDirectoryFiles findFilesRecursive
+
+ listDirectoryFiles :: (FilePath -> IO [FilePath])
+ -> FilePath -> IO [FilePath]
+ listDirectoryFiles go topdir = do
+ ps <- listDirectory topdir >>=
+ mapM (\x -> do
+ let dir = topdir </> x
+ doesDirectoryExist dir >>= \case
+ True -> go dir
+ False -> return [dir])
+ return $ concat ps
diff --git a/lib/Language/Haskell/Stylish/Align.hs b/lib/Language/Haskell/Stylish/Align.hs
index 53549b9..1f28d7a 100644
--- a/lib/Language/Haskell/Stylish/Align.hs
+++ b/lib/Language/Haskell/Stylish/Align.hs
@@ -55,16 +55,21 @@ data Alignable a = Alignable
--------------------------------------------------------------------------------
-- | Create changes that perform the alignment.
align
- :: Int -- ^ Max columns
+ :: Maybe Int -- ^ Max columns
-> [Alignable H.SrcSpan] -- ^ Alignables
-> [Change String] -- ^ Changes performing the alignment.
align _ [] = []
align maxColumns alignment
-- Do not make any change if we would go past the maximum number of columns.
- | longestLeft + longestRight > maxColumns = []
- | not (fixable alignment) = []
- | otherwise = map align' alignment
+ | exceedsColumns (longestLeft + longestRight) = []
+ | not (fixable alignment) = []
+ | otherwise = map align' alignment
where
+ exceedsColumns i = case maxColumns of
+ Nothing -> False -- No number exceeds a maximum column count of
+ -- Nothing, because there is no limit to exceed.
+ Just c -> i > c
+
-- The longest thing in the left column.
longestLeft = maximum $ map (H.srcSpanEndColumn . aLeft) alignment
diff --git a/lib/Language/Haskell/Stylish/Config.hs b/lib/Language/Haskell/Stylish/Config.hs
index 8f43131..475a5e3 100644
--- a/lib/Language/Haskell/Stylish/Config.hs
+++ b/lib/Language/Haskell/Stylish/Config.hs
@@ -16,24 +16,29 @@ import Data.Aeson (FromJSON (..)
import qualified Data.Aeson as A
import qualified Data.Aeson.Types as A
import qualified Data.ByteString as B
+import Data.ByteString.Lazy (fromStrict)
+import Data.Char (toLower)
import qualified Data.FileEmbed as FileEmbed
import Data.List (intercalate,
nub)
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
-import Data.Yaml (decodeEither',
- prettyPrintParseException)
+import qualified Data.Text as T
+import Data.YAML (prettyPosWithSource)
+import Data.YAML.Aeson (decode1Strict)
import System.Directory
import System.FilePath ((</>))
import qualified System.IO as IO (Newline (..),
nativeNewline)
+import Text.Read (readMaybe)
--------------------------------------------------------------------------------
import qualified Language.Haskell.Stylish.Config.Cabal as Cabal
import Language.Haskell.Stylish.Config.Internal
import Language.Haskell.Stylish.Step
+import qualified Language.Haskell.Stylish.Step.Data as Data
import qualified Language.Haskell.Stylish.Step.Imports as Imports
import qualified Language.Haskell.Stylish.Step.LanguagePragmas as LanguagePragmas
import qualified Language.Haskell.Stylish.Step.SimpleAlign as SimpleAlign
@@ -51,7 +56,7 @@ type Extensions = [String]
--------------------------------------------------------------------------------
data Config = Config
{ configSteps :: [Step]
- , configColumns :: Int
+ , configColumns :: Maybe Int
, configLanguageExtensions :: [String]
, configNewline :: IO.Newline
, configCabal :: Bool
@@ -80,12 +85,10 @@ configFilePath verbose Nothing = do
current <- getCurrentDirectory
configPath <- getXdgDirectory XdgConfig "stylish-haskell"
home <- getHomeDirectory
- mbConfig <- search verbose $
+ search verbose $
[d </> configFileName | d <- ancestors current] ++
[configPath </> "config.yaml", home </> configFileName]
- return mbConfig
-
search :: Verbose -> [FilePath] -> IO (Maybe FilePath)
search _ [] = return Nothing
search verbose (f : fs) = do
@@ -100,9 +103,8 @@ loadConfig verbose userSpecified = do
mbFp <- configFilePath verbose userSpecified
verbose $ "Loading configuration at " ++ fromMaybe "<embedded>" mbFp
bytes <- maybe (return defaultConfigBytes) B.readFile mbFp
- case decodeEither' bytes of
- Left err -> error $
- "Language.Haskell.Stylish.Config.loadConfig: " ++ prettyPrintParseException err
+ case decode1Strict bytes of
+ Left (pos, err) -> error $ prettyPosWithSource pos (fromStrict bytes) ("Language.Haskell.Stylish.Config.loadConfig: " ++ err)
Right config -> do
cabalLanguageExtensions <- if configCabal config
then map show <$> Cabal.findLanguageExtensions verbose
@@ -120,7 +122,7 @@ parseConfig (A.Object o) = do
-- First load the config without the actual steps
config <- Config
<$> pure []
- <*> (o A..:? "columns" A..!= 80)
+ <*> (o A..:! "columns" A..!= Just 80)
<*> (o A..:? "language_extensions" A..!= [])
<*> (o A..:? "newline" >>= parseEnum newlines IO.nativeNewline)
<*> (o A..:? "cabal" A..!= True)
@@ -142,6 +144,7 @@ parseConfig _ = mzero
catalog :: Map String (Config -> A.Object -> A.Parser Step)
catalog = M.fromList
[ ("imports", parseImports)
+ , ("records", parseRecords)
, ("language_pragmas", parseLanguagePragmas)
, ("simple_align", parseSimpleAlign)
, ("squash", parseSquash)
@@ -181,6 +184,28 @@ parseSimpleAlign c o = SimpleAlign.step
where
withDef f k = fromMaybe (f SimpleAlign.defaultConfig) <$> (o A..:? k)
+--------------------------------------------------------------------------------
+parseRecords :: Config -> A.Object -> A.Parser Step
+parseRecords _ o = Data.step
+ <$> (Data.Config
+ <$> (o A..: "equals" >>= parseIndent)
+ <*> (o A..: "first_field" >>= parseIndent)
+ <*> (o A..: "field_comment")
+ <*> (o A..: "deriving"))
+
+
+parseIndent :: A.Value -> A.Parser Data.Indent
+parseIndent = A.withText "Indent" $ \t ->
+ if t == "same_line"
+ then return Data.SameLine
+ else
+ if "indent " `T.isPrefixOf` t
+ then
+ case readMaybe (T.unpack $ T.drop 7 t) of
+ Just n -> return $ Data.Indent n
+ Nothing -> fail $ "Indent: not a number" <> T.unpack (T.drop 7 t)
+ else fail $ "can't parse indent setting: " <> T.unpack t
+
--------------------------------------------------------------------------------
parseSquash :: Config -> A.Object -> A.Parser Step
@@ -200,9 +225,9 @@ parseImports config o = Imports.step
-- 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..:? "space_surround" A..!= (def Imports.spaceSurround))
+ <*> o A..:? "list_padding" A..!= def Imports.listPadding
+ <*> o A..:? "separate_lists" A..!= def Imports.separateLists
+ <*> o A..:? "space_surround" A..!= def Imports.spaceSurround)
where
def f = f Imports.defaultOptions
@@ -237,8 +262,9 @@ parseLanguagePragmas :: Config -> A.Object -> A.Parser Step
parseLanguagePragmas config o = LanguagePragmas.step
<$> pure (configColumns config)
<*> (o A..:? "style" >>= parseEnum styles LanguagePragmas.Vertical)
- <*> o A..:? "align" A..!= True
+ <*> o A..:? "align" A..!= True
<*> o A..:? "remove_redundant" A..!= True
+ <*> mkLanguage o
where
styles =
[ ("vertical", LanguagePragmas.Vertical)
@@ -248,6 +274,19 @@ parseLanguagePragmas config o = LanguagePragmas.step
--------------------------------------------------------------------------------
+-- | Utilities for validating language prefixes
+mkLanguage :: A.Object -> A.Parser String
+mkLanguage o = do
+ lang <- o A..:? "language_prefix"
+ maybe (pure "LANGUAGE") validate lang
+ where
+ validate :: String -> A.Parser String
+ validate s
+ | fmap toLower s == "language" = pure s
+ | otherwise = fail "please provide a valid language prefix"
+
+
+--------------------------------------------------------------------------------
parseTabs :: Config -> A.Object -> A.Parser Step
parseTabs _ o = Tabs.step
<$> o A..:? "spaces" A..!= 8
@@ -262,3 +301,4 @@ parseTrailingWhitespace _ _ = return TrailingWhitespace.step
parseUnicodeSyntax :: Config -> A.Object -> A.Parser Step
parseUnicodeSyntax _ o = UnicodeSyntax.step
<$> o A..:? "add_language_pragma" A..!= True
+ <*> mkLanguage o
diff --git a/lib/Language/Haskell/Stylish/Editor.hs b/lib/Language/Haskell/Stylish/Editor.hs
index cad7e68..f71d1f6 100644
--- a/lib/Language/Haskell/Stylish/Editor.hs
+++ b/lib/Language/Haskell/Stylish/Editor.hs
@@ -1,3 +1,5 @@
+{-# language LambdaCase #-}
+
--------------------------------------------------------------------------------
-- | This module provides you with a line-based editor. It's main feature is
-- that you can specify multiple changes at the same time, e.g.:
@@ -19,8 +21,7 @@ module Language.Haskell.Stylish.Editor
--------------------------------------------------------------------------------
-import Data.List (intercalate, sortBy)
-import Data.Ord (comparing)
+import Data.List (intercalate, sortOn)
--------------------------------------------------------------------------------
@@ -31,7 +32,7 @@ import Language.Haskell.Stylish.Block
-- | Changes the lines indicated by the 'Block' into the given 'Lines'
data Change a = Change
{ changeBlock :: Block a
- , changeLines :: ([a] -> [a])
+ , changeLines :: [a] -> [a]
}
@@ -49,7 +50,7 @@ applyChanges changes0
intercalate ", " (map printBlock blocks)
| otherwise = go 1 changes1
where
- changes1 = sortBy (comparing (blockStart . changeBlock)) changes0
+ changes1 = sortOn (blockStart . changeBlock) changes0
blocks = map changeBlock changes1
printBlock b = show (blockStart b) ++ "-" ++ show (blockEnd b)
@@ -87,7 +88,7 @@ change = Change
--------------------------------------------------------------------------------
-- | Change a single line for some other lines
changeLine :: Int -> (a -> [a]) -> Change a
-changeLine start f = change (Block start start) $ \xs -> case xs of
+changeLine start f = change (Block start start) $ \case
[] -> []
(x : _) -> f x
diff --git a/lib/Language/Haskell/Stylish/Step/Data.hs b/lib/Language/Haskell/Stylish/Step/Data.hs
new file mode 100644
index 0000000..1f7732b
--- /dev/null
+++ b/lib/Language/Haskell/Stylish/Step/Data.hs
@@ -0,0 +1,126 @@
+{-# LANGUAGE RecordWildCards #-}
+
+module Language.Haskell.Stylish.Step.Data where
+
+import Data.List (find, intercalate)
+import Data.Maybe (fromMaybe, maybeToList)
+import qualified Language.Haskell.Exts as H
+import Language.Haskell.Exts.Comments
+import Language.Haskell.Stylish.Block
+import Language.Haskell.Stylish.Editor
+import Language.Haskell.Stylish.Step
+import Language.Haskell.Stylish.Util
+import Prelude hiding (init)
+
+data Indent
+ = SameLine
+ | Indent !Int
+ deriving (Show)
+
+data Config = Config
+ { cEquals :: !Indent
+ -- ^ Indent between type constructor and @=@ sign (measured from column 0)
+ , cFirstField :: !Indent
+ -- ^ Indent between data constructor and @{@ line (measured from column with data constructor name)
+ , cFieldComment :: !Int
+ -- ^ Indent between column with @{@ and start of field line comment (this line has @cFieldComment = 2@)
+ , cDeriving :: !Int
+ -- ^ Indent before @deriving@ lines (measured from column 0)
+ } deriving (Show)
+
+datas :: H.Module l -> [H.Decl l]
+datas (H.Module _ _ _ _ decls) = decls
+datas _ = []
+
+type ChangeLine = Change String
+
+step :: Config -> Step
+step cfg = makeStep "Data" (step' cfg)
+
+step' :: Config -> Lines -> Module -> Lines
+step' cfg ls (module', allComments) = applyChanges changes ls
+ where
+ datas' = datas $ fmap linesFromSrcSpan module'
+ changes = datas' >>= maybeToList . changeDecl allComments cfg
+
+findCommentOnLine :: LineBlock -> [Comment] -> Maybe Comment
+findCommentOnLine lb = find commentOnLine
+ where
+ commentOnLine (Comment _ (H.SrcSpan _ start _ end _) _) =
+ blockStart lb == start && blockEnd lb == end
+
+findCommentBelowLine :: LineBlock -> [Comment] -> Maybe Comment
+findCommentBelowLine lb = find commentOnLine
+ where
+ commentOnLine (Comment _ (H.SrcSpan _ start _ end _) _) =
+ blockStart lb == start - 1 && blockEnd lb == end - 1
+
+commentsWithin :: LineBlock -> [Comment] -> [Comment]
+commentsWithin lb = filter within
+ where
+ within (Comment _ (H.SrcSpan _ start _ end _) _) =
+ start >= blockStart lb && end <= blockEnd lb
+
+changeDecl :: [Comment] -> Config -> H.Decl LineBlock -> Maybe ChangeLine
+changeDecl _ _ (H.DataDecl _ (H.DataType _) Nothing _ [] _) = Nothing
+changeDecl allComments cfg@Config{..} (H.DataDecl block (H.DataType _) Nothing dhead decls derivings)
+ | hasRecordFields = Just $ change block (const $ concat newLines)
+ | otherwise = Nothing
+ where
+ hasRecordFields = any
+ (\qual -> case qual of
+ (H.QualConDecl _ _ _ (H.RecDecl {})) -> True
+ _ -> False)
+ decls
+
+ typeConstructor = "data " <> H.prettyPrint dhead
+
+ -- In any case set @pipeIndent@ such that @|@ is aligned with @=@.
+ (firstLine, firstLineInit, pipeIndent) =
+ case cEquals of
+ SameLine -> (Nothing, typeConstructor <> " = ", length typeConstructor + 1)
+ Indent n -> (Just [[typeConstructor]], indent n "= ", n)
+
+ newLines = fromMaybe [] firstLine ++ fmap constructors zipped <> [fmap (indent cDeriving . H.prettyPrint) derivings]
+ zipped = zip decls ([1..] ::[Int])
+
+ constructors (decl, 1) = processConstructor allComments firstLineInit cfg decl
+ constructors (decl, _) = processConstructor allComments (indent pipeIndent "| ") cfg decl
+changeDecl _ _ _ = Nothing
+
+processConstructor :: [Comment] -> String -> Config -> H.QualConDecl LineBlock -> [String]
+processConstructor allComments init Config{..} (H.QualConDecl _ _ _ (H.RecDecl _ dname (f:fs))) = do
+ fromMaybe [] firstLine <> n1 <> ns <> [indent fieldIndent "}"]
+ where
+ n1 = processName firstLinePrefix (extractField f)
+ ns = fs >>= processName (indent fieldIndent ", ") . extractField
+
+ -- Set @fieldIndent@ such that @,@ is aligned with @{@.
+ (firstLine, firstLinePrefix, fieldIndent) =
+ case cFirstField of
+ SameLine ->
+ ( Nothing
+ , init <> H.prettyPrint dname <> " { "
+ , length init + length (H.prettyPrint dname) + 1
+ )
+ Indent n ->
+ ( Just [init <> H.prettyPrint dname]
+ , indent (length init + n) "{ "
+ , length init + n
+ )
+
+ processName prefix (fnames, _type, lineComment, commentBelowLine) =
+ [prefix <> intercalate ", " (fmap H.prettyPrint fnames) <> " :: " <> H.prettyPrint _type <> addLineComment lineComment
+ ] ++ addCommentBelow commentBelowLine
+
+ addLineComment (Just (Comment _ _ c)) = " --" <> c
+ addLineComment Nothing = ""
+
+ -- Field comment indent is measured from the column with @{@, hence adding of @fieldIndent@ here.
+ addCommentBelow Nothing = []
+ addCommentBelow (Just (Comment _ _ c)) = [indent (fieldIndent + cFieldComment) "--" <> c]
+
+ extractField (H.FieldDecl lb names _type) =
+ (names, _type, findCommentOnLine lb allComments, findCommentBelowLine lb allComments)
+
+processConstructor _ init _ decl = [init <> trimLeft (H.prettyPrint decl)]
diff --git a/lib/Language/Haskell/Stylish/Step/Imports.hs b/lib/Language/Haskell/Stylish/Step/Imports.hs
index 4ceb802..7cb78d4 100644
--- a/lib/Language/Haskell/Stylish/Step/Imports.hs
+++ b/lib/Language/Haskell/Stylish/Step/Imports.hs
@@ -258,7 +258,7 @@ prettyImportSpec separate = prettyImportSpec'
--------------------------------------------------------------------------------
prettyImport :: (Ord l, Show l) =>
- Int -> Options -> Bool -> Bool -> Int -> H.ImportDecl l -> [String]
+ Maybe Int -> Options -> Bool -> Bool -> Int -> H.ImportDecl l -> [String]
prettyImport columns Options{..} padQualified padName longest imp
| (void `fmap` H.importSpecs imp) == emptyImportSpec = emptyWrap
| otherwise = case longListAlign of
@@ -277,7 +277,7 @@ prettyImport columns Options{..} padQualified padName longest imp
longListWrapper shortWrap longWrap
| listAlign == NewLine
|| length shortWrap > 1
- || length (head shortWrap) > columns
+ || exceedsColumns (length (head shortWrap))
= longWrap
| otherwise = shortWrap
@@ -292,14 +292,14 @@ prettyImport columns Options{..} padQualified padName longest imp
. withLast (++ (maybeSpace ++ ")"))
inlineWrapper = case listAlign of
- NewLine -> (paddedNoSpecBase :) . wrapRest columns listPadding'
- WithModuleName -> wrap columns paddedBase (withModuleNameBaseLength + 4)
- WithAlias -> wrap columns paddedBase (inlineBaseLength + 1)
+ NewLine -> (paddedNoSpecBase :) . wrapRestMaybe columns listPadding'
+ WithModuleName -> wrapMaybe columns paddedBase (withModuleNameBaseLength + 4)
+ WithAlias -> wrapMaybe columns paddedBase (inlineBaseLength + 1)
-- Add 1 extra space to ensure same padding as in original code.
AfterAlias -> withTail ((' ' : maybeSpace) ++)
- . wrap columns paddedBase (afterAliasBaseLength + 1)
+ . wrapMaybe columns paddedBase (afterAliasBaseLength + 1)
- inlineWithBreakWrap = paddedNoSpecBase : wrapRest columns listPadding'
+ inlineWithBreakWrap = paddedNoSpecBase : wrapRestMaybe columns listPadding'
( mapSpecs
$ withInit (++ ",")
. withHead (("(" ++ maybeSpace) ++)
@@ -307,7 +307,7 @@ prettyImport columns Options{..} padQualified padName longest imp
inlineToMultilineWrap
| length inlineWithBreakWrap > 2
- || any ((> columns) . length) (tail inlineWithBreakWrap)
+ || any (exceedsColumns . length) (tail inlineWithBreakWrap)
= multilineWrap
| otherwise = inlineWithBreakWrap
@@ -389,9 +389,14 @@ prettyImport columns Options{..} padQualified padName longest imp
True -> " "
False -> ""
+ exceedsColumns i = case columns of
+ Nothing -> False -- No number exceeds a maximum column count of
+ -- Nothing, because there is no limit to exceed.
+ Just c -> i > c
+
--------------------------------------------------------------------------------
-prettyImportGroup :: Int -> Options -> Bool -> Int
+prettyImportGroup :: Maybe Int -> Options -> Bool -> Int
-> [H.ImportDecl LineBlock]
-> Lines
prettyImportGroup columns align fileAlign longest imps =
@@ -415,12 +420,12 @@ prettyImportGroup columns align fileAlign longest imps =
--------------------------------------------------------------------------------
-step :: Int -> Options -> Step
+step :: Maybe Int -> Options -> Step
step columns = makeStep "Imports" . step' columns
--------------------------------------------------------------------------------
-step' :: Int -> Options -> Lines -> Module -> Lines
+step' :: Maybe Int -> Options -> Lines -> Module -> Lines
step' columns align ls (module', _) = applyChanges
[ change block $ const $
prettyImportGroup columns align fileAlign longest importGroup
diff --git a/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs b/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs
index cdedfa8..c9d461f 100644
--- a/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs
+++ b/lib/Language/Haskell/Stylish/Step/LanguagePragmas.hs
@@ -2,7 +2,6 @@
module Language.Haskell.Stylish.Step.LanguagePragmas
( Style (..)
, step
-
-- * Utilities
, addLanguagePragma
) where
@@ -42,9 +41,9 @@ firstLocation = minimum . map (blockStart . fst)
--------------------------------------------------------------------------------
-verticalPragmas :: Int -> Bool -> [String] -> Lines
-verticalPragmas longest align pragmas' =
- [ "{-# LANGUAGE " ++ pad pragma ++ " #-}"
+verticalPragmas :: String -> Int -> Bool -> [String] -> Lines
+verticalPragmas lg longest align pragmas' =
+ [ "{-# " ++ lg ++ " " ++ pad pragma ++ " #-}"
| pragma <- pragmas'
]
where
@@ -54,27 +53,23 @@ verticalPragmas longest align pragmas' =
--------------------------------------------------------------------------------
-compactPragmas :: Int -> [String] -> Lines
-compactPragmas columns pragmas' = wrap columns "{-# LANGUAGE" 13 $
+compactPragmas :: String -> Maybe Int -> [String] -> Lines
+compactPragmas lg columns pragmas' = wrapMaybe columns ("{-# " ++ lg) 13 $
map (++ ",") (init pragmas') ++ [last pragmas' ++ " #-}"]
--------------------------------------------------------------------------------
-compactLinePragmas :: Int -> Bool -> [String] -> Lines
-compactLinePragmas _ _ [] = []
-compactLinePragmas columns align pragmas' = map (wrapLanguage . pad) prags
+compactLinePragmas :: String -> Maybe Int -> Bool -> [String] -> Lines
+compactLinePragmas _ _ _ [] = []
+compactLinePragmas lg columns align pragmas' = map (wrapLanguage . pad) prags
where
- wrapLanguage ps = "{-# LANGUAGE" ++ ps ++ " #-}"
-
- maxWidth = columns - 16
-
+ wrapLanguage ps = "{-# " ++ lg ++ ps ++ " #-}"
+ maxWidth = fmap (\c -> c - 16) columns
longest = maximum $ map length prags
-
pad
| align = padRight longest
| otherwise = id
-
- prags = map truncateComma $ wrap maxWidth "" 1 $
+ prags = map truncateComma $ wrapMaybe maxWidth "" 1 $
map (++ ",") (init pragmas') ++ [last pragmas']
@@ -87,10 +82,10 @@ truncateComma xs
--------------------------------------------------------------------------------
-prettyPragmas :: Int -> Int -> Bool -> Style -> [String] -> Lines
-prettyPragmas _ longest align Vertical = verticalPragmas longest align
-prettyPragmas cols _ _ Compact = compactPragmas cols
-prettyPragmas cols _ align CompactLine = compactLinePragmas cols align
+prettyPragmas :: String -> Maybe Int -> Int -> Bool -> Style -> [String] -> Lines
+prettyPragmas lp _ longest align Vertical = verticalPragmas lp longest align
+prettyPragmas lp cols _ _ Compact = compactPragmas lp cols
+prettyPragmas lp cols _ align CompactLine = compactLinePragmas lp cols align
--------------------------------------------------------------------------------
@@ -110,35 +105,34 @@ filterRedundant isRedundant' = snd . foldr filterRedundant' (S.empty, [])
known' = xs' `S.union` known
--------------------------------------------------------------------------------
-step :: Int -> Style -> Bool -> Bool -> Step
-step = (((makeStep "LanguagePragmas" .) .) .) . step'
+step :: Maybe Int -> Style -> Bool -> Bool -> String -> Step
+step = ((((makeStep "LanguagePragmas" .) .) .) .) . step'
--------------------------------------------------------------------------------
-step' :: Int -> Style -> Bool -> Bool -> Lines -> Module -> Lines
-step' columns style align removeRedundant ls (module', _)
+step' :: Maybe Int -> Style -> Bool -> Bool -> String -> Lines -> Module -> Lines
+step' columns style align removeRedundant lngPrefix ls (module', _)
| null pragmas' = ls
| otherwise = applyChanges changes ls
where
isRedundant'
| removeRedundant = isRedundant module'
| otherwise = const False
-
pragmas' = pragmas $ fmap linesFromSrcSpan module'
longest = maximum $ map length $ snd =<< pragmas'
groups = [(b, concat pgs) | (b, pgs) <- groupAdjacent pragmas']
changes =
- [ change b (const $ prettyPragmas columns longest align style pg)
+ [ change b (const $ prettyPragmas lngPrefix columns longest align style pg)
| (b, pg) <- filterRedundant isRedundant' groups
]
--------------------------------------------------------------------------------
-- | Add a LANGUAGE pragma to a module if it is not present already.
-addLanguagePragma :: String -> H.Module H.SrcSpanInfo -> [Change String]
-addLanguagePragma prag modu
+addLanguagePragma :: String -> String -> H.Module H.SrcSpanInfo -> [Change String]
+addLanguagePragma lg prag modu
| prag `elem` present = []
- | otherwise = [insert line ["{-# LANGUAGE " ++ prag ++ " #-}"]]
+ | otherwise = [insert line ["{-# " ++ lg ++ " " ++ prag ++ " #-}"]]
where
pragmas' = pragmas (fmap linesFromSrcSpan modu)
present = concatMap snd pragmas'
@@ -158,7 +152,7 @@ isRedundant _ _ = False
-- | Check if the ViewPatterns language pragma is redundant.
isRedundantViewPatterns :: H.Module H.SrcSpanInfo -> Bool
isRedundantViewPatterns m = null
- [() | H.PViewPat _ _ _ <- everything m :: [H.Pat H.SrcSpanInfo]]
+ [() | H.PViewPat {} <- everything m :: [H.Pat H.SrcSpanInfo]]
--------------------------------------------------------------------------------
diff --git a/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs b/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs
index 924d6c5..5e61123 100644
--- a/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs
+++ b/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs
@@ -108,7 +108,7 @@ fieldDeclToAlignable (H.FieldDecl ann names ty) = Just $ Alignable
--------------------------------------------------------------------------------
-step :: Int -> Config -> Step
+step :: Maybe Int -> Config -> Step
step maxColumns config = makeStep "Cases" $ \ls (module', _) ->
let module'' = fmap H.srcInfoSpan module'
changes search toAlign =
diff --git a/lib/Language/Haskell/Stylish/Step/UnicodeSyntax.hs b/lib/Language/Haskell/Stylish/Step/UnicodeSyntax.hs
index 01e29e8..266e8e5 100644
--- a/lib/Language/Haskell/Stylish/Step/UnicodeSyntax.hs
+++ b/lib/Language/Haskell/Stylish/Step/UnicodeSyntax.hs
@@ -39,12 +39,12 @@ replaceAll :: [(Int, [(Int, String)])] -> [Change String]
replaceAll = map changeLine'
where
changeLine' (r, ns) = changeLine r $ \str -> return $
- flip applyChanges str
+ applyChanges
[ change (Block c ec) (const repl)
| (c, needle) <- sort ns
, let ec = c + length needle - 1
, repl <- maybeToList $ M.lookup needle unicodeReplacements
- ]
+ ] str
--------------------------------------------------------------------------------
@@ -104,15 +104,15 @@ between (startRow, startCol) (endRow, endCol) needle =
--------------------------------------------------------------------------------
-step :: Bool -> Step
-step = makeStep "UnicodeSyntax" . step'
+step :: Bool -> String -> Step
+step = (makeStep "UnicodeSyntax" .) . step'
--------------------------------------------------------------------------------
-step' :: Bool -> Lines -> Module -> Lines
-step' alp ls (module', _) = applyChanges changes ls
+step' :: Bool -> String -> Lines -> Module -> Lines
+step' alp lg ls (module', _) = applyChanges changes ls
where
- changes = (if alp then addLanguagePragma "UnicodeSyntax" module' else []) ++
+ changes = (if alp then addLanguagePragma lg "UnicodeSyntax" module' else []) ++
replaceAll perLine
perLine = sort $ groupPerLine $
typeSigs module' ls ++
diff --git a/lib/Language/Haskell/Stylish/Util.hs b/lib/Language/Haskell/Stylish/Util.hs
index c634043..9883f4b 100644
--- a/lib/Language/Haskell/Stylish/Util.hs
+++ b/lib/Language/Haskell/Stylish/Util.hs
@@ -10,6 +10,8 @@ module Language.Haskell.Stylish.Util
, trimRight
, wrap
, wrapRest
+ , wrapMaybe
+ , wrapRestMaybe
, withHead
, withInit
@@ -99,6 +101,27 @@ wrap maxWidth leading ind = wrap' leading
--------------------------------------------------------------------------------
+wrapMaybe :: Maybe Int -- ^ Maximum line width (maybe)
+ -> String -- ^ Leading string
+ -> Int -- ^ Indentation
+ -> [String] -- ^ Strings to add/wrap
+ -> Lines -- ^ Resulting lines
+wrapMaybe (Just maxWidth) = wrap maxWidth
+wrapMaybe Nothing = noWrap
+
+
+--------------------------------------------------------------------------------
+noWrap :: String -- ^ Leading string
+ -> Int -- ^ Indentation
+ -> [String] -- ^ Strings to add
+ -> Lines -- ^ Resulting lines
+noWrap leading _ind = noWrap' leading
+ where
+ noWrap' ss [] = [ss]
+ noWrap' ss (str:strs) = noWrap' (ss ++ " " ++ str) strs
+
+
+--------------------------------------------------------------------------------
wrapRest :: Int
-> Int
-> [String]
@@ -117,6 +140,29 @@ wrapRest maxWidth ind = reverse . wrapRest' [] ""
--------------------------------------------------------------------------------
+wrapRestMaybe :: Maybe Int
+ -> Int
+ -> [String]
+ -> Lines
+wrapRestMaybe (Just maxWidth) = wrapRest maxWidth
+wrapRestMaybe Nothing = noWrapRest
+
+
+--------------------------------------------------------------------------------
+noWrapRest :: Int
+ -> [String]
+ -> Lines
+noWrapRest ind = reverse . noWrapRest' [] ""
+ where
+ noWrapRest' ls ss []
+ | null ss = ls
+ | otherwise = ss:ls
+ noWrapRest' ls ss (str:strs)
+ | null ss = noWrapRest' ls (indent ind str) strs
+ | otherwise = noWrapRest' ls (ss ++ " " ++ str) strs
+
+
+--------------------------------------------------------------------------------
withHead :: (a -> a) -> [a] -> [a]
withHead _ [] = []
withHead f (x : xs) = f x : xs