Skip to content

Commit 0864e1a

Browse files
committed
treewide: merge Prelude with Utils
This allows to achieve Zen of Text<->String & Path<->FilePath. Set of functions for Text & Path now can be formed & exported.
1 parent 663a53e commit 0864e1a

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

45 files changed

+93
-121
lines changed

benchmarks/ParserBench.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
module ParserBench (benchmarks) where
22

3-
import Nix.Utils
43
import Nix.Parser
54

65
import Criterion

hnix.cabal

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -384,7 +384,6 @@ library
384384
Nix.Type.Env
385385
Nix.Type.Infer
386386
Nix.Type.Type
387-
Nix.Utils
388387
Nix.Utils.Fix1
389388
Nix.Value
390389
Nix.Value.Equal
@@ -399,7 +398,6 @@ library
399398
src
400399
mixins:
401400
base hiding (Prelude)
402-
, relude (Relude as Prelude)
403401
, relude
404402
ghc-options:
405403
-Wall
@@ -534,7 +532,6 @@ executable hnix
534532
, time
535533
mixins:
536534
base hiding (Prelude)
537-
, relude (Relude as Prelude)
538535
, relude
539536
default-extensions:
540537
OverloadedStrings
@@ -582,7 +579,6 @@ test-suite hnix-tests
582579
TestCommon
583580
mixins:
584581
base hiding (Prelude)
585-
, relude (Relude as Prelude)
586582
, relude
587583
hs-source-dirs:
588584
tests
@@ -654,7 +650,6 @@ benchmark hnix-benchmarks
654650
benchmarks
655651
mixins:
656652
base hiding (Prelude)
657-
, relude (Relude as Prelude)
658653
, relude
659654
ghc-options:
660655
-Wall

main/Main.hs

Lines changed: 8 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,16 @@
44

55
module Main ( main ) where
66

7-
import Nix.Utils
7+
import Relude as Prelude ( force )
88
import Control.Comonad ( extract )
99
import qualified Control.Exception as Exception
1010
import GHC.Err ( errorWithoutStackTrace )
1111
import Control.Monad.Free
1212
import Control.Monad.Ref ( MonadRef(readRef) )
1313
import Control.Monad.Catch
14-
import System.IO ( hPutStrLn
15-
, getContents
16-
)
14+
import System.IO ( hPutStrLn )
1715
import qualified Data.HashMap.Lazy as M
1816
import qualified Data.Map as Map
19-
import Data.Maybe ( fromJust )
20-
import qualified Data.String as String
2117
import Data.Time
2218
import qualified Data.Text.IO as Text
2319
import Text.Show.Pretty ( ppShow )
@@ -55,14 +51,14 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
5551
execContentsFilesOrRepl :: StandardT (StdIdT IO) ()
5652
execContentsFilesOrRepl =
5753
fromMaybe
58-
loadFromCLIFilePathList
54+
loadFromCliFilePathList
5955
( loadBinaryCacheFile <|>
6056
loadLiteralExpression <|>
6157
loadExpressionFromFile
6258
)
6359
where
6460
-- | The base case: read expressions from the last CLI directive (@[FILE]@) listed on the command line.
65-
loadFromCLIFilePathList =
61+
loadFromCliFilePathList =
6662
case filePaths of
6763
[] -> runRepl
6864
["-"] -> readExpressionFromStdin
@@ -96,10 +92,10 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
9692
-- We can start use Text as in the base case, requires changing Path -> Text
9793
-- But that is a gradual process:
9894
-- https://github.com/haskell-nix/hnix/issues/912
99-
(processSeveralFiles . (coerce <$>) . String.lines <=< liftIO) .
95+
(processSeveralFiles . (coerce . toString <$>) . lines <=< liftIO) .
10096
(\case
101-
"-" -> getContents
102-
_fp -> readFile _fp
97+
"-" -> Text.getContents
98+
_fp -> Text.readFile _fp
10399
) <$> fromFile
104100

105101
processExpr text = handleResult Nothing $ parseNixTextLoc text
@@ -125,7 +121,7 @@ main' opts@Options{..} = runWithBasicEffectsIO opts execContentsFilesOrRepl
125121
either
126122
(\ err -> errorWithoutStackTrace $ "Type error: " <> ppShow err)
127123
(\ ty -> liftIO $ putStrLn $ "Type of expression: " <>
128-
ppShow (fromJust $ Map.lookup @VarName @[Scheme] "it" (coerce ty))
124+
ppShow (fromMaybe mempty $ Map.lookup @VarName @[Scheme] "it" $ coerce ty)
129125
)
130126
(HM.inferTop mempty [("it", stripAnnotation expr')])
131127

main/Repl.hs

Lines changed: 26 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ module Repl
1717
import Prelude hiding ( state )
1818
import Nix hiding ( exec )
1919
import Nix.Scope
20-
import Nix.Utils
2120
import Nix.Value.Monad ( demand )
2221

2322
import qualified Data.HashMap.Lazy as M
@@ -268,11 +267,15 @@ printValue :: (MonadNix e t f m, MonadIO m)
268267
-> Repl e t f m ()
269268
printValue val = do
270269
cfg <- replCfg <$> get
270+
let
271+
g :: MonadIO m => Doc ann0 -> m ()
272+
g = liftIO . print
273+
271274
lift $ lift $
272275
(if
273-
| cfgStrict cfg -> liftIO . print . prettyNValue <=< normalForm
274-
| cfgValues cfg -> liftIO . print . prettyNValueProv <=< removeEffects
275-
| otherwise -> liftIO . print . prettyNValue <=< removeEffects
276+
| cfgStrict cfg -> g . prettyNValue <=< normalForm
277+
| cfgValues cfg -> g . prettyNValueProv <=< removeEffects
278+
| otherwise -> g . prettyNValue <=< removeEffects
276279
) val
277280

278281

@@ -297,16 +300,15 @@ browse _ =
297300
load
298301
:: (MonadNix e t f m, MonadIO m)
299302
-- This one does I String -> O String pretty fast, it is ugly to double marshall here.
300-
=> String
303+
=> Path
301304
-> Repl e t f m ()
302-
load args =
305+
load path =
303306
do
304-
contents <- liftIO $
305-
Text.readFile $
306-
trim args
307+
contents <- liftIO $ Prelude.readFile $
308+
trim path
307309
void $ exec True contents
308310
where
309-
trim = dropWhileEnd isSpace . dropWhile isSpace
311+
trim = dropWhileEnd isSpace . dropWhile isSpace . coerce
310312

311313
-- | @:type@ command
312314
typeof
@@ -404,14 +406,20 @@ completeFunc reversedPrev word
404406
candidates
405407
)
406408
)
407-
(M.lookup (coerce var) (coerce $ replCtx state))
409+
(M.lookup (coerce var) $ coerce $ replCtx state)
408410

409411
-- Builtins, context variables
410412
| otherwise =
411413
do
412414
state <- get
413-
let contextKeys = M.keys @VarName @(NValue t f m) (coerce $ replCtx state)
414-
(Just (NVSet _ builtins)) = M.lookup "builtins" (coerce $ replCtx state)
415+
let
416+
scopeHashMap :: HashMap VarName (NValue t f m)
417+
scopeHashMap = coerce $ replCtx state
418+
contextKeys :: [VarName]
419+
contextKeys = M.keys scopeHashMap
420+
builtins :: AttrSet (NValue t f m)
421+
(Just (NVSet _ builtins)) = M.lookup "builtins" scopeHashMap
422+
shortBuiltins :: [VarName]
415423
shortBuiltins = M.keys builtins
416424

417425
pure $ listCompletion $ toString <$>
@@ -468,7 +476,7 @@ helpOptions =
468476
"help"
469477
""
470478
"Print help text"
471-
(help helpOptions . toText)
479+
(help helpOptions . fromString)
472480
, HelpOption
473481
"paste"
474482
""
@@ -478,17 +486,17 @@ helpOptions =
478486
"load"
479487
"FILENAME"
480488
"Load .nix file into scope"
481-
load
489+
(load . fromString)
482490
, HelpOption
483491
"browse"
484492
""
485493
"Browse bindings in interpreter context"
486-
(browse . toText)
494+
(browse . fromString)
487495
, HelpOption
488496
"type"
489497
"EXPRESSION"
490498
"Evaluate expression or binding from context and print the type of the result value"
491-
(typeof . toText)
499+
(typeof . fromString)
492500
, HelpOption
493501
"quit"
494502
""
@@ -503,7 +511,7 @@ helpOptions =
503511
<> Prettyprinter.line
504512
<> renderSetOptions helpSetOptions
505513
)
506-
(setConfig . toText)
514+
(setConfig . fromString)
507515
]
508516

509517
-- | Options for :set

src/Nix.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,6 @@ import Nix.Pretty
4747
import Nix.Reduce
4848
import Nix.Render.Frame
4949
import Nix.Thunk
50-
import Nix.Utils
5150
import Nix.Value
5251
import Nix.Value.Monad
5352
import Nix.XML

src/Nix/Builtins.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,9 +21,7 @@ module Nix.Builtins
2121
where
2222

2323

24-
import Prelude hiding ( traceM )
2524
import GHC.Exception ( ErrorCall(ErrorCall) )
26-
import Nix.Utils
2725
import Control.Comonad ( Comonad )
2826
import Control.Monad ( foldM )
2927
import Control.Monad.Catch ( MonadCatch(catch) )

src/Nix/Cache.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
module Nix.Cache where
55

66
import qualified Data.ByteString.Lazy as BSL
7-
import Nix.Utils
87
import Nix.Expr.Types.Annotated
98

109
#if defined (__linux__)

src/Nix/Cited/Basic.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44

55
module Nix.Cited.Basic where
66

7-
import Prelude hiding ( force )
87
import Control.Comonad ( Comonad )
98
import Control.Comonad.Env ( ComonadEnv )
109
import Control.Monad.Catch hiding ( catchJust )
@@ -16,7 +15,6 @@ import Nix.Expr.Types.Annotated
1615
import Nix.Frames
1716
import Nix.Options
1817
import Nix.Thunk
19-
import Nix.Utils
2018
import Nix.Value
2119

2220

src/Nix/Context.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@ import Nix.Frames ( Frames )
77
import Nix.Expr.Types.Annotated ( SrcSpan
88
, nullSpan
99
)
10-
import Nix.Utils ( Has(..) )
1110

1211
-- 2021-07-18: NOTE: It should be Options -> Scopes -> Frames -> Source(span)
1312
data Context m t = Context

src/Nix/Convert.hs

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@
1515

1616
module Nix.Convert where
1717

18-
import Prelude hiding ( force )
1918
import Control.Monad.Free
2019
import qualified Data.HashMap.Lazy as M
2120
import Nix.Atoms
@@ -27,7 +26,6 @@ import Nix.String
2726
import Nix.Value
2827
import Nix.Value.Monad
2928
import Nix.Thunk ( MonadThunk(force) )
30-
import Nix.Utils
3129

3230
newtype Deeper a = Deeper a
3331
deriving (Typeable, Functor, Foldable, Traversable)
@@ -233,6 +231,17 @@ instance Convertible e t f m
233231

234232
fromValue = fromMayToValue $ TString mempty
235233

234+
instance Convertible e t f m
235+
=> FromValue Text m (NValue' t f m (NValue t f m)) where
236+
237+
fromValueMay =
238+
pure .
239+
\case
240+
NVStr' ns -> getStringNoContext ns
241+
_ -> mempty
242+
243+
fromValue = fromMayToValue $ TString mempty
244+
236245
instance ( Convertible e t f m
237246
, MonadValue (NValue t f m) m
238247
)
@@ -374,6 +383,10 @@ instance Convertible e t f m
374383
=> ToValue ByteString m (NValue' t f m (NValue t f m)) where
375384
toValue = pure . nvStr' . mkNixStringWithoutContext . decodeUtf8
376385

386+
instance Convertible e t f m
387+
=> ToValue Text m (NValue' t f m (NValue t f m)) where
388+
toValue = pure . nvStr' . mkNixStringWithoutContext
389+
377390
instance Convertible e t f m
378391
=> ToValue Path m (NValue' t f m (NValue t f m)) where
379392
toValue = pure . nvPath' . coerce

0 commit comments

Comments
 (0)