Skip to content

Commit

Permalink
Enforce UTF-8 encoding on reading and writing files
Browse files Browse the repository at this point in the history
  • Loading branch information
Jimbo4350 authored and newhoggy committed Nov 20, 2024
1 parent 40bd9e5 commit bdd89f7
Showing 1 changed file with 9 additions and 3 deletions.
12 changes: 9 additions & 3 deletions src/Hedgehog/Extras/Test/File.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}

module Hedgehog.Extras.Test.File
( createDirectoryIfMissing
Expand Down Expand Up @@ -65,6 +65,8 @@ import Data.Maybe
import Data.Semigroup
import Data.String (String)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import Data.Time.Clock (UTCTime)
import GHC.Stack (HasCallStack)
import Hedgehog (MonadTest)
Expand Down Expand Up @@ -158,7 +160,9 @@ appendFile filePath contents = GHC.withFrozenCallStack $ do
writeFile :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> String -> m ()
writeFile filePath contents = GHC.withFrozenCallStack $ do
void . H.annotate $ "Writing file: " <> filePath
H.evalIO $ IO.writeFile filePath contents
H.evalIO $ IO.withFile filePath IO.WriteMode $ \handle -> do
IO.hSetEncoding handle IO.utf8
IO.hPutStr handle contents

-- | Open a handle to the 'filePath' file.
openFile :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> IOMode -> m Handle
Expand All @@ -170,7 +174,9 @@ openFile filePath mode = GHC.withFrozenCallStack $ do
readFile :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> m String
readFile filePath = GHC.withFrozenCallStack $ do
void . H.annotate $ "Reading file: " <> filePath
H.evalIO $ IO.readFile filePath
liftIO $ IO.withFile filePath IO.ReadMode $ \handle -> do
IO.hSetEncoding handle IO.utf8
Text.unpack <$> Text.hGetContents handle

-- | Write 'contents' to the 'filePath' file.
lbsWriteFile :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> LBS.ByteString -> m ()
Expand Down

0 comments on commit bdd89f7

Please sign in to comment.