diff --git a/elm-format.cabal b/elm-format.cabal index 85caf2e7e..37cd5660e 100644 --- a/elm-format.cabal +++ b/elm-format.cabal @@ -60,6 +60,7 @@ library AST.V0_16 AST.Variable Box + Defaults Elm.Utils ElmFormat.Cli ElmFormat.Parse diff --git a/parser/src/Reporting/Report.hs b/parser/src/Reporting/Report.hs index 3e5d8f34c..8d42672c1 100644 --- a/parser/src/Reporting/Report.hs +++ b/parser/src/Reporting/Report.hs @@ -15,6 +15,7 @@ import System.IO (hPutStr, stderr) import qualified Reporting.Region as R +import Defaults data Report = Report { _title :: String @@ -106,7 +107,7 @@ ansi tipe = messageBar :: Renderer m -> String -> String -> m () messageBar renderer tag location = let - usedSpace = 4 + length tag + 1 + length location + usedSpace = defaultTabSize + length tag + 1 + length location in header renderer $ "-- " ++ tag ++ " " diff --git a/src/Box.hs b/src/Box.hs index d941a38a0..a2103792c 100644 --- a/src/Box.hs +++ b/src/Box.hs @@ -16,7 +16,7 @@ import qualified Data.Text as T A line is ALWAYS just one line. Space is self-explanatory, - Tab aligns to the nearest multiple of 4 spaces, + Tab aligns to the nearest multiple of Config._tabsize spaces, Text brings any string into the data structure, Row joins more of these elements onto one line. -} @@ -183,10 +183,10 @@ xyz myPrefix abcde xyz -} -prefix :: Line -> Box -> Box -prefix pref = +prefix :: Int -> Line -> Box -> Box +prefix tabSize pref = let - prefixLength = lineLength 0 pref + prefixLength = lineLength tabSize 0 pref paddingSpaces = replicate prefixLength space padLineWithSpaces l = row [ row paddingSpaces, l ] addPrefixToLine l = row [ pref, l ] @@ -205,38 +205,38 @@ addSuffix suffix b = |> andThen [ line $ row [ last ls, suffix ] ] -renderLine :: Int -> Line -> T.Text -renderLine startColumn line' = +renderLine :: Int -> Int -> Line -> T.Text +renderLine tabSize startColumn line' = case line' of Text text -> text Space -> T.singleton ' ' Tab -> - T.pack $ replicate (tabLength startColumn) ' ' + T.pack $ replicate (tabLength tabSize startColumn) ' ' Row lines' -> - renderRow startColumn lines' + renderRow tabSize startColumn lines' -render :: Box -> T.Text -render box' = +render :: Int -> Box -> T.Text +render tabSize box' = case box' of SingleLine line' -> - T.snoc (renderLine 0 line') '\n' + T.snoc (renderLine tabSize 0 line') '\n' Stack l1 l2 rest -> - T.unlines $ map (renderLine 0) (l1 : l2 : rest) + T.unlines $ map (renderLine tabSize 0) (l1 : l2 : rest) MustBreak line' -> - T.snoc (renderLine 0 line') '\n' + T.snoc (renderLine tabSize 0 line') '\n' -lineLength :: Int -> Line -> Int -lineLength startColumn line' = +lineLength :: Int -> Int -> Line -> Int +lineLength tabSize startColumn line' = startColumn + case line' of Text string -> T.length string Space -> 1 - Tab -> tabLength startColumn - Row lines' -> rowLength startColumn lines' + Tab -> tabLength tabSize startColumn + Row lines' -> rowLength tabSize startColumn lines' initRow :: Int -> (T.Text, Int) @@ -244,18 +244,13 @@ initRow startColumn = (T.empty, startColumn) -spacesInTab :: Int -spacesInTab = - 4 +spacesToNextTab :: Int -> Int -> Int +spacesToNextTab tabSize startColumn = + startColumn `mod` tabSize - -spacesToNextTab :: Int -> Int -spacesToNextTab startColumn = - startColumn `mod` spacesInTab - -tabLength :: Int -> Int -tabLength startColumn = - spacesInTab - (spacesToNextTab startColumn) +tabLength :: Int -> Int -> Int +tabLength tabSize startColumn = + tabSize - (spacesToNextTab tabSize startColumn) {- What happens here is we take a row and start building its contents @@ -282,31 +277,32 @@ The (T.Text, Int) type here means the (string, column) from the table above. Then we just need to do one final modification to get from endColumn to resultLength, which is what we are after in the function `rowLength`. -} -renderRow' :: Int -> [Line] -> (T.Text, Int) -renderRow' startColumn lines' = +renderRow' :: Int -> Int -> [Line] -> (T.Text, Int) +renderRow' tabSize startColumn lines' = (result, resultLength) where - (result, endColumn) = foldl addLine (initRow startColumn) lines' + addLine' = addLine tabSize + (result, endColumn) = foldl addLine' (initRow startColumn) lines' resultLength = endColumn - startColumn {- A step function for renderRow'. -addLine (" ",1) Tab == (" ",4) +addLine ... (" ",1) Tab == ... (" ",Flags.Config._tabsize) -} -addLine :: (T.Text, Int) -> Line -> (T.Text, Int) -addLine (string, startColumn') line' = +addLine :: Int -> (T.Text, Int) -> Line -> (T.Text, Int) +addLine tabSize (string, startColumn') line' = (newString, newStartColumn) where - newString = T.append string $ renderLine startColumn' line' - newStartColumn = lineLength startColumn' line' + newString = T.append string $ renderLine tabSize startColumn' line' + newStartColumn = lineLength tabSize startColumn' line' -- Extract the final string from renderRow' -renderRow :: Int -> [Line] -> T.Text -renderRow startColumn lines' = - fst $ renderRow' startColumn lines' +renderRow :: Int -> Int -> [Line] -> T.Text +renderRow tabSize startColumn lines' = + fst $ renderRow' tabSize startColumn lines' -- Extract the final length from renderRow' -rowLength :: Int -> [Line] -> Int -rowLength startColumn lines' = - snd $ renderRow' startColumn lines' +rowLength :: Int -> Int -> [Line] -> Int +rowLength tabSize startColumn lines' = + snd $ renderRow' tabSize startColumn lines' diff --git a/src/Defaults.hs b/src/Defaults.hs new file mode 100644 index 000000000..ff4a9e106 --- /dev/null +++ b/src/Defaults.hs @@ -0,0 +1,9 @@ +{-# OPTIONS_GHC -Wall #-} +module Defaults where + + +-- Configurable indentation +-- +-- See: https://github.com/avh4/elm-format/issues/210 +defaultTabSize :: Int +defaultTabSize = 4 diff --git a/src/ElmFormat.hs b/src/ElmFormat.hs index a4838d6cf..30b7397c2 100644 --- a/src/ElmFormat.hs +++ b/src/ElmFormat.hs @@ -37,17 +37,18 @@ import qualified Reporting.Result as Result writeResult :: Operation f => ElmVersion + -> Int -> Destination -> FilePath -> Text.Text -> Result.Result () Syntax.Error AST.Module.Module -> Free f (Maybe Bool) -writeResult elmVersion destination inputFile inputText result = +writeResult elmVersion tabSize destination inputFile inputText result = case result of Result.Result _ (Result.Ok modu) -> let renderedText = - Render.render elmVersion modu + Render.render elmVersion tabSize modu rendered = renderedText |> Text.encodeUtf8 @@ -82,17 +83,17 @@ writeResult elmVersion destination inputFile inputText result = >> return (Just False) -processTextInput :: Operation f => ElmVersion -> Destination -> FilePath -> Text.Text -> Free f (Maybe Bool) -processTextInput elmVersion destination inputFile inputText = +processTextInput :: Operation f => ElmVersion -> Int -> Destination -> FilePath -> Text.Text -> Free f (Maybe Bool) +processTextInput elmVersion tabSize destination inputFile inputText = Parse.parse inputText - |> writeResult elmVersion destination inputFile inputText + |> writeResult elmVersion tabSize destination inputFile inputText -processFileInput :: Operation f => ElmVersion -> FilePath -> Destination -> Free f (Maybe Bool) -processFileInput elmVersion inputFile destination = +processFileInput :: Operation f => ElmVersion -> Int -> FilePath -> Destination -> Free f (Maybe Bool) +processFileInput elmVersion tabSize inputFile destination = do inputText <- Operation.deprecatedIO $ fmap Text.decodeUtf8 $ ByteString.readFile inputFile - processTextInput elmVersion destination inputFile inputText + processTextInput elmVersion tabSize destination inputFile inputText resolveFile :: FileStore f => FilePath -> Free f (Either InputFileMessage [FilePath]) @@ -147,8 +148,8 @@ resolveFiles inputFiles = return $ Right $ concat files -handleFilesInput :: Operation f => ElmVersion -> [FilePath] -> Maybe FilePath -> Bool -> Bool -> Free f (Maybe Bool) -handleFilesInput elmVersion inputFiles outputFile autoYes validateOnly = +handleFilesInput :: Operation f => ElmVersion -> Int -> [FilePath] -> Maybe FilePath -> Bool -> Bool -> Free f (Maybe Bool) +handleFilesInput elmVersion tabSize inputFiles outputFile autoYes validateOnly = do elmFiles <- resolveFiles inputFiles @@ -169,7 +170,7 @@ handleFilesInput elmVersion inputFiles outputFile autoYes validateOnly = do let destination = if validateOnly then ValidateOnly else ToFile realOutputFile' onInfo $ ProcessingFiles [inputFile] - processFileInput elmVersion inputFile destination + processFileInput elmVersion tabSize inputFile destination Right elmFiles -> do when (isJust outputFile) @@ -195,7 +196,7 @@ handleFilesInput elmVersion inputFiles outputFile autoYes validateOnly = in do onInfo $ ProcessingFiles elmFiles - validationResults <- mapM (\file -> processFileInput elmVersion file (dst file)) elmFiles + validationResults <- mapM (\file -> processFileInput elmVersion tabSize file (dst file)) elmFiles return $ foldl merge Nothing validationResults else return Nothing @@ -257,8 +258,8 @@ determineWhatToDoFromConfig config = determineWhatToDo source destination -validate :: Operation f => ElmVersion -> Source -> Free f Bool -validate elmVersion source = +validate :: Operation f => ElmVersion -> Int -> Source -> Free f Bool +validate elmVersion tabSize source = do result <- case source of @@ -268,10 +269,10 @@ validate elmVersion source = Lazy.toStrict input |> Text.decodeUtf8 - |> processTextInput elmVersion ValidateOnly "" + |> processTextInput elmVersion tabSize ValidateOnly "" FromFiles first rest -> - handleFilesInput elmVersion (first:rest) Nothing True True + handleFilesInput elmVersion tabSize (first:rest) Nothing True True case result of Nothing -> @@ -320,6 +321,7 @@ main defaultVersion = do config <- Flags.parse defaultVersion elmFormatVersion experimental let autoYes = Flags._yes config + let tabSize = Flags._tabSize config let elmVersionResult = determineVersion (Flags._elmVersion config) (Flags._upgrade config) case (elmVersionResult, determineWhatToDoFromConfig config) of @@ -336,13 +338,13 @@ main defaultVersion = (Right elmVersion, Right (Validate source)) -> do isSuccess <- - validate elmVersion source + validate elmVersion tabSize source |> Execute.run (Execute.forMachine elmVersion) exit isSuccess (Right elmVersion, Right (FormatInPlace first rest)) -> do - result <- foldFree Execute.forHuman $ handleFilesInput elmVersion (first:rest) Nothing autoYes False + result <- foldFree Execute.forHuman $ handleFilesInput elmVersion tabSize (first:rest) Nothing autoYes False case result of Just False -> exitFailure @@ -352,7 +354,7 @@ main defaultVersion = (Right elmVersion, Right (FormatToFile input output)) -> do - result <- foldFree Execute.forHuman $ handleFilesInput elmVersion [input] (Just output) autoYes False + result <- foldFree Execute.forHuman $ handleFilesInput elmVersion tabSize [input] (Just output) autoYes False case result of Just False -> exitFailure @@ -367,7 +369,7 @@ main defaultVersion = result <- Lazy.toStrict input |> Text.decodeUtf8 - |> processTextInput elmVersion UpdateInPlace "" + |> processTextInput elmVersion tabSize UpdateInPlace "" |> foldFree Execute.forHuman case result of Just False -> @@ -383,7 +385,7 @@ main defaultVersion = result <- Lazy.toStrict input |> Text.decodeUtf8 - |> processTextInput elmVersion (ToFile output) "" + |> processTextInput elmVersion tabSize (ToFile output) "" |> foldFree Execute.forHuman case result of Just False -> diff --git a/src/ElmFormat/Render/Box.hs b/src/ElmFormat/Render/Box.hs index 60c653469..19efafbb6 100644 --- a/src/ElmFormat/Render/Box.hs +++ b/src/ElmFormat/Render/Box.hs @@ -4,6 +4,7 @@ module ElmFormat.Render.Box where import Elm.Utils ((|>)) import Box import ElmVersion (ElmVersion(..)) +import Defaults import AST.V0_16 import qualified AST.Declaration @@ -40,8 +41,8 @@ pleaseReport what details = line $ pleaseReport' what details -surround :: Char -> Char -> Box -> Box -surround left right b = +surround :: Int -> Char -> Char -> Box -> Box +surround tabSize left right b = let left' = punc (left : []) right' = punc (right : []) @@ -52,17 +53,18 @@ surround left right b = _ -> stack1 [ b - |> prefix left' + |> prefix tabSize left' , line $ right' ] -parens :: Box -> Box -parens = surround '(' ')' +parens :: Int -> Box -> Box +parens tabSize = + surround tabSize '(' ')' -formatBinary :: Bool -> Box -> [ ( Bool, Comments, Box, Box ) ] -> Box -formatBinary multiline left ops = +formatBinary :: Int -> Bool -> Box -> [ ( Bool, Comments, Box, Box ) ] -> Box +formatBinary tabSize multiline left ops = case ops of [] -> left @@ -72,15 +74,16 @@ formatBinary multiline left ops = ElmStructure.forceableSpaceSepOrIndented multiline (ElmStructure.spaceSepOrStack left $ concat - [ Maybe.maybeToList $ formatComments comments + [ Maybe.maybeToList $ formatComments tabSize comments , [op] ] ) - [formatBinary multiline next rest] + [formatBinary tabSize multiline next rest] else formatBinary + tabSize multiline - (ElmStructure.forceableSpaceSepOrIndented multiline left [formatCommented' comments id $ ElmStructure.spaceSepOrPrefix op next]) + (ElmStructure.forceableSpaceSepOrIndented multiline left [formatCommented' tabSize comments id $ ElmStructure.spaceSepOrPrefix tabSize op next]) rest @@ -160,8 +163,8 @@ declarationType decl = DComment -formatModuleHeader :: ElmVersion -> AST.Module.Module -> Box -formatModuleHeader elmVersion modu = +formatModuleHeader :: ElmVersion -> Int -> AST.Module.Module -> Box +formatModuleHeader elmVersion tabSize modu = let header = AST.Module.header modu @@ -169,22 +172,22 @@ formatModuleHeader elmVersion modu = moduleLine = case elmVersion of Elm_0_16 -> - formatModuleLine_0_16 header + formatModuleLine_0_16 tabSize header Elm_0_17 -> - formatModuleLine elmVersion header + formatModuleLine elmVersion tabSize header Elm_0_18 -> - formatModuleLine elmVersion header + formatModuleLine elmVersion tabSize header Elm_0_18_Upgrade -> - formatModuleLine elmVersion header + formatModuleLine elmVersion tabSize header docs = - fmap (formatModuleDocs elmVersion) $ RA.drop $ AST.Module.docs modu + fmap (formatModuleDocs elmVersion tabSize) $ RA.drop $ AST.Module.docs modu imports = - formatImports elmVersion modu + formatImports elmVersion tabSize modu mapIf fn m a = case m of @@ -198,32 +201,32 @@ formatModuleHeader elmVersion modu = |> (if null imports then id else andThen imports . andThen [blankLine]) -formatImports :: ElmVersion -> AST.Module.Module -> [Box] -formatImports elmVersion modu = +formatImports :: ElmVersion -> Int -> AST.Module.Module -> [Box] +formatImports elmVersion tabSize modu = let (comments, imports) = AST.Module.imports modu in - [ formatComments comments + [ formatComments tabSize comments |> maybeToList , imports |> Map.assocs - |> fmap (\(name, (pre, method)) -> formatImport elmVersion ((pre, name), method)) + |> fmap (\(name, (pre, method)) -> formatImport elmVersion tabSize ((pre, name), method)) ] |> List.filter (not . List.null) |> List.intersperse [blankLine] |> concat -formatModuleLine_0_16 :: AST.Module.Header -> Box -formatModuleLine_0_16 header = +formatModuleLine_0_16 :: Int -> AST.Module.Header -> Box +formatModuleLine_0_16 tabSize header = let elmVersion = Elm_0_16 formatExports = case AST.Module.exports header of KeywordCommented _ _ value -> - case formatListing (formatDetailedListing elmVersion) value of + case formatListing tabSize (formatDetailedListing elmVersion tabSize) value of Just listing -> listing _ -> @@ -232,10 +235,10 @@ formatModuleLine_0_16 header = whereClause = case AST.Module.exports header of KeywordCommented pre post _ -> - formatCommented (line . keyword) (Commented pre "where" post) + formatCommented tabSize (line . keyword) (Commented pre "where" post) in case - ( formatCommented (line . formatQualifiedUppercaseIdentifier elmVersion) $ AST.Module.name header + ( formatCommented tabSize (line . formatQualifiedUppercaseIdentifier elmVersion) $ AST.Module.name header , formatExports , whereClause ) @@ -258,8 +261,8 @@ formatModuleLine_0_16 header = ] -formatModuleLine :: ElmVersion -> AST.Module.Header -> Box -formatModuleLine elmVersion header = +formatModuleLine :: ElmVersion -> Int -> AST.Module.Header -> Box +formatModuleLine elmVersion tabSize header = let tag = case AST.Module.srcTag header of @@ -268,41 +271,41 @@ formatModuleLine elmVersion header = AST.Module.Port comments -> ElmStructure.spaceSepOrIndented - (formatTailCommented (line . keyword) ("port", comments)) + (formatTailCommented tabSize (line . keyword) ("port", comments)) [ line $ keyword "module" ] AST.Module.Effect comments -> ElmStructure.spaceSepOrIndented - (formatTailCommented (line . keyword) ("effect", comments)) + (formatTailCommented tabSize (line . keyword) ("effect", comments)) [ line $ keyword "module" ] exports list = - case formatListing (formatDetailedListing elmVersion) $ list of + case formatListing tabSize (formatDetailedListing elmVersion tabSize) $ list of Just listing -> listing _ -> pleaseReport "UNEXPECTED MODULE DECLARATION" "empty listing" formatSetting (k, v) = - formatRecordPair elmVersion "=" (line . formatUppercaseIdentifier elmVersion) (k, v, False) + formatRecordPair elmVersion tabSize "=" (line . formatUppercaseIdentifier elmVersion) (k, v, False) formatSettings settings = map formatSetting settings - |> ElmStructure.group True "{" "," "}" False + |> ElmStructure.group tabSize True "{" "," "}" False whereClause = AST.Module.moduleSettings header - |> fmap (formatKeywordCommented "where" formatSettings) + |> fmap (formatKeywordCommented tabSize "where" formatSettings) |> fmap (\x -> [x]) |> Maybe.fromMaybe [] exposingClause = - formatKeywordCommented "exposing" exports $ AST.Module.exports header + formatKeywordCommented tabSize "exposing" exports $ AST.Module.exports header nameClause = case ( tag - , formatCommented (line . formatQualifiedUppercaseIdentifier elmVersion) $ AST.Module.name header + , formatCommented tabSize (line . formatQualifiedUppercaseIdentifier elmVersion) $ AST.Module.name header ) of (SingleLine tag', SingleLine name') -> @@ -323,15 +326,15 @@ formatModuleLine elmVersion header = (whereClause ++ [exposingClause]) -formatModule :: ElmVersion -> AST.Module.Module -> Box -formatModule elmVersion modu = +formatModule :: ElmVersion -> Int -> AST.Module.Module -> Box +formatModule elmVersion tabSize modu = let initialComments' = case AST.Module.initialComments modu of [] -> [] comments -> - (map formatComment comments) + (map (formatComment tabSize) comments) ++ [ blankLine, blankLine ] spaceBeforeBody = @@ -343,14 +346,14 @@ formatModule elmVersion modu = stack1 $ concat [ initialComments' - , [ formatModuleHeader elmVersion modu ] + , [ formatModuleHeader elmVersion tabSize modu ] , List.replicate spaceBeforeBody blankLine - , maybeToList (formatModuleBody 2 elmVersion modu) + , maybeToList (formatModuleBody 2 elmVersion tabSize modu) ] -formatModuleBody :: Int -> ElmVersion -> AST.Module.Module -> Maybe Box -formatModuleBody linesBetween elmVersion modu = +formatModuleBody :: Int -> ElmVersion -> Int -> AST.Module.Module -> Maybe Box +formatModuleBody linesBetween elmVersion tabSize modu = let spacer first second = case (declarationType first, declarationType second) of @@ -389,7 +392,7 @@ formatModuleBody linesBetween elmVersion modu = List.replicate linesBetween blankLine boxes = - intersperseMap spacer (formatDeclaration elmVersion) $ + intersperseMap spacer (formatDeclaration elmVersion tabSize) $ AST.Module.body modu in case boxes of @@ -397,16 +400,16 @@ formatModuleBody linesBetween elmVersion modu = _ -> Just $ stack1 boxes -formatModuleDocs :: ElmVersion -> Markdown.Blocks -> Box -formatModuleDocs elmVersion blocks = +formatModuleDocs :: ElmVersion -> Int -> Markdown.Blocks -> Box +formatModuleDocs elmVersion tabSize blocks = let format :: AST.Module.Module -> String format modu = let box = case - ( formatImports elmVersion modu - , formatModuleBody 1 elmVersion modu + ( formatImports elmVersion tabSize modu + , formatModuleBody 1 elmVersion tabSize modu ) of ( [], Nothing ) -> Nothing @@ -415,7 +418,7 @@ formatModuleDocs elmVersion blocks = ( imports, Just body ) -> Just $ stack1 (imports ++ [blankLine, body]) in box - |> fmap (Text.unpack . Box.render) + |> fmap (Text.unpack . (Box.render tabSize)) |> fromMaybe "" reformat :: String -> Maybe String @@ -448,8 +451,8 @@ formatDocComment docs = |> andThen [ line $ punc "-}" ] -formatImport :: ElmVersion -> AST.Module.UserImport -> Box -formatImport elmVersion (name, method) = +formatImport :: ElmVersion -> Int -> AST.Module.UserImport -> Box +formatImport elmVersion tabSize (name, method) = let as = (AST.Module.alias method) @@ -463,7 +466,7 @@ formatImport elmVersion (name, method) = exposing = formatImportClause - (formatListing (formatDetailedListing elmVersion)) + (formatListing tabSize (formatDetailedListing elmVersion tabSize)) "exposing" (exposingPreKeyword, exposingPostKeywordAndListing) @@ -477,8 +480,8 @@ formatImport elmVersion (name, method) = (preKeyword, (postKeyword, Just listing')) -> case - ( formatHeadCommented (line . keyword) (preKeyword, keyw) - , formatHeadCommented id (postKeyword, listing') + ( formatHeadCommented tabSize (line . keyword) (preKeyword, keyw) + , formatHeadCommented tabSize id (postKeyword, listing') ) of (SingleLine keyword', SingleLine listing'') -> @@ -498,7 +501,7 @@ formatImport elmVersion (name, method) = Just $ pleaseReport "UNEXPECTED IMPORT" "import clause comments with no clause" in case - ( formatHeadCommented (line . formatQualifiedUppercaseIdentifier elmVersion) name + ( formatHeadCommented tabSize (line . formatQualifiedUppercaseIdentifier elmVersion) name , as , exposing ) @@ -601,50 +604,53 @@ formatImport elmVersion (name, method) = ] -formatListing :: (a -> [Box]) -> AST.Variable.Listing a -> Maybe Box -formatListing format listing = +formatListing :: Int -> (a -> [Box]) -> AST.Variable.Listing a -> Maybe Box +formatListing tabSize format listing = case listing of AST.Variable.ClosedListing -> Nothing AST.Variable.OpenListing comments -> - Just $ parens $ formatCommented (line . keyword) $ fmap (const "..") comments + Just $ parens tabSize $ formatCommented tabSize (line . keyword) $ fmap (const "..") comments AST.Variable.ExplicitListing vars multiline -> - Just $ ElmStructure.group False "(" "," ")" multiline $ format vars + Just $ ElmStructure.group tabSize False "(" "," ")" multiline $ format vars -formatDetailedListing :: ElmVersion -> AST.Module.DetailedListing -> [Box] -formatDetailedListing elmVersion listing = +formatDetailedListing :: ElmVersion -> Int -> AST.Module.DetailedListing -> [Box] +formatDetailedListing elmVersion tabSize listing = concat [ formatCommentedMap + tabSize (\name () -> AST.Variable.OpValue name) - (formatVarValue elmVersion) + (formatVarValue elmVersion tabSize) (AST.Module.operators listing) , formatCommentedMap + tabSize (\name (inner, listing) -> AST.Variable.Union (name, inner) listing) - (formatVarValue elmVersion) + (formatVarValue elmVersion tabSize) (AST.Module.types listing) , formatCommentedMap + tabSize (\name () -> AST.Variable.Value name) - (formatVarValue elmVersion) + (formatVarValue elmVersion tabSize) (AST.Module.values listing) ] -formatCommentedMap :: (k -> v -> a) -> (a -> Box) -> AST.Variable.CommentedMap k v -> [Box] -formatCommentedMap construct format values = +formatCommentedMap :: Int -> (k -> v -> a) -> (a -> Box) -> AST.Variable.CommentedMap k v -> [Box] +formatCommentedMap tabSize construct format values = let format' (k, Commented pre v post) - = formatCommented format $ Commented pre (construct k v) post + = formatCommented tabSize format $ Commented pre (construct k v) post in values |> Map.assocs |> map format' -formatVarValue :: ElmVersion -> AST.Variable.Value -> Box -formatVarValue elmVersion aval = +formatVarValue :: ElmVersion -> Int -> AST.Variable.Value -> Box +formatVarValue elmVersion tabSize aval = case aval of AST.Variable.Value val -> line $ formatLowercaseIdentifier elmVersion [] val @@ -655,12 +661,14 @@ formatVarValue elmVersion aval = AST.Variable.Union name listing -> case ( formatListing + tabSize (formatCommentedMap + tabSize (\name () -> name) (line . formatUppercaseIdentifier elmVersion) ) listing - , formatTailCommented (line . formatUppercaseIdentifier elmVersion) name + , formatTailCommented tabSize (line . formatUppercaseIdentifier elmVersion) name , snd name ) of @@ -684,27 +692,27 @@ formatVarValue elmVersion aval = name' -formatDeclaration :: ElmVersion -> AST.Declaration.Decl -> Box -formatDeclaration elmVersion decl = +formatDeclaration :: ElmVersion -> Int -> AST.Declaration.Decl -> Box +formatDeclaration elmVersion tabSize decl = case decl of AST.Declaration.DocComment docs -> - formatModuleDocs elmVersion docs + formatModuleDocs elmVersion tabSize docs AST.Declaration.BodyComment c -> - formatComment c + formatComment tabSize c AST.Declaration.Decl adecl -> case RA.drop adecl of AST.Declaration.Definition name args comments expr -> - formatDefinition elmVersion name args comments expr + formatDefinition elmVersion tabSize name args comments expr AST.Declaration.TypeAnnotation name typ -> - formatTypeAnnotation elmVersion name typ + formatTypeAnnotation elmVersion tabSize name typ AST.Declaration.Datatype nameWithArgs tags -> let ctor (tag,args') = - case allSingles $ map (formatHeadCommented $ formatType' elmVersion ForCtor) args' of + case allSingles $ map (formatHeadCommented tabSize $ formatType' elmVersion tabSize ForCtor) args' of Right args'' -> line $ row $ List.intersperse space $ (formatUppercaseIdentifier elmVersion tag):args'' Left [] -> @@ -717,11 +725,11 @@ formatDeclaration elmVersion decl = ] in case - formatOpenCommentedList ctor tags + formatOpenCommentedList tabSize ctor tags of [] -> error "List can't be empty" first:rest -> - case formatCommented (formatNameWithArgs elmVersion) nameWithArgs of + case formatCommented tabSize (formatNameWithArgs elmVersion tabSize) nameWithArgs of SingleLine nameWithArgs' -> stack1 [ line $ row @@ -730,8 +738,8 @@ formatDeclaration elmVersion decl = , nameWithArgs' ] , first - |> prefix (row [punc "=", space]) - |> andThen (map (prefix (row [punc "|", space])) rest) + |> prefix tabSize (row [punc "=", space]) + |> andThen (map (prefix tabSize (row [punc "|", space])) rest) |> indent ] nameWithArgs' -> @@ -739,35 +747,35 @@ formatDeclaration elmVersion decl = [ line $ keyword "type" , indent $ nameWithArgs' , first - |> prefix (row [punc "=", space]) - |> andThen (map (prefix (row [punc "|", space])) rest) + |> prefix tabSize (row [punc "=", space]) + |> andThen (map (prefix tabSize (row [punc "|", space])) rest) |> indent ] AST.Declaration.TypeAlias preAlias nameWithArgs typ -> ElmStructure.definition "=" True (line $ keyword "type") - [ formatHeadCommented (line . keyword) (preAlias, "alias") - , formatCommented (formatNameWithArgs elmVersion) nameWithArgs + [ formatHeadCommented tabSize (line . keyword) (preAlias, "alias") + , formatCommented tabSize (formatNameWithArgs elmVersion tabSize) nameWithArgs ] - (formatHeadCommentedStack (formatType elmVersion) typ) + (formatHeadCommentedStack tabSize (formatType elmVersion tabSize) typ) AST.Declaration.PortAnnotation name typeComments typ -> ElmStructure.definition ":" False (line $ keyword "port") - [ formatCommented (line . formatLowercaseIdentifier elmVersion []) name ] - (formatCommented' typeComments (formatType elmVersion) typ) + [ formatCommented tabSize (line . formatLowercaseIdentifier elmVersion []) name ] + (formatCommented' tabSize typeComments (formatType elmVersion tabSize) typ) AST.Declaration.PortDefinition name bodyComments expr -> ElmStructure.definition "=" True (line $ keyword "port") - [formatCommented (line . formatLowercaseIdentifier elmVersion []) name] - (formatCommented' bodyComments (formatExpression elmVersion SyntaxSeparated) expr) + [formatCommented tabSize (line . formatLowercaseIdentifier elmVersion []) name] + (formatCommented' tabSize bodyComments (formatExpression elmVersion tabSize SyntaxSeparated) expr) AST.Declaration.Fixity assoc precedenceComments precedence nameComments name -> case - ( formatCommented' nameComments (line . formatInfixVar elmVersion) name - , formatCommented' precedenceComments (line . literal . show) precedence + ( formatCommented' tabSize nameComments (line . formatInfixVar elmVersion) name + , formatCommented' tabSize precedenceComments (line . literal . show) precedence ) of (SingleLine name', SingleLine precedence') -> @@ -785,9 +793,9 @@ formatDeclaration elmVersion decl = pleaseReport "TODO" "multiline fixity declaration" -formatNameWithArgs :: ElmVersion -> (UppercaseIdentifier, [(Comments, LowercaseIdentifier)]) -> Box -formatNameWithArgs elmVersion (name, args) = - case allSingles $ map (formatHeadCommented (line . formatLowercaseIdentifier elmVersion [])) args of +formatNameWithArgs :: ElmVersion -> Int -> (UppercaseIdentifier, [(Comments, LowercaseIdentifier)]) -> Box +formatNameWithArgs elmVersion tabSize (name, args) = + case allSingles $ map (formatHeadCommented tabSize (line . formatLowercaseIdentifier elmVersion [])) args of Right args' -> line $ row $ List.intersperse space $ ((formatUppercaseIdentifier elmVersion name):args') Left args' -> @@ -796,41 +804,42 @@ formatNameWithArgs elmVersion (name, args) = ++ (map indent args') -formatDefinition :: ElmVersion -> AST.Pattern.Pattern +formatDefinition :: ElmVersion -> Int + -> AST.Pattern.Pattern -> [(Comments, AST.Pattern.Pattern)] -> [Comment] -> AST.Expression.Expr -> Box -formatDefinition elmVersion name args comments expr = +formatDefinition elmVersion tabSize name args comments expr = let body = stack1 $ concat - [ map formatComment comments - , [ formatExpression elmVersion SyntaxSeparated expr ] + [ map (formatComment tabSize) comments + , [ formatExpression elmVersion tabSize SyntaxSeparated expr ] ] in ElmStructure.definition "=" True - (formatPattern elmVersion True name) - (map (\(x,y) -> formatCommented' x (formatPattern elmVersion True) y) args) + (formatPattern elmVersion tabSize True name) + (map (\(x,y) -> formatCommented' tabSize x (formatPattern elmVersion tabSize True) y) args) body -formatTypeAnnotation :: ElmVersion -> (AST.Variable.Ref, Comments) -> (Comments, Type) -> Box -formatTypeAnnotation elmVersion name typ = +formatTypeAnnotation :: ElmVersion -> Int -> (AST.Variable.Ref, Comments) -> (Comments, Type) -> Box +formatTypeAnnotation elmVersion tabSize name typ = ElmStructure.definition ":" False - (formatTailCommented (line . formatVar elmVersion) name) + (formatTailCommented tabSize (line . formatVar elmVersion) name) [] - (formatHeadCommented (formatType elmVersion) typ) + (formatHeadCommented tabSize (formatType elmVersion tabSize) typ) -formatPattern :: ElmVersion -> Bool -> AST.Pattern.Pattern -> Box -formatPattern elmVersion parensRequired apattern = +formatPattern :: ElmVersion -> Int -> Bool -> AST.Pattern.Pattern -> Box +formatPattern elmVersion tabSize parensRequired apattern = case RA.drop apattern of AST.Pattern.Anything -> line $ keyword "_" AST.Pattern.UnitPattern comments -> - formatUnit '(' ')' comments + formatUnit tabSize '(' ')' comments AST.Pattern.Literal lit -> formatLiteral lit @@ -848,14 +857,17 @@ formatPattern elmVersion parensRequired apattern = , preOp , line $ punc "::" , formatCommented - (formatEolCommented $ formatPattern elmVersion True) + tabSize + (formatEolCommented tabSize $ formatPattern elmVersion tabSize True) (Commented postOp (term, eol) []) ) in - formatBinary False - (formatEolCommented (formatPattern elmVersion True) first) + formatBinary + tabSize + False + (formatEolCommented tabSize (formatPattern elmVersion tabSize True) first) (map formatRight rest) - |> if parensRequired then parens else id + |> if parensRequired then parens tabSize else id AST.Pattern.Data ctor [] -> line (formatQualifiedUppercaseIdentifier elmVersion ctor) @@ -864,7 +876,7 @@ formatPattern elmVersion parensRequired apattern = (Elm_0_16, [_]) -> id (Elm_0_16, _) -> - if parensRequired then parens else id + if parensRequired then parens tabSize else id _ -> id @@ -872,29 +884,29 @@ formatPattern elmVersion parensRequired apattern = ElmStructure.application (FAJoinFirst JoinAll) (line $ formatQualifiedUppercaseIdentifier elmVersion ctor) - (map (formatHeadCommented $ formatPattern elmVersion True) patterns) - |> if parensRequired then parens else id + (map (formatHeadCommented tabSize $ formatPattern elmVersion tabSize True) patterns) + |> if parensRequired then parens tabSize else id AST.Pattern.PatternParens pattern -> - formatCommented (formatPattern elmVersion False) pattern - |> parens + formatCommented tabSize (formatPattern elmVersion tabSize False) pattern + |> parens tabSize AST.Pattern.Tuple patterns -> - ElmStructure.group True "(" "," ")" False $ map (formatCommented $ formatPattern elmVersion False) patterns + ElmStructure.group tabSize True "(" "," ")" False $ map (formatCommented tabSize $ formatPattern elmVersion tabSize False) patterns AST.Pattern.EmptyListPattern comments -> - formatUnit '[' ']' comments + formatUnit tabSize '[' ']' comments AST.Pattern.List patterns -> - ElmStructure.group True "[" "," "]" False $ map (formatCommented $ formatPattern elmVersion False) patterns + ElmStructure.group tabSize True "[" "," "]" False $ map (formatCommented tabSize $ formatPattern elmVersion tabSize False) patterns AST.Pattern.Record fields -> - ElmStructure.group True "{" "," "}" False $ map (formatCommented $ line . formatLowercaseIdentifier elmVersion []) fields + ElmStructure.group tabSize True "{" "," "}" False $ map (formatCommented tabSize $ line . formatLowercaseIdentifier elmVersion []) fields AST.Pattern.Alias pattern name -> case - ( formatTailCommented (formatPattern elmVersion True) pattern - , formatHeadCommented (line . formatLowercaseIdentifier elmVersion []) name + ( formatTailCommented tabSize (formatPattern elmVersion tabSize True) pattern + , formatHeadCommented tabSize (line . formatLowercaseIdentifier elmVersion []) name ) of (SingleLine pattern', SingleLine name') -> @@ -913,29 +925,29 @@ formatPattern elmVersion parensRequired apattern = , indent name' ] - |> (if parensRequired then parens else id) + |> (if parensRequired then parens tabSize else id) -formatRecordPair :: ElmVersion -> String -> (v -> Box) -> (Commented LowercaseIdentifier, Commented v, Bool) -> Box -formatRecordPair elmVersion delim formatValue (Commented pre k postK, v, forceMultiline) = +formatRecordPair :: ElmVersion -> Int -> String -> (v -> Box) -> (Commented LowercaseIdentifier, Commented v, Bool) -> Box +formatRecordPair elmVersion tabSize delim formatValue (Commented pre k postK, v, forceMultiline) = ElmStructure.equalsPair delim forceMultiline - (formatCommented (line . formatLowercaseIdentifier elmVersion []) $ Commented [] k postK) - (formatCommented formatValue v) - |> (\x -> Commented pre x []) |> formatCommented id + (formatCommented tabSize (line . formatLowercaseIdentifier elmVersion []) $ Commented [] k postK) + (formatCommented tabSize formatValue v) + |> (\x -> Commented pre x []) |> formatCommented tabSize id -formatPair :: (a -> Line) -> String -> (b -> Box) -> Pair a b -> Box -formatPair formatA delim formatB (Pair a b (ForceMultiline forceMultiline)) = +formatPair :: Int -> (a -> Line) -> String -> (b -> Box) -> Pair a b -> Box +formatPair tabSize formatA delim formatB (Pair a b (ForceMultiline forceMultiline)) = ElmStructure.equalsPair delim forceMultiline - (formatTailCommented (line . formatA) a) - (formatHeadCommented formatB b) + (formatTailCommented tabSize (line . formatA) a) + (formatHeadCommented tabSize formatB b) -negativeCasePatternWorkaround :: Commented AST.Pattern.Pattern -> Box -> Box -negativeCasePatternWorkaround (Commented _ (RA.A _ pattern) _) = +negativeCasePatternWorkaround :: Int -> Commented AST.Pattern.Pattern -> Box -> Box +negativeCasePatternWorkaround tabSize (Commented _ (RA.A _ pattern) _) = case pattern of - AST.Pattern.Literal (IntNum i _) | i < 0 -> parens - AST.Pattern.Literal (FloatNum f _) | f < 0 -> parens + AST.Pattern.Literal (IntNum i _) | i < 0 -> parens tabSize + AST.Pattern.Literal (FloatNum f _) | f < 0 -> parens tabSize _ -> id @@ -946,20 +958,20 @@ data ExpressionContext | AmbiguousEnd -expressionParens :: ExpressionContext -> ExpressionContext -> Box -> Box -expressionParens inner outer = +expressionParens :: Int -> ExpressionContext -> ExpressionContext -> Box -> Box +expressionParens tabSize inner outer = case (inner, outer) of - (SpaceSeparated, SpaceSeparated) -> parens - (InfixSeparated, SpaceSeparated) -> parens - (InfixSeparated, InfixSeparated) -> parens - (AmbiguousEnd, SpaceSeparated) -> parens - (AmbiguousEnd, InfixSeparated) -> parens - (InfixSeparated, AmbiguousEnd) -> parens + (SpaceSeparated, SpaceSeparated) -> parens tabSize + (InfixSeparated, SpaceSeparated) -> parens tabSize + (InfixSeparated, InfixSeparated) -> parens tabSize + (AmbiguousEnd, SpaceSeparated) -> parens tabSize + (AmbiguousEnd, InfixSeparated) -> parens tabSize + (InfixSeparated, AmbiguousEnd) -> parens tabSize _ -> id -formatExpression :: ElmVersion -> ExpressionContext -> AST.Expression.Expr -> Box -formatExpression elmVersion context aexpr = +formatExpression :: ElmVersion -> Int -> ExpressionContext -> AST.Expression.Expr -> Box +formatExpression elmVersion tabSize context aexpr = case RA.drop aexpr of AST.Expression.Literal lit -> formatLiteral lit @@ -969,32 +981,32 @@ formatExpression elmVersion context aexpr = AST.Expression.Range left right multiline -> case elmVersion of - Elm_0_16 -> formatRange_0_17 elmVersion left right multiline - Elm_0_17 -> formatRange_0_17 elmVersion left right multiline - Elm_0_18 -> formatRange_0_17 elmVersion left right multiline - Elm_0_18_Upgrade -> formatRange_0_18 elmVersion context left right + Elm_0_16 -> formatRange_0_17 elmVersion tabSize left right multiline + Elm_0_17 -> formatRange_0_17 elmVersion tabSize left right multiline + Elm_0_18 -> formatRange_0_17 elmVersion tabSize left right multiline + Elm_0_18_Upgrade -> formatRange_0_18 elmVersion tabSize context left right AST.Expression.ExplicitList exprs trailing multiline -> - formatSequence '[' ',' (Just ']') - (formatExpression elmVersion SyntaxSeparated) + formatSequence tabSize '[' ',' (Just ']') + (formatExpression elmVersion tabSize SyntaxSeparated) multiline trailing exprs AST.Expression.Binops left ops multiline -> case elmVersion of - Elm_0_16 -> formatBinops_0_17 elmVersion left ops multiline - Elm_0_17 -> formatBinops_0_17 elmVersion left ops multiline - Elm_0_18 -> formatBinops_0_17 elmVersion left ops multiline - Elm_0_18_Upgrade -> formatBinops_0_18 elmVersion left ops multiline - |> expressionParens InfixSeparated context + Elm_0_16 -> formatBinops_0_17 elmVersion tabSize left ops multiline + Elm_0_17 -> formatBinops_0_17 elmVersion tabSize left ops multiline + Elm_0_18 -> formatBinops_0_17 elmVersion tabSize left ops multiline + Elm_0_18_Upgrade -> formatBinops_0_18 elmVersion tabSize left ops multiline + |> expressionParens tabSize InfixSeparated context AST.Expression.Lambda patterns bodyComments expr multiline -> case ( multiline - , allSingles $ map (formatCommented (formatPattern elmVersion True) . (\(c,p) -> Commented c p [])) patterns + , allSingles $ map (formatCommented tabSize (formatPattern elmVersion tabSize True) . (\(c,p) -> Commented c p [])) patterns , bodyComments == [] - , formatExpression elmVersion SyntaxSeparated expr + , formatExpression elmVersion tabSize SyntaxSeparated expr ) of (False, Right patterns', True, SingleLine expr') -> @@ -1015,30 +1027,30 @@ formatExpression elmVersion context aexpr = , punc "->" ] , indent $ stack1 $ - (map formatComment bodyComments) + (map (formatComment tabSize) bodyComments) ++ [ expr' ] ] (_, Left [], _, _) -> pleaseReport "UNEXPECTED LAMBDA" "no patterns" (_, Left patterns', _, expr') -> stack1 - [ prefix (punc "\\") $ stack1 patterns' + [ prefix tabSize (punc "\\") $ stack1 patterns' , line $ punc "->" , indent $ stack1 $ - (map formatComment bodyComments) + (map (formatComment tabSize) bodyComments) ++ [ expr' ] ] - |> expressionParens AmbiguousEnd context + |> expressionParens tabSize AmbiguousEnd context AST.Expression.Unary AST.Expression.Negative e -> - prefix (punc "-") $ formatExpression elmVersion SpaceSeparated e -- TODO: This might need something stronger than SpaceSeparated? + prefix tabSize (punc "-") $ formatExpression elmVersion tabSize SpaceSeparated e -- TODO: This might need something stronger than SpaceSeparated? AST.Expression.App left args multiline -> ElmStructure.application multiline - (formatExpression elmVersion InfixSeparated left) - (map (\(x,y) -> formatCommented' x (formatExpression elmVersion SpaceSeparated) y) args) - |> expressionParens SpaceSeparated context + (formatExpression elmVersion tabSize InfixSeparated left) + (map (\(x,y) -> formatCommented' tabSize x (formatExpression elmVersion tabSize SpaceSeparated) y) args) + |> expressionParens tabSize SpaceSeparated context AST.Expression.If if' elseifs (elsComments, els) -> let @@ -1061,14 +1073,14 @@ formatExpression elmVersion context aexpr = formatIf (cond, body) = stack1 - [ opening (line $ keyword "if") $ formatCommented (formatExpression elmVersion SyntaxSeparated) cond - , indent $ formatCommented_ True (formatExpression elmVersion SyntaxSeparated) body + [ opening (line $ keyword "if") $ formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated) cond + , indent $ formatCommented_ tabSize True (formatExpression elmVersion tabSize SyntaxSeparated) body ] formatElseIf (ifComments, (cond, body)) = let key = - case (formatHeadCommented id (ifComments, line $ keyword "if")) of + case (formatHeadCommented tabSize id (ifComments, line $ keyword "if")) of SingleLine key' -> line $ row [ keyword "else", space, key' ] key' -> @@ -1079,8 +1091,8 @@ formatExpression elmVersion context aexpr = in stack1 [ blankLine - , opening key $ formatCommented (formatExpression elmVersion SyntaxSeparated) cond - , indent $ formatCommented_ True (formatExpression elmVersion SyntaxSeparated) body + , opening key $ formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated) cond + , indent $ formatCommented_ tabSize True (formatExpression elmVersion tabSize SyntaxSeparated) body ] in formatIf if' @@ -1088,9 +1100,9 @@ formatExpression elmVersion context aexpr = |> andThen [ blankLine , line $ keyword "else" - , indent $ formatCommented_ True (formatExpression elmVersion SyntaxSeparated) (Commented elsComments els []) + , indent $ formatCommented_ tabSize True (formatExpression elmVersion tabSize SyntaxSeparated) (Commented elsComments els []) ] - |> expressionParens AmbiguousEnd context + |> expressionParens tabSize AmbiguousEnd context AST.Expression.Let defs bodyComments expr -> let @@ -1104,13 +1116,12 @@ formatExpression elmVersion context aexpr = formatDefinition' def = case def of AST.Expression.LetDefinition name args comments expr' -> - formatDefinition elmVersion name args comments expr' - + formatDefinition elmVersion tabSize name args comments expr' AST.Expression.LetAnnotation name typ -> - formatTypeAnnotation elmVersion name typ + formatTypeAnnotation elmVersion tabSize name typ AST.Expression.LetComment comment -> - formatComment comment + (formatComment tabSize) comment in (line $ keyword "let") |> andThen @@ -1121,17 +1132,17 @@ formatExpression elmVersion context aexpr = |> andThen [ line $ keyword "in" , stack1 $ - (map formatComment bodyComments) - ++ [formatExpression elmVersion SyntaxSeparated expr] + (map (formatComment tabSize) bodyComments) + ++ [formatExpression elmVersion tabSize SyntaxSeparated expr] ] - |> expressionParens AmbiguousEnd context -- TODO: not tested + |> expressionParens tabSize AmbiguousEnd context -- TODO: not tested AST.Expression.Case (subject,multiline) clauses -> let opening = case ( multiline - , formatCommented (formatExpression elmVersion SyntaxSeparated) subject + , formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated) subject ) of (False, SingleLine subject') -> @@ -1152,11 +1163,11 @@ formatExpression elmVersion context aexpr = clause (pat, expr) = case ( pat - , (formatPattern elmVersion False $ (\(Commented _ x _) -> x) pat) - |> negativeCasePatternWorkaround pat - , formatCommentedStack (formatPattern elmVersion False) pat - |> negativeCasePatternWorkaround pat - , formatHeadCommentedStack (formatExpression elmVersion SyntaxSeparated) expr + , (formatPattern elmVersion tabSize False $ (\(Commented _ x _) -> x) pat) + |> negativeCasePatternWorkaround tabSize pat + , formatCommentedStack tabSize (formatPattern elmVersion tabSize False) pat + |> negativeCasePatternWorkaround tabSize pat + , formatHeadCommentedStack tabSize (formatExpression elmVersion tabSize SyntaxSeparated) expr ) of (_, _, SingleLine pat', body') -> @@ -1166,7 +1177,7 @@ formatExpression elmVersion context aexpr = ] (Commented pre _ [], SingleLine pat', _, body') -> stack1 $ - (map formatComment pre) + (map (formatComment tabSize) pre) ++ [ line $ row [ pat', space, keyword "->"] , indent body' ] @@ -1184,16 +1195,16 @@ formatExpression elmVersion context aexpr = |> List.intersperse blankLine |> map indent ) - |> expressionParens AmbiguousEnd context -- TODO: not tested + |> expressionParens tabSize AmbiguousEnd context -- TODO: not tested AST.Expression.Tuple exprs multiline -> - ElmStructure.group True "(" "," ")" multiline $ map (formatCommented (formatExpression elmVersion SyntaxSeparated)) exprs + ElmStructure.group tabSize True "(" "," ")" multiline $ map (formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated)) exprs AST.Expression.TupleFunction n -> line $ keyword $ "(" ++ (List.replicate (n-1) ',') ++ ")" AST.Expression.Access expr field -> - formatExpression elmVersion SpaceSeparated expr -- TODO: does this need a different context than SpaceSeparated? + formatExpression elmVersion tabSize SpaceSeparated expr -- TODO: does this need a different context than SpaceSeparated? |> addSuffix (row $ [punc ".", formatLowercaseIdentifier elmVersion [] field]) AST.Expression.AccessFunction (LowercaseIdentifier field) -> @@ -1201,24 +1212,25 @@ formatExpression elmVersion context aexpr = AST.Expression.Record base fields trailing multiline -> formatRecordLike + tabSize (line . formatLowercaseIdentifier elmVersion []) (formatLowercaseIdentifier elmVersion []) "=" - (formatExpression elmVersion SyntaxSeparated) + (formatExpression elmVersion tabSize SyntaxSeparated) base fields trailing multiline AST.Expression.Parens expr -> case expr of Commented [] expr' [] -> - formatExpression elmVersion context expr' + formatExpression elmVersion tabSize context expr' _ -> - formatCommented (formatExpression elmVersion SyntaxSeparated) expr - |> parens + formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated) expr + |> parens tabSize AST.Expression.Unit comments -> - formatUnit '(' ')' comments + formatUnit tabSize '(' ')' comments AST.Expression.GLShader src -> line $ row @@ -1229,47 +1241,53 @@ formatExpression elmVersion context aexpr = formatRecordLike :: - (base -> Box) -> (key -> Line) -> String -> (value -> Box) + Int + -> (base -> Box) -> (key -> Line) -> String -> (value -> Box) -> Maybe (Commented base) -> Sequence (Pair key value)-> Comments -> ForceMultiline -> Box -formatRecordLike formatBase formatKey fieldSep formatValue base' fields trailing multiline = +formatRecordLike tabSize formatBase formatKey fieldSep formatValue base' fields trailing multiline = case (base', fields) of ( Just base, pairs' ) -> ElmStructure.extensionGroup' + tabSize ((\(ForceMultiline b) -> b) multiline) - (formatCommented formatBase base) - (formatSequence '|' ',' Nothing - (formatPair formatKey fieldSep formatValue) + (formatCommented tabSize formatBase base) + (formatSequence + tabSize + '|' ',' Nothing + (formatPair tabSize formatKey fieldSep formatValue) multiline trailing pairs') ( Nothing, pairs' ) -> - formatSequence '{' ',' (Just '}') - (formatPair formatKey fieldSep formatValue) + formatSequence + tabSize + '{' ',' (Just '}') + (formatPair tabSize formatKey fieldSep formatValue) multiline trailing pairs' -formatSequence :: Char -> Char -> Maybe Char -> (a -> Box) -> ForceMultiline -> Comments -> Sequence a -> Box -formatSequence left delim right formatA (ForceMultiline multiline) trailing (first:rest) = +formatSequence :: Int -> Char -> Char -> Maybe Char -> (a -> Box) -> ForceMultiline -> Comments -> Sequence a -> Box +formatSequence tabSize left delim right formatA (ForceMultiline multiline) trailing (first:rest) = let formatItem delim (pre, item) = - maybe id (stack' . stack' blankLine) (formatComments pre) $ - prefix (row [ punc [delim], space ]) $ - formatHeadCommented (formatEolCommented formatA) item + maybe id (stack' . stack' blankLine) (formatComments tabSize pre) $ + prefix tabSize (row [ punc [delim], space ]) $ + formatHeadCommented tabSize (formatEolCommented tabSize formatA) item in ElmStructure.forceableSpaceSepOrStack multiline (ElmStructure.forceableRowOrStack multiline (formatItem left first) (map (formatItem delim) rest) ) - (maybe [] (flip (:) [] . stack' blankLine) (formatComments trailing) ++ (Maybe.maybeToList $ fmap (line . punc . flip (:) []) right)) -formatSequence left _ (Just right) _ _ trailing [] = - formatUnit left right trailing -formatSequence left _ Nothing _ _ trailing [] = - formatUnit left ' ' trailing + (maybe [] (flip (:) [] . stack' blankLine) (formatComments tabSize trailing) ++ (Maybe.maybeToList $ fmap (line . punc . flip (:) []) right)) +formatSequence tabSize left _ (Just right) _ _ trailing [] = + formatUnit tabSize left right trailing +formatSequence tabSize left _ Nothing _ _ trailing [] = + formatUnit tabSize left ' ' trailing mapIsLast :: (Bool -> a -> b) -> [a] -> [b] @@ -1280,22 +1298,24 @@ mapIsLast f (next:rest) = f False next : mapIsLast f rest formatBinops_0_17 :: ElmVersion + -> Int -> AST.Expression.Expr -> [(Comments, AST.Variable.Ref, Comments, AST.Expression.Expr)] -> Bool -> Box -formatBinops_0_17 elmVersion left ops multiline = - formatBinops_common (,) elmVersion left ops multiline +formatBinops_0_17 elmVersion tabSize left ops multiline = + formatBinops_common (,) elmVersion tabSize left ops multiline formatBinops_0_18 :: ElmVersion + -> Int -> AST.Expression.Expr -> [(Comments, AST.Variable.Ref, Comments, AST.Expression.Expr)] -> Bool -> Box -formatBinops_0_18 elmVersion left ops multiline = - formatBinops_common removeBackticks elmVersion left ops multiline +formatBinops_0_18 elmVersion tabSize left ops multiline = + formatBinops_common removeBackticks elmVersion tabSize left ops multiline formatBinops_common :: @@ -1306,11 +1326,12 @@ formatBinops_common :: ) ) -> ElmVersion + -> Int -> AST.Expression.Expr -> [(Comments, AST.Variable.Ref, Comments, AST.Expression.Expr)] -> Bool -> Box -formatBinops_common transform elmVersion left ops multiline = +formatBinops_common transform elmVersion tabSize left ops multiline = let (left', ops') = transform left ops @@ -1327,12 +1348,13 @@ formatBinops_common transform elmVersion left ops multiline = ( isLeftPipe , po , (line . formatInfixVar elmVersion) o - , formatCommented' pe (formatExpression elmVersion formatContext) e + , formatCommented' tabSize pe (formatExpression elmVersion tabSize formatContext) e ) in formatBinary + tabSize multiline - (formatExpression elmVersion InfixSeparated left') + (formatExpression elmVersion tabSize InfixSeparated left') (mapIsLast formatPair ops') @@ -1378,12 +1400,12 @@ removeBackticks left ops = (left, (pre, op, post, e'):rest') -formatRange_0_17 :: ElmVersion -> Commented AST.Expression.Expr -> Commented AST.Expression.Expr -> Bool -> Box -formatRange_0_17 elmVersion left right multiline = +formatRange_0_17 :: ElmVersion -> Int -> Commented AST.Expression.Expr -> Commented AST.Expression.Expr -> Bool -> Box +formatRange_0_17 elmVersion tabSize left right multiline = case ( multiline - , formatCommented (formatExpression elmVersion SyntaxSeparated) left - , formatCommented (formatExpression elmVersion SyntaxSeparated) right + , formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated) left + , formatCommented tabSize (formatExpression elmVersion tabSize SyntaxSeparated) right ) of (False, SingleLine left', SingleLine right') -> @@ -1412,8 +1434,8 @@ noRegion :: a -> RA.Located a noRegion = RA.at nowhere nowhere -formatRange_0_18 :: ElmVersion -> ExpressionContext -> Commented AST.Expression.Expr -> Commented AST.Expression.Expr -> Box -formatRange_0_18 elmVersion context left right = +formatRange_0_18 :: ElmVersion -> Int -> ExpressionContext -> Commented AST.Expression.Expr -> Commented AST.Expression.Expr -> Box +formatRange_0_18 elmVersion tabSize context left right = case (left, right) of (Commented preLeft left' [], Commented preRight right' []) -> AST.Expression.App @@ -1423,7 +1445,7 @@ formatRange_0_18 elmVersion context left right = ] (FAJoinFirst JoinAll) |> noRegion - |> formatExpression elmVersion context + |> formatExpression elmVersion tabSize context _ -> AST.Expression.App @@ -1433,21 +1455,21 @@ formatRange_0_18 elmVersion context left right = ] (FAJoinFirst JoinAll) |> noRegion - |> formatExpression elmVersion context + |> formatExpression elmVersion tabSize context -formatUnit :: Char -> Char -> Comments -> Box -formatUnit left right comments = +formatUnit :: Int -> Char -> Char -> Comments -> Box +formatUnit tabSize left right comments = case (left, comments) of (_, []) -> line $ punc (left : right : []) ('{', (LineComment _):_) -> - surround left right $ prefix space $ stack1 $ map formatComment comments + surround tabSize left right $ prefix tabSize space $ stack1 $ map (formatComment tabSize) comments _ -> - surround left right $ - case allSingles $ map formatComment comments of + surround tabSize left right $ + case allSingles $ map (formatComment tabSize) comments of Right comments' -> line $ row $ List.intersperse space comments' @@ -1455,9 +1477,9 @@ formatUnit left right comments = stack1 comments' -formatComments :: Comments -> Maybe Box -formatComments comments = - case fmap formatComment comments of +formatComments :: Int -> Comments -> Maybe Box +formatComments tabSize comments = + case fmap (formatComment tabSize) comments of [] -> Nothing @@ -1465,75 +1487,75 @@ formatComments comments = Just $ ElmStructure.spaceSepOrStack first rest -formatCommented_ :: Bool -> (a -> Box) -> Commented a -> Box -formatCommented_ forceMultiline format (Commented pre inner post) = +formatCommented_ :: Int -> Bool -> (a -> Box) -> Commented a -> Box +formatCommented_ tabSize forceMultiline format (Commented pre inner post) = ElmStructure.forceableSpaceSepOrStack1 forceMultiline $ concat - [ Maybe.maybeToList $ formatComments pre + [ Maybe.maybeToList $ (formatComments tabSize) pre , [format inner] - , Maybe.maybeToList $ formatComments post + , Maybe.maybeToList $ (formatComments tabSize) post ] -formatCommented :: (a -> Box) -> Commented a -> Box -formatCommented = - formatCommented_ False +formatCommented :: Int -> (a -> Box) -> Commented a -> Box +formatCommented tabSize = + formatCommented_ tabSize False -- TODO: rename to formatPreCommented -formatHeadCommented :: (a -> Box) -> (Comments, a) -> Box -formatHeadCommented format (pre, inner) = - formatCommented' pre format inner +formatHeadCommented :: Int -> (a -> Box) -> (Comments, a) -> Box +formatHeadCommented tabSize format (pre, inner) = + formatCommented' tabSize pre format inner -formatCommented' :: Comments -> (a -> Box) -> a -> Box -formatCommented' pre format inner = - formatCommented format (Commented pre inner []) +formatCommented' :: Int -> Comments -> (a -> Box) -> a -> Box +formatCommented' tabSize pre format inner = + formatCommented tabSize format (Commented pre inner []) -formatTailCommented :: (a -> Box) -> (a, Comments) -> Box -formatTailCommented format (inner, post) = - formatCommented format (Commented [] inner post) +formatTailCommented :: Int -> (a -> Box) -> (a, Comments) -> Box +formatTailCommented tabSize format (inner, post) = + formatCommented tabSize format (Commented [] inner post) -formatEolCommented :: (a -> Box) -> WithEol a -> Box -formatEolCommented format (inner, post) = +formatEolCommented :: Int -> (a -> Box) -> WithEol a -> Box +formatEolCommented tabSize format (inner, post) = case (post, format inner) of (Nothing, box) -> box (Just eol, SingleLine result) -> mustBreak $ row [ result, space, punc "--", literal eol ] (Just eol, box) -> - stack1 [ box, formatComment $ LineComment eol ] + stack1 [ box, formatComment tabSize $ LineComment eol ] -formatCommentedStack :: (a -> Box) -> Commented a -> Box -formatCommentedStack format (Commented pre inner post) = +formatCommentedStack :: Int -> (a -> Box) -> Commented a -> Box +formatCommentedStack tabSize format (Commented pre inner post) = stack1 $ - (map formatComment pre) + (map (formatComment tabSize) pre) ++ [ format inner ] - ++ (map formatComment post) + ++ (map (formatComment tabSize) post) -formatHeadCommentedStack :: (a -> Box) -> (Comments, a) -> Box -formatHeadCommentedStack format (pre, inner) = - formatCommentedStack format (Commented pre inner []) +formatHeadCommentedStack :: Int -> (a -> Box) -> (Comments, a) -> Box +formatHeadCommentedStack tabSize format (pre, inner) = + formatCommentedStack tabSize format (Commented pre inner []) -formatKeywordCommented :: String -> (a -> Box) -> KeywordCommented a -> Box -formatKeywordCommented word format (KeywordCommented pre post value) = +formatKeywordCommented :: Int -> String -> (a -> Box) -> KeywordCommented a -> Box +formatKeywordCommented tabSize word format (KeywordCommented pre post value) = ElmStructure.spaceSepOrIndented - (formatCommented (line . keyword) (Commented pre word post)) + (formatCommented tabSize (line . keyword) (Commented pre word post)) [ format value ] -formatOpenCommentedList :: (a -> Box) -> OpenCommentedList a -> [Box] -formatOpenCommentedList format (OpenCommentedList rest (preLst, lst)) = - (fmap (formatCommented $ formatEolCommented format) rest) - ++ [formatCommented (formatEolCommented format) $ Commented preLst lst []] +formatOpenCommentedList :: Int -> (a -> Box) -> OpenCommentedList a -> [Box] +formatOpenCommentedList tabSize format (OpenCommentedList rest (preLst, lst)) = + (fmap (formatCommented tabSize $ formatEolCommented tabSize format) rest) + ++ [formatCommented tabSize (formatEolCommented tabSize format) $ Commented preLst lst []] -formatComment :: Comment -> Box -formatComment comment = +formatComment :: Int -> Comment -> Box +formatComment tabSize comment = case comment of BlockComment c -> case c of @@ -1550,6 +1572,7 @@ formatComment comment = ls -> stack1 [ prefix + tabSize (row [ punc "{-", space ]) (stack1 $ map (line . literal) ls) , line $ punc "-}" @@ -1680,9 +1703,9 @@ data TypeParensRequired deriving (Eq) -formatType :: ElmVersion -> Type -> Box -formatType elmVersion = - formatType' elmVersion NotRequired +formatType :: ElmVersion -> Int -> Type -> Box +formatType elmVersion tabSize = + formatType' elmVersion tabSize NotRequired commaSpace :: Line @@ -1703,11 +1726,11 @@ formatTypeConstructor elmVersion ctor = line $ keyword $ "(" ++ (List.replicate (n-1) ',') ++ ")" -formatType' :: ElmVersion -> TypeParensRequired -> Type -> Box -formatType' elmVersion requireParens atype = +formatType' :: ElmVersion -> Int -> TypeParensRequired -> Type -> Box +formatType' elmVersion tabSize requireParens atype = case RA.drop atype of UnitType comments -> - formatUnit '(' ')' comments + formatUnit tabSize '(' ')' comments FunctionType first rest (ForceMultiline forceMultiline) -> let @@ -1715,11 +1738,12 @@ formatType' elmVersion requireParens atype = ElmStructure.forceableSpaceSepOrStack1 False $ concat - [ Maybe.maybeToList $ formatComments preOp + [ Maybe.maybeToList $ formatComments tabSize preOp , [ ElmStructure.prefixOrIndented (line $ punc "->") (formatCommented - (formatEolCommented $ formatType' elmVersion ForLambda) + tabSize + (formatEolCommented tabSize $ formatType' elmVersion tabSize ForLambda) (Commented postOp (term, eol) []) ) ] @@ -1727,9 +1751,9 @@ formatType' elmVersion requireParens atype = in ElmStructure.forceableSpaceSepOrStack forceMultiline - (formatEolCommented (formatType' elmVersion ForLambda) first) + (formatEolCommented tabSize (formatType' elmVersion tabSize ForLambda) first) (map formatRight rest) - |> if requireParens /= NotRequired then parens else id + |> if requireParens /= NotRequired then parens tabSize else id TypeVariable var -> line $ identifier $ formatVarName elmVersion var @@ -1738,21 +1762,22 @@ formatType' elmVersion requireParens atype = ElmStructure.application (FAJoinFirst JoinAll) (formatTypeConstructor elmVersion ctor) - (map (formatHeadCommented $ formatType' elmVersion ForCtor) args) - |> (if args /= [] && requireParens == ForCtor then parens else id) + (map (formatHeadCommented tabSize $ formatType' elmVersion tabSize ForCtor) args) + |> (if args /= [] && requireParens == ForCtor then parens tabSize else id) TypeParens type' -> - parens $ formatCommented (formatType elmVersion) type' + parens tabSize $ formatCommented tabSize (formatType elmVersion tabSize) type' TupleType types -> - ElmStructure.group True "(" "," ")" False (map (formatCommented (formatEolCommented $ formatType elmVersion)) types) + ElmStructure.group tabSize True "(" "," ")" False (map (formatCommented tabSize (formatEolCommented tabSize $ formatType elmVersion tabSize)) types) RecordType base fields trailing multiline -> formatRecordLike + tabSize (line . formatLowercaseIdentifier elmVersion []) (formatLowercaseIdentifier elmVersion []) ":" - (formatType elmVersion) + (formatType elmVersion tabSize) base fields trailing multiline diff --git a/src/ElmFormat/Render/ElmStructure.hs b/src/ElmFormat/Render/ElmStructure.hs index 8d06384ef..07c40efd6 100644 --- a/src/ElmFormat/Render/ElmStructure.hs +++ b/src/ElmFormat/Render/ElmStructure.hs @@ -109,14 +109,14 @@ Formats as: opLong rest -} -spaceSepOrPrefix :: Box -> Box -> Box -spaceSepOrPrefix op rest = +spaceSepOrPrefix :: Int -> Box -> Box -> Box +spaceSepOrPrefix tabSize op rest = case ( op, rest) of ( SingleLine op', SingleLine rest' ) -> line $ row [ op', space, rest' ] - ( SingleLine op', _ ) | lineLength 0 op' < 4 -> - prefix (row [ op', space ]) rest + ( SingleLine op', _ ) | lineLength tabSize 0 op' < 4 -> + prefix tabSize (row [ op', space ]) rest _ -> stack1 [ op, indent rest ] @@ -248,8 +248,8 @@ application forceMultiline first args = ; child2 > -} -group :: Bool -> String -> String -> String -> Bool -> [Box] -> Box -group innerSpaces left sep right forceMultiline children = +group :: Int -> Bool -> String -> String -> String -> Bool -> [Box] -> Box +group tabSize innerSpaces left sep right forceMultiline children = case (forceMultiline, allSingles children) of (_, Right []) -> line $ row [punc left, punc right] @@ -268,8 +268,8 @@ group innerSpaces left sep right forceMultiline children = (first:rest) -> stack1 $ - prefix (row [punc left, space]) first - : map (prefix $ row [punc sep, space]) rest + prefix tabSize (row [punc left, space]) first + : map (prefix tabSize $ row [punc sep, space]) rest ++ [ line $ punc right ] {-| @@ -285,8 +285,8 @@ Formats as: , rest1 } -} -extensionGroup :: Bool -> Box -> Box -> [Box] -> Box -extensionGroup multiline base first rest = +extensionGroup :: Int -> Bool -> Box -> Box -> [Box] -> Box +extensionGroup tabSize multiline base first rest = case ( multiline , isLine base @@ -308,17 +308,17 @@ extensionGroup multiline base first rest = _ -> stack1 - [ prefix (row [punc "{", space]) base + [ prefix tabSize (row [punc "{", space]) base , stack1 - ( prefix (row [punc "|", space]) first - : map (prefix (row [punc ",", space])) rest) + ( prefix tabSize (row [punc "|", space]) first + : map (prefix tabSize (row [punc ",", space])) rest) |> indent , line $ punc "}" ] -extensionGroup' :: Bool -> Box -> Box -> Box -extensionGroup' multiline base fields = +extensionGroup' :: Int -> Bool -> Box -> Box -> Box +extensionGroup' tabSize multiline base fields = case ( multiline , base @@ -335,7 +335,7 @@ extensionGroup' multiline base fields = _ -> stack1 - [ prefix (row [punc "{", space]) base + [ prefix tabSize (row [punc "{", space]) base , indent fields , line $ punc "}" ] diff --git a/src/ElmFormat/Render/Text.hs b/src/ElmFormat/Render/Text.hs index c407eb623..61823c787 100644 --- a/src/ElmFormat/Render/Text.hs +++ b/src/ElmFormat/Render/Text.hs @@ -10,8 +10,8 @@ import qualified Data.Text as Text import qualified ElmFormat.Render.Box as Render -render :: ElmVersion -> AST.Module.Module -> Text.Text -render elmVersion modu = +render :: ElmVersion -> Int -> AST.Module.Module -> Text.Text +render elmVersion tabSize modu = let trimSpaces text = text @@ -19,6 +19,6 @@ render elmVersion modu = |> map Text.stripEnd |> Text.unlines in - Render.formatModule elmVersion modu - |> Box.render + Render.formatModule elmVersion tabSize modu + |> Box.render tabSize |> trimSpaces diff --git a/src/Flags.hs b/src/Flags.hs index 068ab27f8..9bf6186d7 100644 --- a/src/Flags.hs +++ b/src/Flags.hs @@ -2,6 +2,7 @@ module Flags where import Data.Monoid ((<>)) import ElmVersion (ElmVersion(..)) +import Defaults import qualified Data.Maybe as Maybe import qualified ElmVersion @@ -15,6 +16,7 @@ data Config = Config , _yes :: Bool , _validate :: Bool , _stdin :: Bool + , _tabSize :: Int , _elmVersion :: ElmVersion , _upgrade :: Bool } @@ -82,6 +84,7 @@ flags defaultVersion = <*> yes <*> validate <*> stdin + <*> tabSize <*> elmVersion defaultVersion <*> upgrade @@ -176,6 +179,17 @@ stdin = , Opt.help "Read from stdin, output to stdout." ] +tabSize :: Opt.Parser Int +tabSize = + -- Opt.optional $ + Opt.option Opt.auto $ + mconcat + [ Opt.long "tabsize" + , Opt.metavar "SPACES" + , Opt.value defaultTabSize + , Opt.help $ "Spaces per tab (default: " ++ show defaultTabSize ++ ")" + ] + elmVersion :: ElmVersion -> Opt.Parser ElmVersion elmVersion defaultVersion = diff --git a/tests/BoxTest.hs b/tests/BoxTest.hs index 54656a34b..f399559ea 100644 --- a/tests/BoxTest.hs +++ b/tests/BoxTest.hs @@ -8,6 +8,7 @@ import qualified Data.Text.Lazy as LazyText import qualified Data.Text as Text import Box +import Defaults trim :: String -> String @@ -28,7 +29,7 @@ assertLineOutput expected actual = assertOutput :: String -> Box -> Assertion assertOutput expected actual = assertEqual expected expected $ - trim $ Text.unpack $ render $ actual + trim $ Text.unpack $ render defaultTabSize $ actual word :: String -> Box @@ -74,5 +75,5 @@ tests = ] , testCase "indent (with leading spaces)" $ assertOutput " a\n" $ - prefix space $ indent $ line $ identifier "a" + prefix defaultTabSize space $ indent $ line $ identifier "a" ] diff --git a/tests/ElmFormat/CliTest/Usage.stdout b/tests/ElmFormat/CliTest/Usage.stdout index a086e506e..f9c6c6b87 100644 --- a/tests/ElmFormat/CliTest/Usage.stdout +++ b/tests/ElmFormat/CliTest/Usage.stdout @@ -1,7 +1,7 @@ elm-format-0.18 x.x.x Usage: elm-format [INPUT] [--output FILE] [--yes] [--validate] [--stdin] - [--elm-version VERSION] [--upgrade] + [--tabsize SPACES] [--elm-version VERSION] [--upgrade] Format Elm source files. Available options: @@ -11,6 +11,7 @@ Available options: --yes Reply 'yes' to all automated prompts. --validate Check if files are formatted without changing them. --stdin Read from stdin, output to stdout. + --tabsize SPACES Spaces per tab (default: 4) --elm-version VERSION The Elm version of the source files being formatted. Valid values: 0.17, 0.18. Default: 0.18 --upgrade Upgrade older Elm files to Elm 0.18 syntax diff --git a/tests/ElmFormat/Render/ElmStructureTest.hs b/tests/ElmFormat/Render/ElmStructureTest.hs index 52009b1cd..d664f918b 100644 --- a/tests/ElmFormat/Render/ElmStructureTest.hs +++ b/tests/ElmFormat/Render/ElmStructureTest.hs @@ -10,6 +10,7 @@ import qualified Data.Text as Text import AST.V0_16 import Box import ElmFormat.Render.ElmStructure +import Defaults trim :: String -> String @@ -30,7 +31,7 @@ assertLineOutput expected actual = assertOutput :: String -> Box -> Assertion assertOutput expected actual = assertEqual expected expected $ - trim $ Text.unpack $ render $ actual + trim $ Text.unpack $ render defaultTabSize $ actual word :: String -> Box @@ -72,20 +73,20 @@ tests = ] , testCase "group (empty)" $ assertOutput "()\n" $ - group True "(" "," ")" False [] + group defaultTabSize True "(" "," ")" False [] , testCase "group (single item, single line)" $ assertOutput "( foo )\n" $ - group True "(" "," ")" False [ word "foo" ] + group defaultTabSize True "(" "," ")" False [ word "foo" ] , testCase "group (single line)" $ assertOutput "( foo, bar )\n" $ - group True "(" "," ")" False [ word "foo", word "bar" ] + group defaultTabSize True "(" "," ")" False [ word "foo", word "bar" ] , testCase "group (single line, no spaces)" $ assertOutput "(foo, bar)\n" $ - group False "(" "," ")" False [ word "foo", word "bar" ] + group defaultTabSize False "(" "," ")" False [ word "foo", word "bar" ] , testCase "group (multiline)" $ assertOutput "( aa\n aa\n, b\n, cc\n cc\n)\n" $ - group True "(" "," ")" False [ block "a", word "b", block "c" ] + group defaultTabSize True "(" "," ")" False [ block "a", word "b", block "c" ] , testCase "group (forced multiline)" $ assertOutput "( a\n, b\n, c\n)\n" $ - group True "(" "," ")" True [ word "a", word "b", word "c" ] + group defaultTabSize True "(" "," ")" True [ word "a", word "b", word "c" ] ] diff --git a/tests/Parse/ExpressionTest.hs b/tests/Parse/ExpressionTest.hs index d74067ec8..f8c64d2bb 100644 --- a/tests/Parse/ExpressionTest.hs +++ b/tests/Parse/ExpressionTest.hs @@ -16,6 +16,8 @@ import qualified Box import qualified Data.Text as Text import Parse.TestHelpers +import qualified Defaults + pending :: Expr pending = at 0 0 0 0 $ Unit [] @@ -30,7 +32,7 @@ example name input expected = example' :: String -> String -> String -> TestTree example' name input expected = testCase name $ - assertParse (fmap (Text.unpack . Box.render . formatExpression Elm_0_18 SyntaxSeparated) expr) input expected + assertParse (fmap (Text.unpack . Box.render Defaults.defaultTabSize . formatExpression Elm_0_18 Defaults.defaultTabSize SyntaxSeparated) expr) input expected commentedIntExpr (a,b,c,d) preComment postComment i = diff --git a/tests/Parse/LiteralTest.hs b/tests/Parse/LiteralTest.hs index 7c65ef87c..1a50aaa54 100644 --- a/tests/Parse/LiteralTest.hs +++ b/tests/Parse/LiteralTest.hs @@ -9,11 +9,13 @@ import ElmFormat.Render.Box (formatLiteral) import Parse.Literal (literal) import Parse.TestHelpers (assertParse, assertParseFailure) +import qualified Defaults + example :: String -> String -> String -> TestTree example name input expected = testCase name $ - assertParse (fmap (unpack . render . formatLiteral) literal) input expected + assertParse (fmap (unpack . render Defaults.defaultTabSize . formatLiteral) literal) input expected tests :: TestTree diff --git a/tests/Parse/TypeTest.hs b/tests/Parse/TypeTest.hs index 3b33c1574..8e6eb4ab5 100644 --- a/tests/Parse/TypeTest.hs +++ b/tests/Parse/TypeTest.hs @@ -12,6 +12,8 @@ import ElmFormat.Render.Box (formatType) import qualified Box import qualified Data.Text as Text +import qualified Defaults + pending = at 0 0 0 0 $ TupleType [] @@ -19,7 +21,7 @@ pending = at 0 0 0 0 $ TupleType [] example :: String -> String -> String -> TestTree example name input expected = testCase name $ - assertParse (fmap (Text.unpack . Box.render . formatType Elm_0_18) expr) input expected + assertParse (fmap (Text.unpack . Box.render Defaults.defaultTabSize . formatType Elm_0_18 Defaults.defaultTabSize) expr) input expected tests :: TestTree diff --git a/tests/Test/Property.hs b/tests/Test/Property.hs index a9eda2489..4d36d9537 100644 --- a/tests/Test/Property.hs +++ b/tests/Test/Property.hs @@ -18,7 +18,7 @@ import qualified ElmFormat.Render.Text as Render import qualified ElmVersion import qualified Test.Generators () import qualified Test.ElmSourceGenerators - +import qualified Defaults assertStringToString :: String -> Assertion assertStringToString source = @@ -28,7 +28,7 @@ assertStringToString source = result = Parse.parse source' |> Parse.toEither - |> fmap (Render.render ElmVersion.Elm_0_17) + |> fmap (Render.render ElmVersion.Elm_0_17 Defaults.defaultTabSize) in assertEqual "" (Right source') result @@ -38,7 +38,7 @@ astToAst ast = let result = ast - |> Render.render ElmVersion.Elm_0_17 + |> Render.render ElmVersion.Elm_0_17 Defaults.defaultTabSize |> Parse.parse |> Parse.toEither in @@ -54,9 +54,9 @@ simpleAst = reportFailedAst ast = let - rendering = Render.render ElmVersion.Elm_0_17 ast |> Text.unpack + rendering = Render.render ElmVersion.Elm_0_17 Defaults.defaultTabSize ast |> Text.unpack result = - Render.render ElmVersion.Elm_0_17 ast + Render.render ElmVersion.Elm_0_17 Defaults.defaultTabSize ast |> Parse.parse |> fmap stripRegion |> show