Skip to content

Commit 28a5f69

Browse files
committed
Prelude: use readFile (Path -> Text)
1 parent 0679283 commit 28a5f69

File tree

6 files changed

+20
-19
lines changed

6 files changed

+20
-19
lines changed

main/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -81,7 +81,7 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
8181
(\ (binaryCacheFile :: Path) ->
8282
do
8383
let file = coerce $ (replaceExtension . coerce) binaryCacheFile "nixc"
84-
processCLIOptions (Just file) =<< liftIO (readCache $ binaryCacheFile)
84+
processCLIOptions (Just file) =<< liftIO (readCache binaryCacheFile)
8585
) <$> readFrom
8686

8787
-- | The `--expr` option: read expression from the argument string
@@ -95,7 +95,7 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
9595
(processSeveralFiles . (coerce . toString <$>) . lines <=< liftIO) .
9696
(\case
9797
"-" -> Text.getContents
98-
_fp -> readFile $ coerce _fp
98+
_fp -> readFile _fp
9999
) <$> fromFile
100100

101101
processExpr text = handleResult Nothing $ parseNixTextLoc text

main/Repl.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@ main' iniVal =
9696

9797
rcFile =
9898
do
99-
f <- liftIO $ Text.readFile ".hnixrc" `catch` handleMissing
99+
f <- liftIO $ readFile ".hnixrc" `catch` handleMissing
100100

101101
traverse_
102102
(\case
@@ -116,8 +116,8 @@ main' iniVal =
116116

117117
-- Replicated and slightly adjusted `optMatcher` from `System.Console.Repline`
118118
-- which doesn't export it.
119-
-- * @MonadIO m@ instead of @MonadHaskeline m@
120-
-- * @putStrLn@ instead of @outputStrLn@
119+
-- * @MonadIO m@ instead of @MonadHaskeline m@
120+
-- * @putStrLn@ instead of @outputStrLn@
121121
optMatcher :: MonadIO m
122122
=> Text
123123
-> Console.Options m
@@ -304,11 +304,12 @@ load
304304
-> Repl e t f m ()
305305
load path =
306306
do
307-
contents <- liftIO $ Prelude.readFile $
307+
contents <- liftIO $ readFile $
308308
trim path
309309
void $ exec True contents
310310
where
311-
trim = dropWhileEnd isSpace . dropWhile isSpace . coerce
311+
trim :: Path -> Path
312+
trim = coerce . dropWhileEnd isSpace . dropWhile isSpace . coerce
312313

313314
-- | @:type@ command
314315
typeof

src/Nix/Parser.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,6 @@ where
4242
import Prelude hiding ( (<|>)
4343
, some
4444
, many
45-
, readFile
4645
)
4746
import Data.Foldable ( foldr1 )
4847

@@ -72,7 +71,7 @@ import Nix.Expr.Strings ( escapeCodes
7271
, mergePlain
7372
, removeEmptyPlains
7473
)
75-
import Nix.Render ( MonadFile(readFile) )
74+
import Nix.Render ( MonadFile() )
7675
import Prettyprinter ( Doc
7776
, pretty
7877
)
@@ -876,7 +875,7 @@ type Result a = Either (Doc Void) a
876875
parseFromFileEx :: MonadFile m => Parser a -> Path -> m (Result a)
877876
parseFromFileEx parser file =
878877
do
879-
input <- readFile file
878+
input <- liftIO $ readFile file
880879

881880
pure $
882881
either

src/Nix/Render.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import qualified Data.Text as Text
2323
class (MonadFail m, MonadIO m) => MonadFile m where
2424
readFile :: Path -> m Text
2525
default readFile :: (MonadTrans t, MonadIO m', MonadFile m', m ~ t m') => Path -> m Text
26-
readFile = liftIO . Prelude.readFile . coerce
26+
readFile = liftIO . Prelude.readFile
2727
listDirectory :: Path -> m [Path]
2828
default listDirectory :: (MonadTrans t, MonadFile m', m ~ t m') => Path -> m [Path]
2929
listDirectory = lift . listDirectory
@@ -50,7 +50,7 @@ class (MonadFail m, MonadIO m) => MonadFile m where
5050
getSymbolicLinkStatus = lift . getSymbolicLinkStatus
5151

5252
instance MonadFile IO where
53-
readFile = liftIO . Prelude.readFile . coerce
53+
readFile = Prelude.readFile
5454
listDirectory = coerce <$> (S.listDirectory . coerce)
5555
getCurrentDirectory = coerce <$> S.getCurrentDirectory
5656
canonicalizePath = coerce <$> (S.canonicalizePath . coerce)

src/Prelude.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@
88
module Prelude
99
( module Prelude
1010
, module Relude
11-
, Text.readFile
1211
, module X
1312
) where
1413

@@ -294,3 +293,6 @@ mapPair ~(f,g) ~(a,b) = (f a, g b)
294293
stub :: (Applicative f, Monoid a) => f a
295294
stub = pure mempty
296295
{-# inline stub #-}
296+
297+
readFile :: Path -> IO Text
298+
readFile = Text.readFile . coerce

tests/NixLanguageTests.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@ import qualified Data.Map as Map
1010
import qualified Data.Set as Set
1111
import qualified Data.String as String
1212
import qualified Data.Text as Text
13-
import qualified Data.Text.IO as Text
1413
import Data.Time
1514
import GHC.Exts
1615
import Nix.Lint
@@ -130,21 +129,21 @@ assertParseFail opts file = do
130129
assertLangOk :: Options -> Path -> Assertion
131130
assertLangOk opts file = do
132131
actual <- printNix <$> hnixEvalFile opts (file <> ".nix")
133-
expected <- Text.readFile $ coerce $ file <> ".exp"
134-
assertEqual "" expected $ toText (actual <> "\n")
132+
expected <- readFile $ file <> ".exp"
133+
assertEqual "" expected $ fromString (actual <> "\n")
135134

136135
assertLangOkXml :: Options -> Path -> Assertion
137136
assertLangOkXml opts file = do
138137
actual <- stringIgnoreContext . toXML <$> hnixEvalFile opts (file <> ".nix")
139-
expected <- Text.readFile $ coerce $ file <> ".exp.xml"
138+
expected <- readFile $ file <> ".exp.xml"
140139
assertEqual "" expected actual
141140

142141
assertEval :: Options -> [Path] -> Assertion
143142
assertEval _opts files =
144143
do
145144
time <- liftIO getCurrentTime
146145
let opts = defaultOptions time
147-
case delete ".nix" $ sort $ toText . takeExtensions . coerce <$> files of
146+
case delete ".nix" $ sort $ fromString @Text . takeExtensions . coerce <$> files of
148147
[] -> void $ hnixEvalFile opts (name <> ".nix")
149148
[".exp" ] -> assertLangOk opts name
150149
[".exp.xml" ] -> assertLangOkXml opts name
@@ -153,7 +152,7 @@ assertEval _opts files =
153152
[".exp", ".flags"] ->
154153
do
155154
liftIO $ setEnv "NIX_PATH" "lang/dir4:lang/dir5"
156-
flags <- Text.readFile $ coerce $ name <> ".flags"
155+
flags <- readFile $ name <> ".flags"
157156
let flags' | Text.last flags == '\n' = Text.init flags
158157
| otherwise = flags
159158
case runParserGetResult time flags' of

0 commit comments

Comments
 (0)