2727module Nix.Expr.Types where
2828
2929#ifdef MIN_VERSION_serialise
30- import qualified Codec.Serialise ( Serialise ( decode , encode ) ) -- For instance implementation function disamburgation
30+ import qualified Codec.Serialise as Serialise
3131import Codec.Serialise ( Serialise )
3232#endif
3333import Control.Applicative
3434import Control.DeepSeq
3535import Control.Monad
3636import Data.Aeson
3737import Data.Aeson.TH
38+ import qualified Data.Binary as Binary
3839import Data.Binary ( Binary )
39- import qualified Data.Binary as Bin
4040import Data.Data
4141import Data.Eq.Deriving
4242import Data.Fix
@@ -65,8 +65,8 @@ import Nix.Utils
6565import Text.Megaparsec.Pos
6666import Text.Read.Deriving
6767import Text.Show.Deriving
68- import Type.Reflection ( eqTypeRep )
6968import qualified Type.Reflection as Reflection
69+ import Type.Reflection ( eqTypeRep )
7070
7171type VarName = Text
7272
@@ -347,16 +347,16 @@ data NKeyName r
347347instance Serialise r => Serialise (NKeyName r )
348348
349349instance Serialise Pos where
350- encode x = Codec. Serialise. encode (unPos x)
351- decode = mkPos <$> Codec. Serialise. decode
350+ encode = Serialise. encode . unPos
351+ decode = mkPos <$> Serialise. decode
352352
353353instance Serialise SourcePos where
354- encode (SourcePos f l c) = Codec. Serialise. encode f <> Codec. Serialise. encode l <> Codec. Serialise. encode c
355- decode = SourcePos <$> Codec. Serialise. decode <*> Codec. Serialise. decode <*> Codec. Serialise. decode
354+ encode (SourcePos f l c) = Serialise. encode f <> Serialise. encode l <> Serialise. encode c
355+ decode = SourcePos <$> Serialise. decode <*> Serialise. decode <*> Serialise. decode
356356#endif
357357
358358instance Hashable Pos where
359- hashWithSalt salt x = hashWithSalt salt (unPos x)
359+ hashWithSalt salt = hashWithSalt salt . unPos
360360
361361instance Hashable SourcePos where
362362 hashWithSalt salt (SourcePos f l c) =
@@ -418,7 +418,7 @@ instance Traversable NKeyName where
418418 DynamicKey (Plain str) -> DynamicKey . Plain <$> traverse f str
419419 DynamicKey (Antiquoted e ) -> DynamicKey . Antiquoted <$> f e
420420 DynamicKey EscapedNewline -> pure $ DynamicKey EscapedNewline
421- StaticKey key -> pure ( StaticKey key)
421+ StaticKey key -> pure $ StaticKey key
422422
423423-- | A selector (for example in a @let@ or an attribute set) is made up
424424-- of strung-together key names.
@@ -518,8 +518,8 @@ instance (Binary v, Binary a) => Binary (Antiquoted v a)
518518instance Binary a => Binary (NString a )
519519instance Binary a => Binary (Binding a )
520520instance Binary Pos where
521- put x = Bin . put (unPos x)
522- get = mkPos <$> Bin . get
521+ put = Binary . put . unPos
522+ get = mkPos <$> Binary . get
523523instance Binary SourcePos
524524instance Binary a => Binary (NKeyName a )
525525instance Binary a => Binary (Params a )
@@ -532,7 +532,7 @@ instance (ToJSON v, ToJSON a) => ToJSON (Antiquoted v a)
532532instance ToJSON a => ToJSON (NString a )
533533instance ToJSON a => ToJSON (Binding a )
534534instance ToJSON Pos where
535- toJSON x = toJSON (unPos x)
535+ toJSON = toJSON . unPos
536536instance ToJSON SourcePos
537537instance ToJSON a => ToJSON (NKeyName a )
538538instance ToJSON a => ToJSON (Params a )
@@ -566,8 +566,8 @@ $(makeTraversals ''NBinaryOp)
566566-- x $(makeLenses ''Fix)
567567
568568class NExprAnn ann g | g -> ann where
569- fromNExpr :: g r -> (NExprF r , ann )
570- toNExpr :: (NExprF r , ann ) -> g r
569+ fromNExpr :: g r -> (NExprF r , ann )
570+ toNExpr :: (NExprF r , ann ) -> g r
571571
572572ekey
573573 :: NExprAnn ann g
@@ -599,7 +599,7 @@ ekey _ _ f e = fromMaybe e <$> f Nothing
599599stripPositionInfo :: NExpr -> NExpr
600600stripPositionInfo = transport phi
601601 where
602- phi (NSet recur binds) = NSet recur ( fmap go binds)
602+ phi (NSet recur binds) = NSet recur $ fmap go binds
603603 phi (NLet binds body) = NLet (fmap go binds) body
604604 phi x = x
605605
0 commit comments