hnix-0.5.1: Haskell implementation of the Nix language

Safe HaskellNone
LanguageHaskell2010

Nix.Expr.Types

Contents

Description

The nix expression type and supporting types.

Synopsis

Documentation

data NExprF r Source #

The main nix expression type. This is polymorphic so that it can be made a functor, which allows us to traverse expressions and map functions over them. The actual NExpr type is a fixed point of this functor, defined below.

Constructors

NConstant !NAtom

Constants: ints, bools, URIs, and null.

NStr !(NString r)

A string, with interpolated expressions.

NSym !VarName

A variable. For example, in the expression f a, f is represented as NSym "f" and a as NSym "a".

NList ![r]

A list literal.

NSet ![Binding r]

An attribute set literal, not recursive.

NRecSet ![Binding r]

An attribute set literal, recursive.

NLiteralPath !FilePath

A path expression, which is evaluated to a store path. The path here can be relative, in which case it's evaluated relative to the file in which it appears.

NEnvPath !FilePath

A path which refers to something in the Nix search path (the NIX_PATH environment variable. For example, nixpkgs/pkgs.

NUnary !NUnaryOp !r

Application of a unary operator to an expression.

NBinary !NBinaryOp !r !r

Application of a binary operator to two expressions.

NSelect !r !(NAttrPath r) !(Maybe r)

Dot-reference into an attribute set, optionally providing an alternative if the key doesn't exist.

NHasAttr !r !(NAttrPath r)

Ask if a set contains a given attribute path.

NAbs !(Params r) !r

A function literal (lambda abstraction).

NLet ![Binding r] !r

Evaluate the second argument after introducing the bindings.

NIf !r !r !r

If-then-else statement.

NWith !r !r

Evaluate an attribute set, bring its bindings into scope, and evaluate the second argument.

NAssert !r !r

Assert that the first returns true before evaluating the second.

Instances

Functor NExprF Source # 

Methods

fmap :: (a -> b) -> NExprF a -> NExprF b #

(<$) :: a -> NExprF b -> NExprF a #

IsString NExpr Source #

We make an IsString for expressions, where the string is interpreted as an identifier. This is the most common use-case...

Methods

fromString :: String -> NExpr #

Foldable NExprF Source # 

Methods

fold :: Monoid m => NExprF m -> m #

foldMap :: Monoid m => (a -> m) -> NExprF a -> m #

foldr :: (a -> b -> b) -> b -> NExprF a -> b #

foldr' :: (a -> b -> b) -> b -> NExprF a -> b #

foldl :: (b -> a -> b) -> b -> NExprF a -> b #

foldl' :: (b -> a -> b) -> b -> NExprF a -> b #

foldr1 :: (a -> a -> a) -> NExprF a -> a #

foldl1 :: (a -> a -> a) -> NExprF a -> a #

toList :: NExprF a -> [a] #

null :: NExprF a -> Bool #

length :: NExprF a -> Int #

elem :: Eq a => a -> NExprF a -> Bool #

maximum :: Ord a => NExprF a -> a #

minimum :: Ord a => NExprF a -> a #

sum :: Num a => NExprF a -> a #

product :: Num a => NExprF a -> a #

Traversable NExprF Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NExprF a -> f (NExprF b) #

sequenceA :: Applicative f => NExprF (f a) -> f (NExprF a) #

mapM :: Monad m => (a -> m b) -> NExprF a -> m (NExprF b) #

sequence :: Monad m => NExprF (m a) -> m (NExprF a) #

Hashable NExprLoc # 

Methods

hashWithSalt :: Int -> NExprLoc -> Int #

hash :: NExprLoc -> Int #

ToJSON NExpr Source # 
FromJSON NExpr Source # 
Eq1 NExprF Source # 

Methods

liftEq :: (a -> b -> Bool) -> NExprF a -> NExprF b -> Bool #

Show1 NExprF Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NExprF a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NExprF a] -> ShowS #

Binary NExprLoc # 

Methods

put :: NExprLoc -> Put #

get :: Get NExprLoc #

putList :: [NExprLoc] -> Put #

NFData NExprLoc # 

Methods

rnf :: NExprLoc -> () #

NFData1 NExprF Source # 

Methods

liftRnf :: (a -> ()) -> NExprF a -> () #

Hashable1 NExprF Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NExprF a -> Int #

Serialise NExpr Source # 
Serialise NExprLoc # 
Applicative m => ToNix Bool m (NExprF r) Source # 

Methods

toNix :: Bool -> m (NExprF r) Source #

Applicative m => ToNix () m (NExprF r) Source # 

Methods

toNix :: () -> m (NExprF r) Source #

Applicative m => ToValue Bool m (NExprF r) Source # 

Methods

toValue :: Bool -> m (NExprF r) Source #

Applicative m => ToValue () m (NExprF r) Source # 

Methods

toValue :: () -> m (NExprF r) Source #

Eq r => Eq (NExprF r) Source # 

Methods

(==) :: NExprF r -> NExprF r -> Bool #

(/=) :: NExprF r -> NExprF r -> Bool #

Data r => Data (NExprF r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NExprF r -> c (NExprF r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (NExprF r) #

toConstr :: NExprF r -> Constr #

dataTypeOf :: NExprF r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NExprF r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NExprF r)) #

gmapT :: (forall b. Data b => b -> b) -> NExprF r -> NExprF r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NExprF r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NExprF r -> r #

gmapQ :: (forall d. Data d => d -> u) -> NExprF r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NExprF r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NExprF r -> m (NExprF r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NExprF r -> m (NExprF r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NExprF r -> m (NExprF r) #

Ord r => Ord (NExprF r) Source # 

Methods

compare :: NExprF r -> NExprF r -> Ordering #

(<) :: NExprF r -> NExprF r -> Bool #

(<=) :: NExprF r -> NExprF r -> Bool #

(>) :: NExprF r -> NExprF r -> Bool #

(>=) :: NExprF r -> NExprF r -> Bool #

max :: NExprF r -> NExprF r -> NExprF r #

min :: NExprF r -> NExprF r -> NExprF r #

Show r => Show (NExprF r) Source # 

Methods

showsPrec :: Int -> NExprF r -> ShowS #

show :: NExprF r -> String #

showList :: [NExprF r] -> ShowS #

Generic (NExprF r) Source # 

Associated Types

type Rep (NExprF r) :: * -> * #

Methods

from :: NExprF r -> Rep (NExprF r) x #

to :: Rep (NExprF r) x -> NExprF r #

Lift (Fix NExprF) Source # 

Methods

lift :: Fix NExprF -> Q Exp #

Hashable r => Hashable (NExprF r) Source # 

Methods

hashWithSalt :: Int -> NExprF r -> Int #

hash :: NExprF r -> Int #

ToJSON a => ToJSON (NExprF a) Source # 
FromJSON a => FromJSON (NExprF a) Source # 
Binary a => Binary (NExprF a) Source # 

Methods

put :: NExprF a -> Put #

get :: Get (NExprF a) #

putList :: [NExprF a] -> Put #

Binary r => Binary (NExprLocF r) # 

Methods

put :: NExprLocF r -> Put #

get :: Get (NExprLocF r) #

putList :: [NExprLocF r] -> Put #

NFData r => NFData (NExprF r) Source # 

Methods

rnf :: NExprF r -> () #

Serialise r => Serialise (NExprF r) Source # 
Generic1 * NExprF Source # 

Associated Types

type Rep1 NExprF (f :: NExprF -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 NExprF f a #

to1 :: Rep1 NExprF f a -> f a #

Serialise r => Serialise (Compose * * (Ann SrcSpan) NExprF r) # 
type Rep (NExprF r) Source # 
type Rep (NExprF r) = D1 * (MetaData "NExprF" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NConstant" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NAtom))) (C1 * (MetaCons "NStr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (NString r))))) ((:+:) * (C1 * (MetaCons "NSym" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * VarName))) (C1 * (MetaCons "NList" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [r]))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Binding r]))) (C1 * (MetaCons "NRecSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Binding r])))) ((:+:) * (C1 * (MetaCons "NLiteralPath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath))) (C1 * (MetaCons "NEnvPath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NUnary" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NUnaryOp)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))) (C1 * (MetaCons "NBinary" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NBinaryOp)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))))) ((:+:) * (C1 * (MetaCons "NSelect" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (NAttrPath r))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe r)))))) (C1 * (MetaCons "NHasAttr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (NAttrPath r))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NAbs" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Params r))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))) (C1 * (MetaCons "NLet" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Binding r])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r))))) ((:+:) * (C1 * (MetaCons "NIf" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r))))) ((:+:) * (C1 * (MetaCons "NWith" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))) (C1 * (MetaCons "NAssert" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))))))))
type Rep1 * NExprF Source # 
type Rep1 * NExprF = D1 * (MetaData "NExprF" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NConstant" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NAtom))) (C1 * (MetaCons "NStr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 * NString)))) ((:+:) * (C1 * (MetaCons "NSym" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * VarName))) (C1 * (MetaCons "NList" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 * []))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ((:.:) * * [] (Rec1 * Binding)))) (C1 * (MetaCons "NRecSet" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ((:.:) * * [] (Rec1 * Binding))))) ((:+:) * (C1 * (MetaCons "NLiteralPath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath))) (C1 * (MetaCons "NEnvPath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NUnary" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NUnaryOp)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))) (C1 * (MetaCons "NBinary" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * NBinaryOp)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))))) ((:+:) * (C1 * (MetaCons "NSelect" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ((:.:) * * NonEmpty (Rec1 * NKeyName))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 * Maybe))))) (C1 * (MetaCons "NHasAttr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ((:.:) * * NonEmpty (Rec1 * NKeyName))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NAbs" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 * Params)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))) (C1 * (MetaCons "NLet" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) ((:.:) * * [] (Rec1 * Binding))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))) ((:+:) * (C1 * (MetaCons "NIf" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))) ((:+:) * (C1 * (MetaCons "NWith" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))) (C1 * (MetaCons "NAssert" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))))))))

type NExpr = Fix NExprF Source #

The monomorphic expression type is a fixed point of the polymorphic one.

data Binding r Source #

A single line of the bindings section of a let expression or of a set.

Constructors

NamedVar !(NAttrPath r) !r !SourcePos

An explicit naming, such as x = y or x.y = z.

Inherit !(Maybe r) ![NKeyName r] !SourcePos

Using a name already in scope, such as inherit x; which is shorthand for x = x; or inherit (x) y; which means y = x.y;. The unsafeGetAttrPos for every name so inherited is the position of the first name, whether that be the first argument to this constructor, or the first member of the list in the second argument.

Instances

Functor Binding Source # 

Methods

fmap :: (a -> b) -> Binding a -> Binding b #

(<$) :: a -> Binding b -> Binding a #

Foldable Binding Source # 

Methods

fold :: Monoid m => Binding m -> m #

foldMap :: Monoid m => (a -> m) -> Binding a -> m #

foldr :: (a -> b -> b) -> b -> Binding a -> b #

foldr' :: (a -> b -> b) -> b -> Binding a -> b #

foldl :: (b -> a -> b) -> b -> Binding a -> b #

foldl' :: (b -> a -> b) -> b -> Binding a -> b #

foldr1 :: (a -> a -> a) -> Binding a -> a #

foldl1 :: (a -> a -> a) -> Binding a -> a #

toList :: Binding a -> [a] #

null :: Binding a -> Bool #

length :: Binding a -> Int #

elem :: Eq a => a -> Binding a -> Bool #

maximum :: Ord a => Binding a -> a #

minimum :: Ord a => Binding a -> a #

sum :: Num a => Binding a -> a #

product :: Num a => Binding a -> a #

Traversable Binding Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Binding a -> f (Binding b) #

sequenceA :: Applicative f => Binding (f a) -> f (Binding a) #

mapM :: Monad m => (a -> m b) -> Binding a -> m (Binding b) #

sequence :: Monad m => Binding (m a) -> m (Binding a) #

Eq1 Binding Source # 

Methods

liftEq :: (a -> b -> Bool) -> Binding a -> Binding b -> Bool #

Show1 Binding Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Binding a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Binding a] -> ShowS #

NFData1 Binding Source # 

Methods

liftRnf :: (a -> ()) -> Binding a -> () #

Hashable1 Binding Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Binding a -> Int #

Eq r => Eq (Binding r) Source # 

Methods

(==) :: Binding r -> Binding r -> Bool #

(/=) :: Binding r -> Binding r -> Bool #

Data r => Data (Binding r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binding r -> c (Binding r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Binding r) #

toConstr :: Binding r -> Constr #

dataTypeOf :: Binding r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Binding r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Binding r)) #

gmapT :: (forall b. Data b => b -> b) -> Binding r -> Binding r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binding r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binding r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Binding r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binding r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binding r -> m (Binding r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding r -> m (Binding r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binding r -> m (Binding r) #

Ord r => Ord (Binding r) Source # 

Methods

compare :: Binding r -> Binding r -> Ordering #

(<) :: Binding r -> Binding r -> Bool #

(<=) :: Binding r -> Binding r -> Bool #

(>) :: Binding r -> Binding r -> Bool #

(>=) :: Binding r -> Binding r -> Bool #

max :: Binding r -> Binding r -> Binding r #

min :: Binding r -> Binding r -> Binding r #

Show r => Show (Binding r) Source # 

Methods

showsPrec :: Int -> Binding r -> ShowS #

show :: Binding r -> String #

showList :: [Binding r] -> ShowS #

Generic (Binding r) Source # 

Associated Types

type Rep (Binding r) :: * -> * #

Methods

from :: Binding r -> Rep (Binding r) x #

to :: Rep (Binding r) x -> Binding r #

Hashable r => Hashable (Binding r) Source # 

Methods

hashWithSalt :: Int -> Binding r -> Int #

hash :: Binding r -> Int #

ToJSON a => ToJSON (Binding a) Source # 
FromJSON a => FromJSON (Binding a) Source # 
Binary a => Binary (Binding a) Source # 

Methods

put :: Binding a -> Put #

get :: Get (Binding a) #

putList :: [Binding a] -> Put #

NFData r => NFData (Binding r) Source # 

Methods

rnf :: Binding r -> () #

Serialise r => Serialise (Binding r) Source # 
Generic1 * Binding Source # 

Associated Types

type Rep1 Binding (f :: Binding -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Binding f a #

to1 :: Rep1 Binding f a -> f a #

type Rep (Binding r) Source # 
type Rep1 * Binding Source # 

data Params r Source #

Params represents all the ways the formal parameters to a function can be represented.

Constructors

Param !VarName

For functions with a single named argument, such as x: x + 1.

ParamSet !(ParamSet r) !Bool !(Maybe VarName)

Explicit parameters (argument must be a set). Might specify a name to bind to the set in the function body. The bool indicates whether it is variadic or not.

Instances

Functor Params Source # 

Methods

fmap :: (a -> b) -> Params a -> Params b #

(<$) :: a -> Params b -> Params a #

Foldable Params Source # 

Methods

fold :: Monoid m => Params m -> m #

foldMap :: Monoid m => (a -> m) -> Params a -> m #

foldr :: (a -> b -> b) -> b -> Params a -> b #

foldr' :: (a -> b -> b) -> b -> Params a -> b #

foldl :: (b -> a -> b) -> b -> Params a -> b #

foldl' :: (b -> a -> b) -> b -> Params a -> b #

foldr1 :: (a -> a -> a) -> Params a -> a #

foldl1 :: (a -> a -> a) -> Params a -> a #

toList :: Params a -> [a] #

null :: Params a -> Bool #

length :: Params a -> Int #

elem :: Eq a => a -> Params a -> Bool #

maximum :: Ord a => Params a -> a #

minimum :: Ord a => Params a -> a #

sum :: Num a => Params a -> a #

product :: Num a => Params a -> a #

Traversable Params Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Params a -> f (Params b) #

sequenceA :: Applicative f => Params (f a) -> f (Params a) #

mapM :: Monad m => (a -> m b) -> Params a -> m (Params b) #

sequence :: Monad m => Params (m a) -> m (Params a) #

ToJSON1 Params Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Params a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Params a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Params a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Params a] -> Encoding #

FromJSON1 Params Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Params a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Params a] #

Eq1 Params Source # 

Methods

liftEq :: (a -> b -> Bool) -> Params a -> Params b -> Bool #

Ord1 Params Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Params a -> Params b -> Ordering #

Read1 Params Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Params a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Params a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Params a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Params a] #

Show1 Params Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Params a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Params a] -> ShowS #

NFData1 Params Source # 

Methods

liftRnf :: (a -> ()) -> Params a -> () #

Hashable1 Params Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Params a -> Int #

Eq r => Eq (Params r) Source # 

Methods

(==) :: Params r -> Params r -> Bool #

(/=) :: Params r -> Params r -> Bool #

Data r => Data (Params r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params r -> c (Params r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Params r) #

toConstr :: Params r -> Constr #

dataTypeOf :: Params r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Params r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Params r)) #

gmapT :: (forall b. Data b => b -> b) -> Params r -> Params r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Params r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Params r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params r -> m (Params r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params r -> m (Params r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params r -> m (Params r) #

Ord r => Ord (Params r) Source # 

Methods

compare :: Params r -> Params r -> Ordering #

(<) :: Params r -> Params r -> Bool #

(<=) :: Params r -> Params r -> Bool #

(>) :: Params r -> Params r -> Bool #

(>=) :: Params r -> Params r -> Bool #

max :: Params r -> Params r -> Params r #

min :: Params r -> Params r -> Params r #

Show r => Show (Params r) Source # 

Methods

showsPrec :: Int -> Params r -> ShowS #

show :: Params r -> String #

showList :: [Params r] -> ShowS #

IsString (Params r) Source # 

Methods

fromString :: String -> Params r #

Generic (Params r) Source # 

Associated Types

type Rep (Params r) :: * -> * #

Methods

from :: Params r -> Rep (Params r) x #

to :: Rep (Params r) x -> Params r #

Hashable r => Hashable (Params r) Source # 

Methods

hashWithSalt :: Int -> Params r -> Int #

hash :: Params r -> Int #

ToJSON a => ToJSON (Params a) Source # 
FromJSON a => FromJSON (Params a) Source # 
Binary a => Binary (Params a) Source # 

Methods

put :: Params a -> Put #

get :: Get (Params a) #

putList :: [Params a] -> Put #

NFData r => NFData (Params r) Source # 

Methods

rnf :: Params r -> () #

Serialise r => Serialise (Params r) Source # 
Generic1 * Params Source # 

Associated Types

type Rep1 Params (f :: Params -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Params f a #

to1 :: Rep1 Params f a -> f a #

type Rep (Params r) Source # 
type Rep1 * Params Source # 

type ParamSet r = [(VarName, Maybe r)] Source #

data Antiquoted (v :: *) (r :: *) Source #

Antiquoted represents an expression that is either antiquoted (surrounded by ${...}) or plain (not antiquoted).

Constructors

Plain !v 
EscapedNewline 
Antiquoted !r 

Instances

ToJSON2 Antiquoted Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Antiquoted a b -> Value #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Antiquoted a b] -> Value #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Antiquoted a b -> Encoding #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Antiquoted a b] -> Encoding #

FromJSON2 Antiquoted Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Antiquoted a b) #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Antiquoted a b] #

Eq2 Antiquoted Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Antiquoted a c -> Antiquoted b d -> Bool #

Ord2 Antiquoted Source # 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Antiquoted a c -> Antiquoted b d -> Ordering #

Read2 Antiquoted Source # 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Antiquoted a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Antiquoted a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Antiquoted a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Antiquoted a b] #

Show2 Antiquoted Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Antiquoted a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Antiquoted a b] -> ShowS #

Hashable2 Antiquoted Source # 

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Antiquoted a b -> Int #

Functor (Antiquoted v) Source # 

Methods

fmap :: (a -> b) -> Antiquoted v a -> Antiquoted v b #

(<$) :: a -> Antiquoted v b -> Antiquoted v a #

Foldable (Antiquoted v) Source # 

Methods

fold :: Monoid m => Antiquoted v m -> m #

foldMap :: Monoid m => (a -> m) -> Antiquoted v a -> m #

foldr :: (a -> b -> b) -> b -> Antiquoted v a -> b #

foldr' :: (a -> b -> b) -> b -> Antiquoted v a -> b #

foldl :: (b -> a -> b) -> b -> Antiquoted v a -> b #

foldl' :: (b -> a -> b) -> b -> Antiquoted v a -> b #

foldr1 :: (a -> a -> a) -> Antiquoted v a -> a #

foldl1 :: (a -> a -> a) -> Antiquoted v a -> a #

toList :: Antiquoted v a -> [a] #

null :: Antiquoted v a -> Bool #

length :: Antiquoted v a -> Int #

elem :: Eq a => a -> Antiquoted v a -> Bool #

maximum :: Ord a => Antiquoted v a -> a #

minimum :: Ord a => Antiquoted v a -> a #

sum :: Num a => Antiquoted v a -> a #

product :: Num a => Antiquoted v a -> a #

Traversable (Antiquoted v) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Antiquoted v a -> f (Antiquoted v b) #

sequenceA :: Applicative f => Antiquoted v (f a) -> f (Antiquoted v a) #

mapM :: Monad m => (a -> m b) -> Antiquoted v a -> m (Antiquoted v b) #

sequence :: Monad m => Antiquoted v (m a) -> m (Antiquoted v a) #

ToJSON v => ToJSON1 (Antiquoted v) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Antiquoted v a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Antiquoted v a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Antiquoted v a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Antiquoted v a] -> Encoding #

FromJSON v => FromJSON1 (Antiquoted v) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Antiquoted v a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Antiquoted v a] #

Eq v => Eq1 (Antiquoted v) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Antiquoted v a -> Antiquoted v b -> Bool #

Ord v => Ord1 (Antiquoted v) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Antiquoted v a -> Antiquoted v b -> Ordering #

Read v => Read1 (Antiquoted v) Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Antiquoted v a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Antiquoted v a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Antiquoted v a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Antiquoted v a] #

Show v => Show1 (Antiquoted v) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Antiquoted v a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Antiquoted v a] -> ShowS #

NFData v => NFData1 (Antiquoted v) Source # 

Methods

liftRnf :: (a -> ()) -> Antiquoted v a -> () #

Hashable v => Hashable1 (Antiquoted v) Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Antiquoted v a -> Int #

Generic1 * (Antiquoted v) Source # 

Associated Types

type Rep1 (Antiquoted v) (f :: Antiquoted v -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Antiquoted v) f a #

to1 :: Rep1 (Antiquoted v) f a -> f a #

(Eq r, Eq v) => Eq (Antiquoted v r) Source # 

Methods

(==) :: Antiquoted v r -> Antiquoted v r -> Bool #

(/=) :: Antiquoted v r -> Antiquoted v r -> Bool #

(Data r, Data v) => Data (Antiquoted v r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Antiquoted v r -> c (Antiquoted v r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Antiquoted v r) #

toConstr :: Antiquoted v r -> Constr #

dataTypeOf :: Antiquoted v r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Antiquoted v r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Antiquoted v r)) #

gmapT :: (forall b. Data b => b -> b) -> Antiquoted v r -> Antiquoted v r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Antiquoted v r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Antiquoted v r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Antiquoted v r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Antiquoted v r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Antiquoted v r -> m (Antiquoted v r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Antiquoted v r -> m (Antiquoted v r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Antiquoted v r -> m (Antiquoted v r) #

(Ord r, Ord v) => Ord (Antiquoted v r) Source # 

Methods

compare :: Antiquoted v r -> Antiquoted v r -> Ordering #

(<) :: Antiquoted v r -> Antiquoted v r -> Bool #

(<=) :: Antiquoted v r -> Antiquoted v r -> Bool #

(>) :: Antiquoted v r -> Antiquoted v r -> Bool #

(>=) :: Antiquoted v r -> Antiquoted v r -> Bool #

max :: Antiquoted v r -> Antiquoted v r -> Antiquoted v r #

min :: Antiquoted v r -> Antiquoted v r -> Antiquoted v r #

(Read r, Read v) => Read (Antiquoted v r) Source # 
(Show r, Show v) => Show (Antiquoted v r) Source # 

Methods

showsPrec :: Int -> Antiquoted v r -> ShowS #

show :: Antiquoted v r -> String #

showList :: [Antiquoted v r] -> ShowS #

Generic (Antiquoted v r) Source # 

Associated Types

type Rep (Antiquoted v r) :: * -> * #

Methods

from :: Antiquoted v r -> Rep (Antiquoted v r) x #

to :: Rep (Antiquoted v r) x -> Antiquoted v r #

(Hashable r, Hashable v) => Hashable (Antiquoted v r) Source # 

Methods

hashWithSalt :: Int -> Antiquoted v r -> Int #

hash :: Antiquoted v r -> Int #

(ToJSON v, ToJSON a) => ToJSON (Antiquoted v a) Source # 
(FromJSON v, FromJSON a) => FromJSON (Antiquoted v a) Source # 
(Binary v, Binary a) => Binary (Antiquoted v a) Source # 

Methods

put :: Antiquoted v a -> Put #

get :: Get (Antiquoted v a) #

putList :: [Antiquoted v a] -> Put #

(NFData r, NFData v) => NFData (Antiquoted v r) Source # 

Methods

rnf :: Antiquoted v r -> () #

(Serialise v, Serialise r) => Serialise (Antiquoted v r) Source # 
type Rep1 * (Antiquoted v) Source # 
type Rep1 * (Antiquoted v) = D1 * (MetaData "Antiquoted" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * (C1 * (MetaCons "Plain" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * v))) ((:+:) * (C1 * (MetaCons "EscapedNewline" PrefixI False) (U1 *)) (C1 * (MetaCons "Antiquoted" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1))))
type Rep (Antiquoted v r) Source # 
type Rep (Antiquoted v r) = D1 * (MetaData "Antiquoted" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * (C1 * (MetaCons "Plain" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * v))) ((:+:) * (C1 * (MetaCons "EscapedNewline" PrefixI False) (U1 *)) (C1 * (MetaCons "Antiquoted" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * r)))))

data NString r Source #

An NString is a list of things that are either a plain string or an antiquoted expression. After the antiquotes have been evaluated, the final string is constructed by concating all the parts.

Constructors

DoubleQuoted ![Antiquoted Text r]

Strings wrapped with double-quotes (") can contain literal newline characters, but the newlines are preserved and no indentation is stripped.

Indented !Int ![Antiquoted Text r]

Strings wrapped with two single quotes ('') can contain newlines, and their indentation will be stripped, but the amount stripped is remembered.

Instances

Functor NString Source # 

Methods

fmap :: (a -> b) -> NString a -> NString b #

(<$) :: a -> NString b -> NString a #

Foldable NString Source # 

Methods

fold :: Monoid m => NString m -> m #

foldMap :: Monoid m => (a -> m) -> NString a -> m #

foldr :: (a -> b -> b) -> b -> NString a -> b #

foldr' :: (a -> b -> b) -> b -> NString a -> b #

foldl :: (b -> a -> b) -> b -> NString a -> b #

foldl' :: (b -> a -> b) -> b -> NString a -> b #

foldr1 :: (a -> a -> a) -> NString a -> a #

foldl1 :: (a -> a -> a) -> NString a -> a #

toList :: NString a -> [a] #

null :: NString a -> Bool #

length :: NString a -> Int #

elem :: Eq a => a -> NString a -> Bool #

maximum :: Ord a => NString a -> a #

minimum :: Ord a => NString a -> a #

sum :: Num a => NString a -> a #

product :: Num a => NString a -> a #

Traversable NString Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NString a -> f (NString b) #

sequenceA :: Applicative f => NString (f a) -> f (NString a) #

mapM :: Monad m => (a -> m b) -> NString a -> m (NString b) #

sequence :: Monad m => NString (m a) -> m (NString a) #

ToJSON1 NString Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> NString a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [NString a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> NString a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [NString a] -> Encoding #

FromJSON1 NString Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (NString a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [NString a] #

Eq1 NString Source # 

Methods

liftEq :: (a -> b -> Bool) -> NString a -> NString b -> Bool #

Ord1 NString Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> NString a -> NString b -> Ordering #

Read1 NString Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NString a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NString a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NString a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NString a] #

Show1 NString Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NString a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NString a] -> ShowS #

NFData1 NString Source # 

Methods

liftRnf :: (a -> ()) -> NString a -> () #

Hashable1 NString Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NString a -> Int #

Eq r => Eq (NString r) Source # 

Methods

(==) :: NString r -> NString r -> Bool #

(/=) :: NString r -> NString r -> Bool #

Data r => Data (NString r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NString r -> c (NString r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (NString r) #

toConstr :: NString r -> Constr #

dataTypeOf :: NString r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NString r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NString r)) #

gmapT :: (forall b. Data b => b -> b) -> NString r -> NString r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NString r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NString r -> r #

gmapQ :: (forall d. Data d => d -> u) -> NString r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NString r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NString r -> m (NString r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NString r -> m (NString r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NString r -> m (NString r) #

Ord r => Ord (NString r) Source # 

Methods

compare :: NString r -> NString r -> Ordering #

(<) :: NString r -> NString r -> Bool #

(<=) :: NString r -> NString r -> Bool #

(>) :: NString r -> NString r -> Bool #

(>=) :: NString r -> NString r -> Bool #

max :: NString r -> NString r -> NString r #

min :: NString r -> NString r -> NString r #

Read r => Read (NString r) Source # 
Show r => Show (NString r) Source # 

Methods

showsPrec :: Int -> NString r -> ShowS #

show :: NString r -> String #

showList :: [NString r] -> ShowS #

IsString (NString r) Source #

For the the IsString instance, we use a plain doublequoted string.

Methods

fromString :: String -> NString r #

Generic (NString r) Source # 

Associated Types

type Rep (NString r) :: * -> * #

Methods

from :: NString r -> Rep (NString r) x #

to :: Rep (NString r) x -> NString r #

Hashable r => Hashable (NString r) Source # 

Methods

hashWithSalt :: Int -> NString r -> Int #

hash :: NString r -> Int #

ToJSON a => ToJSON (NString a) Source # 
FromJSON a => FromJSON (NString a) Source # 
Binary a => Binary (NString a) Source # 

Methods

put :: NString a -> Put #

get :: Get (NString a) #

putList :: [NString a] -> Put #

NFData r => NFData (NString r) Source # 

Methods

rnf :: NString r -> () #

Serialise r => Serialise (NString r) Source # 
Generic1 * NString Source # 

Associated Types

type Rep1 NString (f :: NString -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 NString f a #

to1 :: Rep1 NString f a -> f a #

type Rep (NString r) Source # 
type Rep1 * NString Source # 

data NKeyName r Source #

A KeyName is something that can appear on the left side of an equals sign. For example, a is a KeyName in { a = 3; }, let a = 3; in ..., {}.a or {} ? a.

Nix supports both static keynames (just an identifier) and dynamic identifiers. Dynamic identifiers can be either a string (e.g.: { "a" = 3; }) or an antiquotation (e.g.: let a = "example"; in { ${a} = 3; }.example).

Note: There are some places where a dynamic keyname is not allowed. In particular, those include:

  • The RHS of a binding inside let: let ${"a"} = 3; in ... produces a syntax error.
  • The attribute names of an inherit: inherit ${"a"}; is forbidden.

Note: In Nix, a simple string without antiquotes such as "foo" is allowed even if the context requires a static keyname, but the parser still considers it a DynamicKey for simplicity.

Constructors

DynamicKey !(Antiquoted (NString r) r) 
StaticKey !VarName 

Instances

Functor NKeyName Source # 

Methods

fmap :: (a -> b) -> NKeyName a -> NKeyName b #

(<$) :: a -> NKeyName b -> NKeyName a #

Foldable NKeyName Source # 

Methods

fold :: Monoid m => NKeyName m -> m #

foldMap :: Monoid m => (a -> m) -> NKeyName a -> m #

foldr :: (a -> b -> b) -> b -> NKeyName a -> b #

foldr' :: (a -> b -> b) -> b -> NKeyName a -> b #

foldl :: (b -> a -> b) -> b -> NKeyName a -> b #

foldl' :: (b -> a -> b) -> b -> NKeyName a -> b #

foldr1 :: (a -> a -> a) -> NKeyName a -> a #

foldl1 :: (a -> a -> a) -> NKeyName a -> a #

toList :: NKeyName a -> [a] #

null :: NKeyName a -> Bool #

length :: NKeyName a -> Int #

elem :: Eq a => a -> NKeyName a -> Bool #

maximum :: Ord a => NKeyName a -> a #

minimum :: Ord a => NKeyName a -> a #

sum :: Num a => NKeyName a -> a #

product :: Num a => NKeyName a -> a #

Traversable NKeyName Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NKeyName a -> f (NKeyName b) #

sequenceA :: Applicative f => NKeyName (f a) -> f (NKeyName a) #

mapM :: Monad m => (a -> m b) -> NKeyName a -> m (NKeyName b) #

sequence :: Monad m => NKeyName (m a) -> m (NKeyName a) #

Eq1 NKeyName Source # 

Methods

liftEq :: (a -> b -> Bool) -> NKeyName a -> NKeyName b -> Bool #

Show1 NKeyName Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NKeyName a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NKeyName a] -> ShowS #

NFData1 NKeyName Source # 

Methods

liftRnf :: (a -> ()) -> NKeyName a -> () #

Hashable1 NKeyName Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NKeyName a -> Int #

Generic1 * NKeyName Source # 

Associated Types

type Rep1 NKeyName (f :: NKeyName -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 NKeyName f a #

to1 :: Rep1 NKeyName f a -> f a #

Eq r => Eq (NKeyName r) Source # 

Methods

(==) :: NKeyName r -> NKeyName r -> Bool #

(/=) :: NKeyName r -> NKeyName r -> Bool #

Data r => Data (NKeyName r) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NKeyName r -> c (NKeyName r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (NKeyName r) #

toConstr :: NKeyName r -> Constr #

dataTypeOf :: NKeyName r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NKeyName r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NKeyName r)) #

gmapT :: (forall b. Data b => b -> b) -> NKeyName r -> NKeyName r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NKeyName r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NKeyName r -> r #

gmapQ :: (forall d. Data d => d -> u) -> NKeyName r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NKeyName r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NKeyName r -> m (NKeyName r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NKeyName r -> m (NKeyName r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NKeyName r -> m (NKeyName r) #

Ord r => Ord (NKeyName r) Source # 

Methods

compare :: NKeyName r -> NKeyName r -> Ordering #

(<) :: NKeyName r -> NKeyName r -> Bool #

(<=) :: NKeyName r -> NKeyName r -> Bool #

(>) :: NKeyName r -> NKeyName r -> Bool #

(>=) :: NKeyName r -> NKeyName r -> Bool #

max :: NKeyName r -> NKeyName r -> NKeyName r #

min :: NKeyName r -> NKeyName r -> NKeyName r #

Read r => Read (NKeyName r) Source # 
Show r => Show (NKeyName r) Source # 

Methods

showsPrec :: Int -> NKeyName r -> ShowS #

show :: NKeyName r -> String #

showList :: [NKeyName r] -> ShowS #

IsString (NKeyName r) Source #

Most key names are just static text, so this instance is convenient.

Methods

fromString :: String -> NKeyName r #

Generic (NKeyName r) Source # 

Associated Types

type Rep (NKeyName r) :: * -> * #

Methods

from :: NKeyName r -> Rep (NKeyName r) x #

to :: Rep (NKeyName r) x -> NKeyName r #

Hashable r => Hashable (NKeyName r) Source # 

Methods

hashWithSalt :: Int -> NKeyName r -> Int #

hash :: NKeyName r -> Int #

ToJSON a => ToJSON (NKeyName a) Source # 
FromJSON a => FromJSON (NKeyName a) Source # 
Binary a => Binary (NKeyName a) Source # 

Methods

put :: NKeyName a -> Put #

get :: Get (NKeyName a) #

putList :: [NKeyName a] -> Put #

NFData r => NFData (NKeyName r) Source # 

Methods

rnf :: NKeyName r -> () #

Serialise r => Serialise (NKeyName r) Source # 
type Rep1 * NKeyName Source # 
type Rep (NKeyName r) Source # 
type Rep (NKeyName r) = D1 * (MetaData "NKeyName" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * (C1 * (MetaCons "DynamicKey" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Antiquoted (NString r) r)))) (C1 * (MetaCons "StaticKey" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * VarName))))

type NAttrPath r = NonEmpty (NKeyName r) Source #

A selector (for example in a let or an attribute set) is made up of strung-together key names.

data NUnaryOp Source #

There are two unary operations: logical not and integer negation.

Constructors

NNeg 
NNot 

Instances

Eq NUnaryOp Source # 
Data NUnaryOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NUnaryOp -> c NUnaryOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NUnaryOp #

toConstr :: NUnaryOp -> Constr #

dataTypeOf :: NUnaryOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NUnaryOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NUnaryOp) #

gmapT :: (forall b. Data b => b -> b) -> NUnaryOp -> NUnaryOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NUnaryOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NUnaryOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> NUnaryOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NUnaryOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NUnaryOp -> m NUnaryOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NUnaryOp -> m NUnaryOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NUnaryOp -> m NUnaryOp #

Ord NUnaryOp Source # 
Read NUnaryOp Source # 
Show NUnaryOp Source # 
Generic NUnaryOp Source # 

Associated Types

type Rep NUnaryOp :: * -> * #

Methods

from :: NUnaryOp -> Rep NUnaryOp x #

to :: Rep NUnaryOp x -> NUnaryOp #

Hashable NUnaryOp Source # 

Methods

hashWithSalt :: Int -> NUnaryOp -> Int #

hash :: NUnaryOp -> Int #

ToJSON NUnaryOp Source # 
FromJSON NUnaryOp Source # 
Binary NUnaryOp Source # 

Methods

put :: NUnaryOp -> Put #

get :: Get NUnaryOp #

putList :: [NUnaryOp] -> Put #

NFData NUnaryOp Source # 

Methods

rnf :: NUnaryOp -> () #

Serialise NUnaryOp Source # 
type Rep NUnaryOp Source # 
type Rep NUnaryOp = D1 * (MetaData "NUnaryOp" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * (C1 * (MetaCons "NNeg" PrefixI False) (U1 *)) (C1 * (MetaCons "NNot" PrefixI False) (U1 *)))

data NBinaryOp Source #

Binary operators expressible in the nix language.

Constructors

NEq

Equality (==)

NNEq

Inequality (!=)

NLt

Less than (<)

NLte

Less than or equal (<=)

NGt

Greater than (>)

NGte

Greater than or equal (>=)

NAnd

Logical and (&&)

NOr

Logical or (||)

NImpl

Logical implication (->)

NUpdate

Joining two attribut sets (//)

NPlus

Addition (+)

NMinus

Subtraction (-)

NMult

Multiplication (*)

NDiv

Division (/)

NConcat

List concatenation (++)

NApp

Apply a function to an argument.

Instances

Eq NBinaryOp Source # 
Data NBinaryOp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NBinaryOp -> c NBinaryOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NBinaryOp #

toConstr :: NBinaryOp -> Constr #

dataTypeOf :: NBinaryOp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NBinaryOp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NBinaryOp) #

gmapT :: (forall b. Data b => b -> b) -> NBinaryOp -> NBinaryOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NBinaryOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NBinaryOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> NBinaryOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NBinaryOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NBinaryOp -> m NBinaryOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NBinaryOp -> m NBinaryOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NBinaryOp -> m NBinaryOp #

Ord NBinaryOp Source # 
Read NBinaryOp Source # 
Show NBinaryOp Source # 
Generic NBinaryOp Source # 

Associated Types

type Rep NBinaryOp :: * -> * #

Hashable NBinaryOp Source # 
ToJSON NBinaryOp Source # 
FromJSON NBinaryOp Source # 
Binary NBinaryOp Source # 
NFData NBinaryOp Source # 

Methods

rnf :: NBinaryOp -> () #

Serialise NBinaryOp Source # 
type Rep NBinaryOp Source # 
type Rep NBinaryOp = D1 * (MetaData "NBinaryOp" "Nix.Expr.Types" "hnix-0.5.1-1AEILKRXuiNL8eYeTMwPu7" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NEq" PrefixI False) (U1 *)) (C1 * (MetaCons "NNEq" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NLt" PrefixI False) (U1 *)) (C1 * (MetaCons "NLte" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NGt" PrefixI False) (U1 *)) (C1 * (MetaCons "NGte" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NAnd" PrefixI False) (U1 *)) (C1 * (MetaCons "NOr" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NImpl" PrefixI False) (U1 *)) (C1 * (MetaCons "NUpdate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NPlus" PrefixI False) (U1 *)) (C1 * (MetaCons "NMinus" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NMult" PrefixI False) (U1 *)) (C1 * (MetaCons "NDiv" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NConcat" PrefixI False) (U1 *)) (C1 * (MetaCons "NApp" PrefixI False) (U1 *))))))

paramName :: Params r -> Maybe VarName Source #

Get the name out of the parameter (there might be none).

defaultOptions ''NExprF)

defaultOptions ''Binding)

_NAssert :: Applicative f => ((r, r) -> f (r, r)) -> NExprF r -> f (NExprF r) Source #

_NWith :: Applicative f => ((r, r) -> f (r, r)) -> NExprF r -> f (NExprF r) Source #

_NIf :: Applicative f => ((r, r, r) -> f (r, r, r)) -> NExprF r -> f (NExprF r) Source #

_NLet :: Applicative f => (([Binding r], r) -> f ([Binding r], r)) -> NExprF r -> f (NExprF r) Source #

_NAbs :: Applicative f => ((Params r, r) -> f (Params r, r)) -> NExprF r -> f (NExprF r) Source #

_NHasAttr :: Applicative f => ((r, NAttrPath r) -> f (r, NAttrPath r)) -> NExprF r -> f (NExprF r) Source #

_NSelect :: Applicative f => ((r, NAttrPath r, Maybe r) -> f (r, NAttrPath r, Maybe r)) -> NExprF r -> f (NExprF r) Source #

_NBinary :: Applicative f => ((NBinaryOp, r, r) -> f (NBinaryOp, r, r)) -> NExprF r -> f (NExprF r) Source #

_NUnary :: Applicative f => ((NUnaryOp, r) -> f (NUnaryOp, r)) -> NExprF r -> f (NExprF r) Source #

_NRecSet :: Applicative f => ([Binding r] -> f [Binding r]) -> NExprF r -> f (NExprF r) Source #

_NSet :: Applicative f => ([Binding r] -> f [Binding r]) -> NExprF r -> f (NExprF r) Source #

_NList :: Applicative f => ([r] -> f [r]) -> NExprF r -> f (NExprF r) Source #

_NSym :: Applicative f => (VarName -> f VarName) -> NExprF r -> f (NExprF r) Source #

_NStr :: Applicative f => (NString r -> f (NString r)) -> NExprF r -> f (NExprF r) Source #

_NConstant :: Applicative f => (NAtom -> f NAtom) -> NExprF r -> f (NExprF r) Source #

_Inherit :: Applicative f => ((Maybe r, [NKeyName r], SourcePos) -> f (Maybe r, [NKeyName r], SourcePos)) -> Binding r -> f (Binding r) Source #

_NamedVar :: Applicative f => ((NAttrPath r, r, SourcePos) -> f (NAttrPath r, r, SourcePos)) -> Binding r -> f (Binding r) Source #

_ParamSet :: Applicative f => ((ParamSet r1, Bool, Maybe VarName) -> f (ParamSet r2, Bool, Maybe VarName)) -> Params r1 -> f (Params r2) Source #

_Param :: Applicative f => (VarName -> f VarName) -> Params r -> f (Params r) Source #

_Antiquoted :: Applicative f => (t -> f r) -> Antiquoted v t -> f (Antiquoted v r) Source #

_EscapedNewline :: Applicative f => (() -> f ()) -> Antiquoted v r -> f (Antiquoted v r) Source #

_Plain :: Applicative f => (t -> f v) -> Antiquoted t r -> f (Antiquoted v r) Source #

_Indented :: Applicative f => ((Int, [Antiquoted Text r]) -> f (Int, [Antiquoted Text r])) -> NString r -> f (NString r) Source #

_DynamicKey :: Applicative f => (Antiquoted (NString r1) r1 -> f (Antiquoted (NString r2) r2)) -> NKeyName r1 -> f (NKeyName r2) Source #

_NNot :: Applicative f => (() -> f ()) -> NUnaryOp -> f NUnaryOp Source #

_NNeg :: Applicative f => (() -> f ()) -> NUnaryOp -> f NUnaryOp Source #

_NApp :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NConcat :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NDiv :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NMult :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NMinus :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NPlus :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NUpdate :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NImpl :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NOr :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NAnd :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NGte :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NGt :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NLte :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NLt :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NNEq :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

_NEq :: Applicative f => (() -> f ()) -> NBinaryOp -> f NBinaryOp Source #

''Fix)

class NExprAnn ann g | g -> ann where Source #

Minimal complete definition

fromNExpr, toNExpr

Methods

fromNExpr :: g r -> (NExprF r, ann) Source #

toNExpr :: (NExprF r, ann) -> g r Source #

ekey :: NExprAnn ann g => NonEmpty Text -> SourcePos -> Lens' (Fix g) (Maybe (Fix g)) Source #

Orphan instances

Hashable Pos Source # 

Methods

hashWithSalt :: Int -> Pos -> Int #

hash :: Pos -> Int #

Hashable SourcePos Source # 
ToJSON Pos Source # 
ToJSON SourcePos Source # 
ToJSON NAtom Source # 
FromJSON Pos Source # 
FromJSON SourcePos Source # 
FromJSON NAtom Source # 
Binary Pos Source # 

Methods

put :: Pos -> Put #

get :: Get Pos #

putList :: [Pos] -> Put #

Binary SourcePos Source # 
Binary NAtom Source # 

Methods

put :: NAtom -> Put #

get :: Get NAtom #

putList :: [NAtom] -> Put #

Hashable1 NonEmpty Source # 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int #

Serialise Pos Source # 
Serialise SourcePos Source #