Skip to content

Commit e9958d8

Browse files
committed
clean-up
1 parent e82e9c4 commit e9958d8

File tree

5 files changed

+6
-8
lines changed

5 files changed

+6
-8
lines changed

src/Nix/Builtins.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -659,6 +659,7 @@ splitMatches numDropped (((_, (start, len)) : captures) : mts) haystack =
659659
caps = nvList (map f captures)
660660
f (a, (s, _)) = if s < 0 then nvConstant NNull else thunkStr a
661661

662+
thunkStr :: Applicative f => ByteString -> NValue t f m
662663
thunkStr s = nvStr (makeNixStringWithoutContext (decodeUtf8 s))
663664

664665
substring :: forall e t f m. MonadNix e t f m => Int -> Int -> NixString -> Prim m NixString
@@ -1512,16 +1513,16 @@ newtype Prim m a = Prim { runPrim :: m a }
15121513

15131514
-- | Types that support conversion to nix in a particular monad
15141515
class ToBuiltin t f m a | a -> m where
1515-
toBuiltin :: String -> a -> m (NValue t f m)
1516+
toBuiltin :: String -> a -> m (NValue t f m)
15161517

15171518
instance (MonadNix e t f m, ToValue a m (NValue t f m))
1518-
=> ToBuiltin t f m (Prim m a) where
1519+
=> ToBuiltin t f m (Prim m a) where
15191520
toBuiltin _ p = toValue =<< runPrim p
15201521

15211522
instance ( MonadNix e t f m
15221523
, FromValue a m (Deeper (NValue t f m))
15231524
, ToBuiltin t f m b
15241525
)
1525-
=> ToBuiltin t f m (a -> b) where
1526+
=> ToBuiltin t f m (a -> b) where
15261527
toBuiltin name f =
15271528
pure $ nvBuiltin name (fromValue . Deeper >=> toBuiltin name . f)

src/Nix/Lint.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE AllowAmbiguousTypes #-}
21
{-# LANGUAGE ConstraintKinds #-}
32
{-# LANGUAGE DataKinds #-}
43
{-# LANGUAGE DeriveTraversable #-}

src/Nix/Value/Equal.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
{-# LANGUAGE DeriveTraversable #-}
88
{-# LANGUAGE FlexibleContexts #-}
99
{-# LANGUAGE FlexibleInstances #-}
10-
{-# LANGUAGE FunctionalDependencies #-}
1110
{-# LANGUAGE GADTs #-}
1211
{-# LANGUAGE LambdaCase #-}
1312
{-# LANGUAGE OverloadedStrings #-}
@@ -88,7 +87,7 @@ isDerivationM f m = case M.lookup "type" m of
8887
Nothing -> pure False
8988

9089
isDerivation :: Monad m => (t -> Maybe NixString) -> AttrSet t -> Bool
91-
isDerivation f = runIdentity . isDerivationM (\x -> Identity (f x))
90+
isDerivation f = runIdentity . isDerivationM (Identity . f)
9291

9392
valueFEqM
9493
:: Monad n

tests/EvalTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
{-# LANGUAGE ScopedTypeVariables #-}
55
{-# LANGUAGE TemplateHaskell #-}
66

7-
{-# OPTIONS_GHC -Wno-missing-signatures -Wno-orphans #-}
7+
{-# OPTIONS_GHC -Wno-missing-signatures #-}
88

99
module EvalTests (tests, genEvalCompareTests) where
1010

tests/PrettyParseTests.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@
66
{-# LANGUAGE NoMonomorphismRestriction #-}
77
{-# LANGUAGE OverloadedStrings #-}
88

9-
{-# OPTIONS -Wno-orphans#-}
109

1110
module PrettyParseTests where
1211

0 commit comments

Comments
 (0)