1
1
mirror of https://github.com/tweag/ormolu.git synced 2024-09-11 13:16:13 +03:00

Read and write text files using UTF8 and ignoring native line ending

This commit is contained in:
amesgen 2021-08-11 12:41:22 +02:00 committed by Mark Karpov
parent 011f0dad79
commit 3f52afa1d3
7 changed files with 40 additions and 11 deletions

View File

@ -9,6 +9,10 @@
* `do` arrow commands are formatted more flexibly. Fixes [Issue
753](https://github.com/tweag/ormolu/issues/753).
* Always read and write formatted source code using UTF8 and ignoring
the native line ending conventions. [Issue
717](https://github.com/tweag/ormolu/issues/717).
## Ormolu 0.2.0.0
* Now standalone kind signatures are grouped with type synonyms. [Issue

View File

@ -19,6 +19,7 @@ import Ormolu.Diff.Text (diffText, printTextDiff)
import Ormolu.Parser (manualExts)
import Ormolu.Terminal
import Ormolu.Utils (showOutputable)
import Ormolu.Utils.IO
import Paths_ormolu (version)
import System.Exit (ExitCode (..), exitWith)
import qualified System.FilePath as FP
@ -73,7 +74,7 @@ formatOne mode config mpath = withPrettyOrmoluExceptions (cfgColorMode config) $
-- 101 is different from all the other exit codes we already use.
return (ExitFailure 101)
Just inputFile -> do
originalInput <- TIO.readFile inputFile
originalInput <- readFileUtf8 inputFile
formattedInput <- ormoluFile config inputFile
case mode of
Stdout -> do
@ -84,7 +85,7 @@ formatOne mode config mpath = withPrettyOrmoluExceptions (cfgColorMode config) $
-- updating the modified timestamp if the file was already correctly
-- formatted.
when (formattedInput /= originalInput) $
TIO.writeFile inputFile formattedInput
writeFileUtf8 inputFile formattedInput
return ExitSuccess
Check ->
case diffText originalInput formattedInput inputFile of

View File

@ -76,6 +76,7 @@ library
Ormolu.Processing.Preprocess
Ormolu.Terminal
Ormolu.Utils
Ormolu.Utils.IO
hs-source-dirs: src
other-modules: GHC.DynFlags

View File

@ -31,6 +31,7 @@ import Ormolu.Parser
import Ormolu.Parser.Result
import Ormolu.Printer
import Ormolu.Utils (showOutputable)
import Ormolu.Utils.IO
-- | Format a 'String', return formatted version as 'Text'.
--
@ -103,7 +104,7 @@ ormoluFile ::
-- | Resulting rendition
m Text
ormoluFile cfg path =
liftIO (readFile path) >>= ormolu cfg path
readFileUtf8 path >>= ormolu cfg path . T.unpack
-- | Read input from stdin and format it.
--

23
src/Ormolu/Utils/IO.hs Normal file
View File

@ -0,0 +1,23 @@
-- | Write 'Text' to files using UTF8 and ignoring native
-- line ending conventions.
module Ormolu.Utils.IO
( writeFileUtf8,
readFileUtf8,
)
where
import Control.Exception (throwIO)
import Control.Monad.IO.Class
import qualified Data.ByteString as B
import Data.Text (Text)
import qualified Data.Text.Encoding as TE
-- | Write a 'Text' to a file using UTF8 and ignoring native
-- line ending conventions.
writeFileUtf8 :: MonadIO m => FilePath -> Text -> m ()
writeFileUtf8 p = liftIO . B.writeFile p . TE.encodeUtf8
-- | Read an entire file strictly into a 'Text' using UTF8 and
-- ignoring native line ending conventions.
readFileUtf8 :: MonadIO m => FilePath -> m Text
readFileUtf8 p = liftIO $ either throwIO pure . TE.decodeUtf8' =<< B.readFile p

View File

@ -3,9 +3,9 @@
module Ormolu.Diff.TextSpec (spec) where
import Data.Text (Text)
import qualified Data.Text.IO as T
import Ormolu.Diff.Text
import Ormolu.Terminal
import Ormolu.Utils.IO
import Path
import Path.IO
import qualified System.FilePath as FP
@ -37,14 +37,14 @@ stdTest ::
stdTest name pathA pathB = it name $ do
inputA <-
parseRelFile (FP.addExtension pathA "hs")
>>= T.readFile . toFilePath . (diffInputsDir </>)
>>= readFileUtf8 . toFilePath . (diffInputsDir </>)
inputB <-
parseRelFile (FP.addExtension pathB "hs")
>>= T.readFile . toFilePath . (diffInputsDir </>)
>>= readFileUtf8 . toFilePath . (diffInputsDir </>)
let expectedDiffPath = FP.addExtension name "txt"
expectedDiffText <-
parseRelFile expectedDiffPath
>>= T.readFile . toFilePath . (diffOutputsDir </>)
>>= readFileUtf8 . toFilePath . (diffOutputsDir </>)
let Just actualDiff = diffText inputA inputB "TEST"
actualDiffText <- printDiff actualDiff
actualDiffText `shouldBe` expectedDiffText
@ -55,7 +55,7 @@ printDiff diff =
withSystemTempFile "ormolu-diff-test" $ \path h -> do
runTerm (printTextDiff diff) Never h
hClose h
T.readFile (toFilePath path)
readFileUtf8 (toFilePath path)
diffTestsDir :: Path Rel Dir
diffTestsDir = $(mkRelDir "data/diff-tests")

View File

@ -4,12 +4,11 @@ module Ormolu.PrinterSpec (spec) where
import Control.Exception
import Control.Monad
import Control.Monad.IO.Class
import Data.List (isSuffixOf)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Ormolu
import Ormolu.Utils.IO
import Path
import Path.IO
import qualified System.FilePath as F
@ -33,7 +32,7 @@ checkExample srcPath' = it (fromRelFile srcPath' ++ " works") . withNiceExceptio
-- 3. Check the output against expected output. Thus all tests should
-- include two files: input and expected output.
-- T.writeFile (fromRelFile expectedOutputPath) formatted0
expected <- (liftIO . T.readFile . fromRelFile) expectedOutputPath
expected <- readFileUtf8 $ fromRelFile expectedOutputPath
shouldMatch False formatted0 expected
-- 4. Check that running the formatter on the output produces the same
-- output again (the transformation is idempotent).