(#1027) mk mod Prelude NoImplicitPrelude, mv mod Prelude (->Nix.)

This commit is contained in:
Anton Latukha 2022-01-12 23:17:07 +02:00 committed by GitHub
parent 27e357db89
commit 9bccd0fd05
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
63 changed files with 102 additions and 69 deletions

View File

@ -1,5 +1,6 @@
module Main where
import Nix.Prelude
import Criterion.Main
import qualified ParserBench

View File

@ -1,5 +1,6 @@
module ParserBench (benchmarks) where
import Nix.Prelude
import Nix.Parser
import Criterion

View File

@ -341,8 +341,8 @@ flag profiling
library
exposed-modules:
Prelude
Nix
Nix.Prelude
Nix.Utils
Nix.Atoms
Nix.Builtins
@ -398,9 +398,6 @@ library
Paths_hnix
hs-source-dirs:
src
mixins:
base hiding (Prelude)
, relude
ghc-options:
-Wall
-fprint-potential-instances
@ -469,7 +466,8 @@ library
, vector >= 0.12.0 && < 0.13
, xml >= 1.3.14 && < 1.4
default-extensions:
OverloadedStrings
NoImplicitPrelude
, OverloadedStrings
, DeriveGeneric
, DeriveDataTypeable
, DeriveFunctor
@ -532,11 +530,9 @@ executable hnix
, serialise
, template-haskell
, time
mixins:
base hiding (Prelude)
, relude
default-extensions:
OverloadedStrings
NoImplicitPrelude
, OverloadedStrings
, DeriveGeneric
, DeriveDataTypeable
, DeriveFunctor
@ -579,9 +575,6 @@ test-suite hnix-tests
PrettyTests
ReduceExprTests
TestCommon
mixins:
base hiding (Prelude)
, relude
hs-source-dirs:
tests
ghc-options:
@ -615,7 +608,8 @@ test-suite hnix-tests
, time
, unix-compat
default-extensions:
OverloadedStrings
NoImplicitPrelude
, OverloadedStrings
, DeriveGeneric
, DeriveDataTypeable
, DeriveFunctor
@ -650,9 +644,6 @@ benchmark hnix-benchmarks
ParserBench
hs-source-dirs:
benchmarks
mixins:
base hiding (Prelude)
, relude
ghc-options:
-Wall
build-depends:
@ -668,7 +659,8 @@ benchmark hnix-benchmarks
, template-haskell
, time
default-extensions:
OverloadedStrings
NoImplicitPrelude
, OverloadedStrings
, DeriveGeneric
, DeriveDataTypeable
, DeriveFunctor

View File

@ -4,6 +4,7 @@
module Main ( main ) where
import Nix.Prelude
import Relude as Prelude ( force )
import Control.Comonad ( extract )
import qualified Control.Exception as Exception

View File

@ -14,16 +14,16 @@ module Repl
, main'
) where
import Prelude hiding ( state )
import Nix.Prelude hiding ( state )
import Nix hiding ( exec )
import Nix.Scope
import Nix.Value.Monad ( demand )
import qualified Data.HashMap.Lazy as M
import qualified Data.HashMap.Lazy as M
import Data.Char ( isSpace )
import Data.List ( dropWhileEnd )
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import Data.Version ( showVersion )
import Paths_hnix ( version )
@ -33,7 +33,7 @@ import Prettyprinter ( Doc
, space
)
import qualified Prettyprinter
import qualified Prettyprinter.Render.Text as Prettyprinter
import qualified Prettyprinter.Render.Text as Prettyprinter
import System.Console.Haskeline.Completion
( Completion(isFinished)
@ -49,9 +49,9 @@ import System.Console.Repline ( Cmd
, HaskelineT
, evalRepl
)
import qualified System.Console.Repline as Console
import qualified System.Exit as Exit
import qualified System.IO.Error as Error
import qualified System.Console.Repline as Console
import qualified System.Exit as Exit
import qualified System.IO.Error as Error
-- | Repl entry point
main :: (MonadNix e t f m, MonadIO m, MonadMask m) => m ()

View File

@ -1,4 +1,3 @@
module Nix
( module Nix.Cache
, module Nix.Exec
@ -25,6 +24,7 @@ module Nix
)
where
import Nix.Prelude
import Relude.Unsafe ( (!!) )
import GHC.Err ( errorWithoutStackTrace )
import Data.Fix ( Fix )

View File

@ -1,8 +1,9 @@
{-# language CPP #-}
{-# language DeriveAnyClass #-}
{-# language CPP #-}
{-# language DeriveAnyClass #-}
module Nix.Atoms where
import Nix.Prelude
import Codec.Serialise ( Serialise )
import Data.Data ( Data)

View File

@ -13,6 +13,7 @@
{-# options_ghc -fno-warn-name-shadowing #-}
-- | Code that implements Nix builtins. Lists the functions that are built into the Nix expression evaluator. Some built-ins (aka `derivation`), are always in the scope, so they can be accessed by the name. To keap the namespace clean, most built-ins are inside the `builtins` scope - a set that contains all what is a built-in.
module Nix.Builtins
( withNixContext
@ -20,7 +21,7 @@ module Nix.Builtins
)
where
import Nix.Prelude
import GHC.Exception ( ErrorCall(ErrorCall) )
import Control.Comonad ( Comonad )
import Control.Monad ( foldM )

View File

@ -3,6 +3,7 @@
-- | Reading and writing Nix cache files
module Nix.Cache where
import Nix.Prelude
import qualified Data.ByteString.Lazy as BSL
import Nix.Expr.Types.Annotated

View File

@ -5,6 +5,7 @@
module Nix.Cited where
import Nix.Prelude
import Control.Comonad
import Control.Comonad.Env
import Lens.Family2.TH

View File

@ -4,6 +4,7 @@
module Nix.Cited.Basic where
import Nix.Prelude
import Control.Comonad ( Comonad )
import Control.Comonad.Env ( ComonadEnv )
import Control.Monad.Catch hiding ( catchJust )

View File

@ -1,6 +1,6 @@
module Nix.Context where
import Nix.Prelude
import Nix.Options ( Options )
import Nix.Scope ( Scopes )
import Nix.Frames ( Frames )

View File

@ -15,6 +15,7 @@
module Nix.Convert where
import Nix.Prelude
import Control.Monad.Free
import qualified Data.HashMap.Lazy as M
import Nix.Atoms

View File

@ -12,9 +12,10 @@
module Nix.Effects where
import Prelude hiding ( putStrLn
import Nix.Prelude hiding ( putStrLn
, print
)
import qualified Nix.Prelude as Prelude
import GHC.Exception ( ErrorCall(ErrorCall) )
import qualified Data.HashSet as HS
import qualified Data.Text as Text

View File

@ -2,7 +2,7 @@
module Nix.Effects.Basic where
import Prelude hiding ( head
import Nix.Prelude hiding ( head
)
import Relude.Unsafe ( head )
import GHC.Exception ( ErrorCall(ErrorCall) )

View File

@ -5,7 +5,7 @@
module Nix.Effects.Derivation ( defaultDerivationStrict ) where
import Prelude hiding ( readFile )
import Nix.Prelude hiding ( readFile )
import GHC.Exception ( ErrorCall(ErrorCall) )
import Data.Char ( isAscii
, isAlphaNum

View File

@ -3,9 +3,9 @@
{-# language RankNTypes #-}
module Nix.Eval where
import Nix.Prelude
import Relude.Extra ( set )
import Control.Monad ( foldM )
import Control.Monad.Fix ( MonadFix )

View File

@ -12,7 +12,7 @@
module Nix.Exec where
import Prelude hiding ( putStr
import Nix.Prelude hiding ( putStr
, putStrLn
, print
)
@ -44,7 +44,7 @@ import Nix.Value.Monad
import Prettyprinter
import qualified Text.Show.Pretty as PS
#ifdef MIN_VERSION_ghc_datasize
#ifdef MIN_VERSION_ghc_datasize
import GHC.DataSize
#endif

View File

@ -1,10 +1,10 @@
-- | Shorthands for making Nix expressions.
--
-- Functions with an @F@ suffix return a more general type (base functor @F a@) without the outer
-- 'Fix' wrapper that creates @a@.
module Nix.Expr.Shorthands where
import Nix.Prelude
import Data.Fix
import Nix.Atoms
import Nix.Expr.Types

View File

@ -1,7 +1,7 @@
-- | Functions for manipulating nix strings.
module Nix.Expr.Strings where
import Nix.Prelude
import Relude.Unsafe as Unsafe
-- Please, switch things to NonEmpty
import Data.List ( dropWhileEnd

View File

@ -20,7 +20,8 @@
-- (additiona info for dev): Big use of TemplateHaskell in the module requires proper (top-down) organization of declarations.
module Nix.Expr.Types where
import qualified Codec.Serialise as Serialise
import Nix.Prelude
import qualified Codec.Serialise as Serialise
import Codec.Serialise ( Serialise )
import Control.DeepSeq ( NFData1(..) )
import Data.Aeson

View File

@ -16,6 +16,7 @@ module Nix.Expr.Types.Annotated
)
where
import Nix.Prelude
import Codec.Serialise
import Control.DeepSeq
import Data.Aeson ( ToJSON(..)

View File

@ -15,6 +15,7 @@ module Nix.Frames
)
where
import Nix.Prelude
import Data.Typeable hiding ( typeOf )
import Control.Monad.Catch ( MonadThrow(..) )
import qualified Text.Show

View File

@ -8,6 +8,7 @@
module Nix.Fresh where
import Nix.Prelude
import Control.Monad.Base ( MonadBase(..) )
import Control.Monad.Catch ( MonadCatch
, MonadMask

View File

@ -8,6 +8,7 @@ module Nix.Fresh.Basic where
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ( MonadFail )
#endif
import Nix.Prelude
import Nix.Effects
import Nix.Render
import Nix.Fresh

View File

@ -2,6 +2,7 @@
module Nix.Json where
import Nix.Prelude
import qualified Data.Aeson as A
import qualified Data.Aeson.Encoding as A
import qualified Data.Vector as V

View File

@ -11,6 +11,7 @@
module Nix.Lint where
import Nix.Prelude
import Relude.Unsafe as Unsafe ( head )
import Control.Exception ( throw )
import GHC.Exception ( ErrorCall(ErrorCall) )

View File

@ -10,6 +10,7 @@
-- And so do not converge into a normal form.
module Nix.Normal where
import Nix.Prelude
import Control.Monad.Free ( Free(..) )
import Data.Set ( member
, insert

View File

@ -3,6 +3,7 @@
-- | Definitions & defaults for the CLI options
module Nix.Options where
import Nix.Prelude
import Data.Time
-- 2021-07-15: NOTE: What these are? They need to be documented.

View File

@ -3,6 +3,7 @@
-- | Code that configures presentation parser for the CLI options
module Nix.Options.Parser where
import Nix.Prelude
import Relude.Unsafe ( read )
import GHC.Err ( errorWithoutStackTrace )
import Data.Char ( isDigit )

View File

@ -40,7 +40,7 @@ module Nix.Parser
)
where
import Prelude hiding ( (<|>)
import Nix.Prelude hiding ( (<|>)
, some
, many
)

View File

@ -3,7 +3,7 @@
-- between our custom code ("Nix.Utils") that shadows over the outside prelude that is in use ("Relude")
-- "Prelude" module has a problem of being imported & used by other projects.
-- "Nix.Utils" as a module with a regular name does not have that problem.
module Prelude
module Nix.Prelude
( module Nix.Utils
, module Relude
) where

View File

@ -1,12 +1,11 @@
{-# language CPP #-}
{-# language AllowAmbiguousTypes #-}
{-# options_ghc -fno-warn-name-shadowing #-}
module Nix.Pretty where
import Prelude hiding ( toList, group )
import Nix.Prelude hiding ( toList, group )
import Control.Monad.Free ( Free(Free) )
import Data.Fix ( Fix(..)
, foldFix )

View File

@ -20,6 +20,7 @@ module Nix.Reduce
, reducingEvalExpr
) where
import Nix.Prelude
import Control.Monad.Catch ( MonadCatch(catch) )
#if !MIN_VERSION_base(4,13,0)
import Prelude hiding ( fail )

View File

@ -9,6 +9,7 @@
module Nix.Render where
import Nix.Prelude
import qualified Data.Set as Set
import Nix.Utils.Fix1 ( Fix1T
, MonadFix1T
@ -24,7 +25,7 @@ import qualified Data.Text as Text
class (MonadFail m, MonadIO m) => MonadFile m where
readFile :: Path -> m Text
default readFile :: (MonadTrans t, MonadIO m', MonadFile m', m ~ t m') => Path -> m Text
readFile = liftIO . Prelude.readFile
readFile = liftIO . Nix.Prelude.readFile
listDirectory :: Path -> m [Path]
default listDirectory :: (MonadTrans t, MonadFile m', m ~ t m') => Path -> m [Path]
listDirectory = lift . listDirectory
@ -51,7 +52,7 @@ class (MonadFail m, MonadIO m) => MonadFile m where
getSymbolicLinkStatus = lift . getSymbolicLinkStatus
instance MonadFile IO where
readFile = Prelude.readFile
readFile = Nix.Prelude.readFile
listDirectory = coerce S.listDirectory
getCurrentDirectory = coerce S.getCurrentDirectory
canonicalizePath = coerce S.canonicalizePath

View File

@ -9,7 +9,7 @@
-- | Code for rendering/representation of the messages packaged with their context (Frames).
module Nix.Render.Frame where
import Prelude hiding ( Comparison )
import Nix.Prelude hiding ( Comparison )
import GHC.Exception ( ErrorCall )
import Data.Fix ( Fix(..) )
import Nix.Eval hiding ( addMetaInfo )

View File

@ -1,4 +1,4 @@
{-# LANGUAGE UndecidableInstances #-}
{-# language UndecidableInstances #-}
{-# language AllowAmbiguousTypes #-}
{-# language ConstraintKinds #-}
{-# language FunctionalDependencies #-}
@ -6,6 +6,7 @@
module Nix.Scope where
import Nix.Prelude
import qualified Data.HashMap.Lazy as M
import qualified Text.Show
import Lens.Family2

View File

@ -8,6 +8,7 @@
module Nix.Standard where
import Nix.Prelude
import Control.Comonad ( Comonad )
import Control.Comonad.Env ( ComonadEnv )
import Control.Monad.Catch ( MonadThrow

View File

@ -32,6 +32,7 @@ where
import Nix.Prelude hiding ( Type, TVar )
import Control.Monad.Writer ( WriterT(..), MonadWriter(tell))
import qualified Data.HashMap.Lazy as M
import qualified Data.HashSet as S

View File

@ -2,6 +2,7 @@
module Nix.String.Coerce where
import Nix.Prelude
import Control.Monad.Catch ( MonadThrow )
import GHC.Exception ( ErrorCall(ErrorCall) )
import qualified Data.HashMap.Lazy as M

View File

@ -5,6 +5,7 @@
module Nix.TH where
import Nix.Prelude
import Data.Generics.Aliases ( extQ )
import qualified Data.Set as Set
import Language.Haskell.TH

View File

@ -4,6 +4,7 @@
module Nix.Thunk where
import Nix.Prelude
import Control.Monad.Trans.Writer ( WriterT )
import qualified Text.Show

View File

@ -10,6 +10,7 @@ module Nix.Thunk.Basic
, MonadBasicThunk
) where
import Nix.Prelude
import Control.Monad.Ref ( MonadRef(Ref, newRef, readRef, writeRef)
, MonadAtomicRef(atomicModifyRef)
)

View File

@ -1,6 +1,7 @@
{-# language TypeFamilies #-}
-- | Basing on the Nix (HindleyMilner) type system (that provides decidable type inference):
-- gathering assumptions (inference evidence) about polymorphic types.
{-# language TypeFamilies #-}
module Nix.Type.Assumption
( Assumption(..)
, empty
@ -13,7 +14,7 @@ module Nix.Type.Assumption
)
where
import Prelude hiding ( Type
import Nix.Prelude hiding ( Type
, empty
)
@ -36,6 +37,7 @@ instance One Assumption where
type OneItem Assumption = (VarName, Type)
one vt = Assumption $ one vt
-- 2022-01-12: NOTE: `empty` implies Alternative. Either have Alternative or use `mempty`
empty :: Assumption
empty = Assumption mempty

View File

@ -1,4 +1,5 @@
{-# language TypeFamilies #-}
module Nix.Type.Env
( Env(..)
, empty
@ -15,7 +16,7 @@ module Nix.Type.Env
)
where
import Prelude hiding ( empty
import Nix.Prelude hiding ( empty
, toList
, fromList
)

View File

@ -18,14 +18,14 @@ module Nix.Type.Infer
)
where
import Nix.Prelude hiding ( Constraint
, Type
, TVar
)
import Control.Monad.Catch ( MonadThrow(..)
, MonadCatch(..)
)
import Control.Monad.Except ( MonadError(throwError,catchError) )
import Prelude hiding ( Type
, TVar
, Constraint
)
import Control.Monad.Logic hiding ( fail )
import Control.Monad.Reader ( MonadFix )
import Control.Monad.Ref ( MonadAtomicRef(..)
@ -58,10 +58,6 @@ import Nix.String
import Nix.Scope
import Nix.Type.Assumption hiding ( extend )
import qualified Nix.Type.Assumption as Assumption
( remove
, lookup
, keys
)
import Nix.Type.Env
import qualified Nix.Type.Env as Env
import Nix.Type.Type

View File

@ -3,7 +3,7 @@
-- Therefore -> from this the type inference follows.
module Nix.Type.Type where
import Prelude hiding (Type, TVar)
import Nix.Prelude hiding ( Type, TVar )
import Nix.Expr.Types
-- | Hindrey-Milner type interface

View File

@ -8,6 +8,7 @@
module Nix.Unused
where
import Nix.Prelude
import Control.Monad.Free ( Free(..) )
import Data.Fix ( Fix(..) )
import Lens.Family2.TH ( makeLensesBy )

View File

@ -1,4 +1,3 @@
{-# language NoImplicitPrelude #-}
{-# language CPP #-}
{-# language GeneralizedNewtypeDeriving #-}

View File

@ -7,13 +7,15 @@
module Nix.Utils.Fix1 where
import Nix.Prelude
import Control.Monad.Fix ( MonadFix )
import Control.Monad.Ref ( MonadAtomicRef(..)
, MonadRef(..)
)
import Control.Monad.Catch ( MonadCatch
, MonadMask
, MonadThrow )
, MonadThrow
)
-- | The fixpoint combinator.
-- Courtesy of Gregory Malecha.

View File

@ -13,6 +13,7 @@
module Nix.Value
where
import Nix.Prelude
import Control.Comonad ( Comonad
, extract
)

View File

@ -6,7 +6,7 @@
module Nix.Value.Equal where
import Prelude hiding ( Comparison )
import Nix.Prelude hiding ( Comparison )
import Control.Comonad ( Comonad(extract))
import Control.Monad.Free ( Free(Pure,Free) )
import Control.Monad.Trans.Except ( throwE )

View File

@ -1,4 +1,3 @@
module Nix.Value.Monad where
-- * @MonadValue@ - a main implementation class

View File

@ -7,6 +7,7 @@
module Nix.Var ()
where
import Nix.Prelude
import Control.Monad.Ref
import Data.GADT.Compare ( GEq(..) )
import Data.STRef ( STRef )

View File

@ -1,8 +1,8 @@
module Nix.XML
( toXML )
where
import Nix.Prelude
import qualified Data.HashMap.Lazy as M
import Nix.Atoms
import Nix.Expr.Types

View File

@ -4,8 +4,12 @@
{-# options_ghc -Wno-missing-signatures #-}
module EvalTests (tests, genEvalCompareTests) where
module EvalTests
( tests
, genEvalCompareTests
) where
import Nix.Prelude
import Control.Monad.Catch
import Data.List ((\\))
import qualified Data.Set as S

View File

@ -2,6 +2,7 @@
module Main where
import Nix.Prelude
import Relude (force)
import Relude.Unsafe (read)
import qualified Control.Exception as Exc

View File

@ -1,6 +1,6 @@
module NixLanguageTests (genTests) where
import Nix.Prelude
import Control.Exception
import GHC.Err ( errorWithoutStackTrace )
import Control.Monad.ST

View File

@ -10,7 +10,7 @@
module ParserTests (tests) where
import Prelude hiding (($<))
import Nix.Prelude hiding (($<))
import Data.Fix
import NeatInterpolation (text)
import Nix.Atoms

View File

@ -6,6 +6,7 @@
module PrettyParseTests where
import Nix.Prelude
import Data.Algorithm.Diff
import Data.Algorithm.DiffOutput
import Data.Char

View File

@ -1,6 +1,8 @@
{-# language TemplateHaskell #-}
module PrettyTests (tests) where
module PrettyTests ( tests ) where
import Nix.Prelude
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH

View File

@ -1,5 +1,8 @@
{-# options_ghc -fno-warn-name-shadowing #-}
module ReduceExprTests (tests) where
import Nix.Prelude
import Test.Tasty
import Test.Tasty.HUnit

View File

@ -1,6 +1,6 @@
module TestCommon where
import Nix.Prelude
import GHC.Err ( errorWithoutStackTrace )
import Control.Monad.Catch
import Data.Time