Skip to content

Commit

Permalink
Use Data.Text.IO.Utf8 from text-2.1
Browse files Browse the repository at this point in the history
  • Loading branch information
amesgen authored and mrkkrp committed May 21, 2024
1 parent 1c70545 commit 9de2dfa
Show file tree
Hide file tree
Showing 10 changed files with 29 additions and 58 deletions.
15 changes: 7 additions & 8 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Data.List.NonEmpty (NonEmpty)
import Data.Map.Strict qualified as Map
import Data.Maybe (fromMaybe, mapMaybe, maybeToList)
import Data.Set qualified as Set
import Data.Text.IO qualified as TIO
import Data.Text.IO.Utf8 qualified as T.Utf8
import Data.Version (showVersion)
import Distribution.ModuleName (ModuleName)
import Distribution.Types.PackageName (PackageName)
Expand All @@ -28,7 +28,6 @@ import Ormolu.Parser (manualExts)
import Ormolu.Terminal
import Ormolu.Utils (showOutputable)
import Ormolu.Utils.Fixity
import Ormolu.Utils.IO
import Paths_ormolu (version)
import System.Directory
import System.Exit (ExitCode (..), exitWith)
Expand Down Expand Up @@ -117,7 +116,7 @@ formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
config <- patchConfig Nothing mcabalInfo mdotOrmolu
case mode of
Stdout -> do
ormoluStdin config >>= TIO.putStr
ormoluStdin config >>= T.Utf8.putStr
return ExitSuccess
InPlace -> do
hPutStrLn
Expand All @@ -127,7 +126,7 @@ formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
return (ExitFailure 101)
Check -> do
-- ormoluStdin is not used because we need the originalInput
originalInput <- getContentsUtf8
originalInput <- T.Utf8.getContents
let stdinRepr = "<stdin>"
formattedInput <-
ormolu config stdinRepr originalInput
Expand All @@ -146,19 +145,19 @@ formatOne ConfigFileOpts {..} mode reqSourceType rawConfig mpath =
mdotOrmolu
case mode of
Stdout -> do
ormoluFile config inputFile >>= TIO.putStr
ormoluFile config inputFile >>= T.Utf8.putStr
return ExitSuccess
InPlace -> do
-- ormoluFile is not used because we need originalInput
originalInput <- readFileUtf8 inputFile
originalInput <- T.Utf8.readFile inputFile
formattedInput <-
ormolu config inputFile originalInput
when (formattedInput /= originalInput) $
writeFileUtf8 inputFile formattedInput
T.Utf8.writeFile inputFile formattedInput
return ExitSuccess
Check -> do
-- ormoluFile is not used because we need originalInput
originalInput <- readFileUtf8 inputFile
originalInput <- T.Utf8.readFile inputFile
formattedInput <-
ormolu config inputFile originalInput
handleDiff originalInput formattedInput inputFile
Expand Down
2 changes: 1 addition & 1 deletion extract-hackage-info/extract-hackage-info.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,6 @@ executable extract-hackage-info
filepath >=1.2 && <1.6,
optparse-applicative >=0.14 && <0.19,
ormolu,
text >=2 && <3,
text >=2.1 && <3,
formatting >=7.1 && <7.3,
megaparsec >=9
4 changes: 2 additions & 2 deletions extract-hackage-info/src/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.Text (Text)
import Data.Text.Encoding (decodeLatin1)
import Data.Text.IO qualified as TIO
import Data.Text.IO.Utf8 qualified as T.Utf8
import Distribution.ModuleName (ModuleName)
import Distribution.Types.PackageName (PackageName)
import Formatting
Expand Down Expand Up @@ -59,7 +59,7 @@ walkDir top = do
-- | Try to read the specified file using utf-8 encoding first, and latin1
-- otherwise.
readFileUtf8Latin1 :: FilePath -> IO Text
readFileUtf8Latin1 filePath = catch @IOException (TIO.readFile filePath) $
readFileUtf8Latin1 filePath = catch @IOException (T.Utf8.readFile filePath) $
\e -> do
hprintLn
stderr
Expand Down
6 changes: 3 additions & 3 deletions ormolu.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ library
megaparsec >=9,
mtl >=2 && <3,
syb >=0.7 && <0.8,
text >=2 && <3
text >=2.1 && <3

if flag(dev)
ghc-options:
Expand Down Expand Up @@ -142,7 +142,7 @@ executable ormolu
ghc-lib-parser >=9.10 && <9.11,
optparse-applicative >=0.14 && <0.19,
ormolu,
text >=2 && <3,
text >=2.1 && <3,
th-env >=0.1.1 && <0.2

if flag(dev)
Expand Down Expand Up @@ -186,7 +186,7 @@ test-suite tests
path >=0.6 && <0.10,
path-io >=1.4.2 && <2,
temporary ^>=1.3,
text >=2 && <3
text >=2.1 && <3

if flag(dev)
ghc-options:
Expand Down
6 changes: 3 additions & 3 deletions src/Ormolu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ import Data.Maybe (fromMaybe)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.IO.Utf8 qualified as T.Utf8
import Debug.Trace
import GHC.Driver.Errors.Types
import GHC.Types.Error
Expand All @@ -62,7 +63,6 @@ import Ormolu.Printer
import Ormolu.Utils (showOutputable)
import Ormolu.Utils.Cabal qualified as CabalUtils
import Ormolu.Utils.Fixity (getDotOrmoluForSourceFile)
import Ormolu.Utils.IO
import System.FilePath

-- | Format a 'Text'.
Expand Down Expand Up @@ -159,7 +159,7 @@ ormoluFile ::
-- | Resulting rendition
m Text
ormoluFile cfg path =
readFileUtf8 path >>= ormolu cfg path
liftIO (T.Utf8.readFile path) >>= ormolu cfg path

-- | Read input from stdin and format it.
--
Expand All @@ -173,7 +173,7 @@ ormoluStdin ::
-- | Resulting rendition
m Text
ormoluStdin cfg =
getContentsUtf8 >>= ormolu cfg "<stdin>"
liftIO T.Utf8.getContents >>= ormolu cfg "<stdin>"

-- | Refine a 'Config' by incorporating given 'SourceType', 'CabalInfo', and
-- fixity overrides 'FixityMap'. You can use 'detectSourceType' to deduce
Expand Down
4 changes: 2 additions & 2 deletions src/Ormolu/Terminal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ import Data.Sequence (Seq)
import Data.Sequence qualified as Seq
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.IO qualified as T
import Data.Text.IO.Utf8 qualified as T.Utf8
import GHC.Utils.Outputable (Outputable)
import Ormolu.Utils (showOutputable)
import System.Console.ANSI
Expand Down Expand Up @@ -76,7 +76,7 @@ runTerm term0 colorMode handle = do
where
go (TermOutput (Const nodes)) =
forM_ nodes $ \case
OutputText s -> T.hPutStr handle s
OutputText s -> T.Utf8.hPutStr handle s
WithColor color term -> withSGR [SetColor Foreground Dull color] (go term)
WithBold term -> withSGR [SetConsoleIntensity BoldIntensity] (go term)

Expand Down
5 changes: 3 additions & 2 deletions src/Ormolu/Utils/Fixity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,12 +15,13 @@ import Data.List.NonEmpty (NonEmpty)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Text qualified as T
import Data.Text.IO.Utf8 qualified as T.Utf8
import Distribution.ModuleName (ModuleName)
import Distribution.Types.PackageName (PackageName)
import Ormolu.Exception
import Ormolu.Fixity
import Ormolu.Fixity.Parser
import Ormolu.Utils.IO (findClosestFileSatisfying, readFileUtf8, withIORefCache)
import Ormolu.Utils.IO (findClosestFileSatisfying, withIORefCache)
import System.Directory
import System.IO.Unsafe (unsafePerformIO)
import Text.Megaparsec (errorBundlePretty)
Expand All @@ -38,7 +39,7 @@ getDotOrmoluForSourceFile sourceFile =
liftIO (findDotOrmoluFile sourceFile) >>= \case
Just dotOrmoluFile -> liftIO $ withIORefCache cacheRef dotOrmoluFile $ do
dotOrmoluRelative <- makeRelativeToCurrentDirectory dotOrmoluFile
contents <- readFileUtf8 dotOrmoluFile
contents <- T.Utf8.readFile dotOrmoluFile
case parseDotOrmolu dotOrmoluRelative contents of
Left errorBundle ->
throwIO (OrmoluFixityOverridesParseError errorBundle)
Expand Down
30 changes: 1 addition & 29 deletions src/Ormolu/Utils/IO.hs
Original file line number Diff line number Diff line change
@@ -1,49 +1,21 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}

-- | Write 'Text' to files using UTF8 and ignoring native
-- line ending conventions.
module Ormolu.Utils.IO
( writeFileUtf8,
readFileUtf8,
getContentsUtf8,
findClosestFileSatisfying,
( findClosestFileSatisfying,
withIORefCache,
)
where

import Control.Exception (catch, throwIO)
import Control.Monad.IO.Class
import Data.ByteString (ByteString)
import Data.ByteString qualified as B
import Data.IORef
import Data.Map.Lazy (Map)
import Data.Map.Lazy qualified as M
import Data.Text (Text)
import Data.Text.Encoding qualified as TE
import System.Directory
import System.FilePath
import System.IO.Error (isDoesNotExistError)

-- | 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 (B.readFile p) >>= decodeUtf8

-- | Read stdin as UTF8-encoded 'Text' value.
getContentsUtf8 :: (MonadIO m) => m Text
getContentsUtf8 = liftIO B.getContents >>= decodeUtf8

-- | A helper function for decoding a strict 'ByteString' into 'Text'. It is
-- strict and fails immediately if decoding encounters a problem.
decodeUtf8 :: (MonadIO m) => ByteString -> m Text
decodeUtf8 = liftIO . either throwIO pure . TE.decodeUtf8'

-- | Find the path to the closest file higher in the file hierarchy that
-- satisfies a given predicate.
findClosestFileSatisfying ::
Expand Down
8 changes: 4 additions & 4 deletions tests/Ormolu/Diff/TextSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,9 @@

module Ormolu.Diff.TextSpec (spec) where

import Data.Text.IO.Utf8 qualified as T.Utf8
import Ormolu.Diff.Text
import Ormolu.Terminal
import Ormolu.Utils.IO
import Path
import System.FilePath qualified as FP
import Test.Hspec
Expand Down Expand Up @@ -36,14 +36,14 @@ stdTest ::
stdTest name pathA pathB = it name $ do
inputA <-
parseRelFile (FP.addExtension pathA "hs")
>>= readFileUtf8 . toFilePath . (diffInputsDir </>)
>>= T.Utf8.readFile . toFilePath . (diffInputsDir </>)
inputB <-
parseRelFile (FP.addExtension pathB "hs")
>>= readFileUtf8 . toFilePath . (diffInputsDir </>)
>>= T.Utf8.readFile . toFilePath . (diffInputsDir </>)
let expectedDiffPath = FP.addExtension name "txt"
expectedDiffText <-
parseRelFile expectedDiffPath
>>= readFileUtf8 . toFilePath . (diffOutputsDir </>)
>>= T.Utf8.readFile . toFilePath . (diffOutputsDir </>)
Just actualDiff <- pure $ diffText inputA inputB "TEST"
runTermPure (printTextDiff actualDiff) `shouldBe` expectedDiffText

Expand Down
7 changes: 3 additions & 4 deletions tests/Ormolu/PrinterSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,9 @@ import Data.Maybe (isJust)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.IO qualified as T
import Data.Text.IO.Utf8 qualified as T.Utf8
import Ormolu
import Ormolu.Fixity
import Ormolu.Utils.IO
import Path
import Path.IO
import System.Environment (lookupEnv)
Expand Down Expand Up @@ -63,8 +62,8 @@ 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.
whenShouldRegenerateOutput $
T.writeFile (fromRelFile expectedOutputPath) formatted0
expected <- readFileUtf8 $ fromRelFile expectedOutputPath
T.Utf8.writeFile (fromRelFile expectedOutputPath) formatted0
expected <- T.Utf8.readFile $ fromRelFile expectedOutputPath
shouldMatch False formatted0 expected
-- 4. Check that running the formatter on the output produces the same
-- output again (the transformation is idempotent).
Expand Down

0 comments on commit 9de2dfa

Please sign in to comment.