Skip to content

Commit 2432e37

Browse files
committed
{Pretty, & Test modules}: String -> Text
1 parent 0895b75 commit 2432e37

File tree

5 files changed

+72
-52
lines changed

5 files changed

+72
-52
lines changed

src/Nix/Pretty.hs

Lines changed: 14 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,6 @@ import Nix.Parser
2929
import Nix.String
3030
import Nix.Thunk
3131
import Nix.Value
32-
import qualified GHC.OldList as OldList
3332

3433
-- | This type represents a pretty printed nix expression
3534
-- together with some information about the expression.
@@ -356,7 +355,7 @@ prettyNValueProv v =
356355
fillSep
357356
[ prettyNVal
358357
, indent 2 $
359-
"(" <> fold ("from: " : (prettyOriginExpr . _originExpr <$> ps)) <> ")"
358+
"(" <> fold (one "from: " <> (prettyOriginExpr . _originExpr <$> ps)) <> ")"
360359
]
361360
)
362361
(citations @m @(NValue t f m) v)
@@ -380,36 +379,36 @@ prettyNThunk t =
380379
fillSep
381380
[ v'
382381
, indent 2 $
383-
"(" <> fold ( "thunk from: " : (prettyOriginExpr . _originExpr <$> ps)) <> ")"
382+
"(" <> fold (one "thunk from: " <> (prettyOriginExpr . _originExpr <$> ps)) <> ")"
384383
]
385384

386385
-- | This function is used only by the testing code.
387-
printNix :: forall t f m . MonadDataContext f m => NValue t f m -> String
386+
printNix :: forall t f m . MonadDataContext f m => NValue t f m -> Text
388387
printNix = iterNValueByDiscardWith thk phi
389388
where
390-
thk = toString thunkStubText
389+
thk = thunkStubText
391390

392-
phi :: NValue' t f m String -> String
393-
phi (NVConstant' a ) = toString $ atomText a
391+
phi :: NValue' t f m Text -> Text
392+
phi (NVConstant' a ) = atomText a
394393
phi (NVStr' ns) = show $ stringIgnoreContext ns
395-
phi (NVList' l ) = "[ " <> OldList.unwords l <> " ]"
394+
phi (NVList' l ) = "[ " <> unwords l <> " ]"
396395
phi (NVSet' _ s) =
397396
"{ " <>
398397
fold
399-
[ check (toString k) <> " = " <> v <> "; "
400-
| (k, v) <- sort $ toList s
398+
[ check k <> " = " <> v <> "; "
399+
| (coerce -> k, v) <- sort $ toList s
401400
] <> "}"
402401
where
403-
check :: [Char] -> [Char]
402+
check :: Text -> Text
404403
check v =
405404
fromMaybe
406405
v
407406
(tryRead @Int <|> tryRead @Float)
408407
where
409408
surround s = "\"" <> s <> "\""
410409

411-
tryRead :: forall a . (Read a, Show a) => Maybe String
412-
tryRead = fmap (surround . show) (readMaybe v :: Maybe a)
410+
tryRead :: forall a . (Read a, Show a) => Maybe Text
411+
tryRead = fmap (surround . show) (readMaybe (toString v) :: Maybe a)
413412
phi NVClosure'{} = "<<lambda>>"
414-
phi (NVPath' fp ) = coerce fp
415-
phi (NVBuiltin' name _) = toString @Text $ "<<builtin " <> coerce name <> ">>"
413+
phi (NVPath' fp ) = fromString $ coerce fp
414+
phi (NVBuiltin' name _) = "<<builtin " <> coerce name <> ">>"

tests/EvalTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -598,7 +598,7 @@ constantEqual expected actual =
598598
"Inequal normal forms:\n"
599599
<> "Expected: " <> printNix expectedNF <> "\n"
600600
<> "Actual: " <> printNix actualNF
601-
assertBool message eq
601+
assertBool (toString message) eq
602602
where
603603
getNormForm = normalForm <=< nixEvalExprLoc mempty
604604

tests/NixLanguageTests.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@ assertLangOk opts fileBaseName =
158158
do
159159
actual <- printNix <$> hnixEvalFile opts (addNixExt fileBaseName)
160160
expected <- read fileBaseName ".exp"
161-
assertEqual mempty expected $ fromString (actual <> "\n")
161+
assertEqual mempty expected (actual <> "\n")
162162

163163
assertLangOkXml :: Options -> Path -> Assertion
164164
assertLangOkXml opts fileBaseName =
@@ -218,7 +218,7 @@ assertEvalFail file =
218218
do
219219
time <- liftIO getCurrentTime
220220
evalResult <- printNix <$> hnixEvalFile (defaultOptions time) file
221-
evalResult `seq` assertFailure $ "File: ''" <> coerce file <> "'' should not evaluate.\nThe evaluation result was `" <> evalResult <> "`."
221+
evalResult `seq` assertFailure $ "File: ''" <> coerce file <> "'' should not evaluate.\nThe evaluation result was `" <> toString evalResult <> "`."
222222

223223
nixTestDir :: FilePath
224224
nixTestDir = "data/nix/tests/lang/"

tests/PrettyTests.hs

Lines changed: 31 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -9,29 +9,48 @@ import Nix.Expr
99
import Nix.Pretty
1010

1111
case_indented_antiquotation :: Assertion
12-
case_indented_antiquotation = do
13-
assertPretty (mkIndentedStr 0 "echo $foo") "''echo $foo''"
14-
assertPretty (mkIndentedStr 0 "echo ${foo}") "''echo ''${foo}''"
12+
case_indented_antiquotation =
13+
do
14+
assertPretty
15+
(mkIndentedStr 0 "echo $foo")
16+
"''echo $foo''"
17+
assertPretty
18+
(mkIndentedStr 0 "echo ${foo}")
19+
"''echo ''${foo}''"
1520

1621
case_string_antiquotation :: Assertion
17-
case_string_antiquotation = do
18-
assertPretty (mkStr "echo $foo") "\"echo \\$foo\""
19-
assertPretty (mkStr "echo ${foo}") "\"echo \\${foo}\""
22+
case_string_antiquotation =
23+
do
24+
assertPretty
25+
(mkStr "echo $foo")
26+
"\"echo \\$foo\""
27+
assertPretty
28+
(mkStr "echo ${foo}")
29+
"\"echo \\${foo}\""
2030

2131
case_function_params :: Assertion
2232
case_function_params =
23-
assertPretty (mkFunction (mkVariadicParamSet mempty) (mkInt 3)) "{ ... }:\n 3"
33+
assertPretty
34+
(mkFunction (mkVariadicParamSet mempty) (mkInt 3))
35+
"{ ... }:\n 3"
2436

2537
case_paths :: Assertion
26-
case_paths = do
27-
assertPretty (mkPath False "~/test.nix") "~/test.nix"
28-
assertPretty (mkPath False "/test.nix") "/test.nix"
29-
assertPretty (mkPath False "./test.nix") "./test.nix"
38+
case_paths =
39+
do
40+
assertPretty
41+
(mkPath False "~/test.nix")
42+
"~/test.nix"
43+
assertPretty
44+
(mkPath False "/test.nix")
45+
"/test.nix"
46+
assertPretty
47+
(mkPath False "./test.nix")
48+
"./test.nix"
3049

3150
tests :: TestTree
3251
tests = $testGroupGenerator
3352

3453
---------------------------------------------------------------------------------
35-
assertPretty :: NExpr -> String -> Assertion
54+
assertPretty :: NExpr -> Text -> Assertion
3655
assertPretty e s =
3756
assertEqual ("When pretty-printing " <> show e) s . show $ prettyNix e

tests/TestCommon.hs

Lines changed: 24 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module TestCommon where
55
import GHC.Err ( errorWithoutStackTrace )
66
import Control.Monad.Catch
77
import Data.Time
8+
import Data.Text.IO as Text
89
import Nix
910
import Nix.Standard
1011
import Nix.Fresh.Basic
@@ -45,30 +46,31 @@ hnixEvalText opts src =
4546
)
4647
(parseNixText src)
4748

48-
nixEvalString :: String -> IO String
49-
nixEvalString expr = do
50-
(coerce -> fp, h) <- mkstemp "nix-test-eval"
51-
hPutStr h expr
52-
hClose h
53-
res <- nixEvalFile fp
54-
removeLink $ coerce fp
55-
pure res
49+
nixEvalString :: Text -> IO Text
50+
nixEvalString expr =
51+
do
52+
(coerce -> fp, h) <- mkstemp "nix-test-eval"
53+
Text.hPutStr h expr
54+
hClose h
55+
res <- nixEvalFile fp
56+
removeLink $ coerce fp
57+
pure res
5658

57-
nixEvalFile :: Path -> IO String
58-
nixEvalFile fp = readProcess "nix-instantiate" ["--eval", "--strict", coerce fp] mempty
59+
nixEvalFile :: Path -> IO Text
60+
nixEvalFile fp = fromString <$> readProcess "nix-instantiate" ["--eval", "--strict", coerce fp] mempty
5961

6062
assertEvalFileMatchesNix :: Path -> Assertion
61-
assertEvalFileMatchesNix fp = do
62-
time <- liftIO getCurrentTime
63-
hnixVal <- (<> "\n") . printNix <$> hnixEvalFile (defaultOptions time) fp
64-
nixVal <- nixEvalFile fp
65-
assertEqual (coerce fp) nixVal hnixVal
63+
assertEvalFileMatchesNix fp =
64+
do
65+
time <- liftIO getCurrentTime
66+
hnixVal <- (<> "\n") . printNix <$> hnixEvalFile (defaultOptions time) fp
67+
nixVal <- nixEvalFile fp
68+
assertEqual (coerce fp) nixVal hnixVal
6669

6770
assertEvalMatchesNix :: Text -> Assertion
68-
assertEvalMatchesNix expr = do
69-
time <- liftIO getCurrentTime
70-
hnixVal <- (<> "\n") . printNix <$> hnixEvalText (defaultOptions time) expr
71-
nixVal <- nixEvalString expr'
72-
assertEqual expr' nixVal hnixVal
73-
where
74-
expr' = toString expr
71+
assertEvalMatchesNix expr =
72+
do
73+
time <- liftIO getCurrentTime
74+
hnixVal <- (<> "\n") . printNix <$> hnixEvalText (defaultOptions time) expr
75+
nixVal <- nixEvalString expr
76+
assertEqual (toString expr) nixVal hnixVal

0 commit comments

Comments
 (0)