Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions elm-format.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ library
AST.V0_16
AST.Variable
Box
Defaults
Elm.Utils
ElmFormat.Cli
ElmFormat.Parse
Expand Down
3 changes: 2 additions & 1 deletion parser/src/Reporting/Report.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import System.IO (hPutStr, stderr)

import qualified Reporting.Region as R

import Defaults

data Report = Report
{ _title :: String
Expand Down Expand Up @@ -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 ++ " "
Expand Down
80 changes: 38 additions & 42 deletions src/Box.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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.
-}
Expand Down Expand Up @@ -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 ]
Expand All @@ -205,57 +205,52 @@ 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)
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
Expand All @@ -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'
9 changes: 9 additions & 0 deletions src/Defaults.hs
Original file line number Diff line number Diff line change
@@ -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
44 changes: 23 additions & 21 deletions src/ElmFormat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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])
Expand Down Expand Up @@ -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

Expand All @@ -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)
Expand All @@ -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
Expand Down Expand Up @@ -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
Expand All @@ -268,10 +269,10 @@ validate elmVersion source =

Lazy.toStrict input
|> Text.decodeUtf8
|> processTextInput elmVersion ValidateOnly "<STDIN>"
|> processTextInput elmVersion tabSize ValidateOnly "<STDIN>"

FromFiles first rest ->
handleFilesInput elmVersion (first:rest) Nothing True True
handleFilesInput elmVersion tabSize (first:rest) Nothing True True

case result of
Nothing ->
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand All @@ -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
Expand All @@ -367,7 +369,7 @@ main defaultVersion =
result <-
Lazy.toStrict input
|> Text.decodeUtf8
|> processTextInput elmVersion UpdateInPlace "<STDIN>"
|> processTextInput elmVersion tabSize UpdateInPlace "<STDIN>"
|> foldFree Execute.forHuman
case result of
Just False ->
Expand All @@ -383,7 +385,7 @@ main defaultVersion =
result <-
Lazy.toStrict input
|> Text.decodeUtf8
|> processTextInput elmVersion (ToFile output) "<STDIN>"
|> processTextInput elmVersion tabSize (ToFile output) "<STDIN>"
|> foldFree Execute.forHuman
case result of
Just False ->
Expand Down
Loading