hnix-0.13.1: Haskell implementation of the Nix language
Safe HaskellNone
LanguageHaskell2010

Nix.Utils

Synopsis

Documentation

trace :: String -> a -> a Source #

traceM :: Monad m => String -> m () Source #

class Has a b where Source #

Methods

hasLens :: Lens' a b Source #

Instances

Instances details
Has a a Source # 
Instance details

Defined in Nix.Utils

Methods

hasLens :: Lens' a a Source #

Has (a, b) b Source # 
Instance details

Defined in Nix.Utils

Methods

hasLens :: Lens' (a, b) b Source #

Has (a, b) a Source # 
Instance details

Defined in Nix.Utils

Methods

hasLens :: Lens' (a, b) a Source #

Has (Context m t) Options Source # 
Instance details

Defined in Nix.Context

Has (Context m t) Frames Source # 
Instance details

Defined in Nix.Context

Has (Context m t) SrcSpan Source # 
Instance details

Defined in Nix.Context

Has (Context m t) (Scopes m t) Source # 
Instance details

Defined in Nix.Context

Methods

hasLens :: Lens' (Context m t) (Scopes m t) Source #

type Transform f a = (Fix f -> a) -> Fix f -> a Source #

Transform here means a modification of a catamorphism.

type AlgM f m a = f a -> m a Source #

type Alg f a = f a -> a Source #

F-algebra defines how to reduce the fixed-point of a functor to a value.

_unFix :: Functor f1 => (f2 (Fix f2) -> f1 (f3 (Fix f3))) -> Fix f2 -> f1 (Fix f3) Source #

loeb :: Functor f => f (f a -> a) -> f a Source #

loebM :: (MonadFix m, Traversable t) => t (t a -> m a) -> m (t a) Source #

para :: Functor f => (f (Fix f, a) -> a) -> Fix f -> a Source #

paraM :: (Traversable f, Monad m) => (f (Fix f, a) -> m a) -> Fix f -> m a Source #

cataP :: Functor f => (Fix f -> f a -> a) -> Fix f -> a Source #

cataPM :: (Traversable f, Monad m) => (Fix f -> f a -> m a) -> Fix f -> m a Source #

lifted :: (MonadTransControl u, Monad (u m), Monad m) => ((a -> m (StT u b)) -> m (StT u b)) -> (a -> u m b) -> u m b Source #

freeToFix :: Functor f => (a -> Fix f) -> Free f a -> Fix f Source #

Replace: Pure a -> a Free -> Fix

fixToFree :: Functor f => Fix f -> Free f a Source #

adi :: Functor f => (f a -> a) -> ((Fix f -> a) -> Fix f -> a) -> Fix f -> a Source #

adi is Abstracting Definitional Interpreters:

https://arxiv.org/abs/1707.04755

Essentially, it does for evaluation what recursion schemes do for representation: allows threading layers through existing structure, only in this case through behavior.

adiM :: (Traversable t, Monad m) => (t a -> m a) -> ((Fix t -> m a) -> Fix t -> m a) -> Fix t -> m a Source #

uriAwareSplit :: Text -> [(Text, NixPathEntryType)] Source #

NIX_PATH is colon-separated, but can also contain URLs, which have a colon (i.e. https://...)

alterF :: (Eq k, Hashable k, Functor f) => (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) Source #

list :: Foldable t => b -> (t a -> b) -> t a -> b Source #

Analog for bool or maybe, for list-like cons structures.

free :: (a -> b) -> (f (Free f a) -> b) -> Free f a -> b Source #

Lambda analog of maybe or either for Free monad.

whenTrue :: Monoid a => a -> Bool -> a Source #

whenFalse :: Monoid a => a -> Bool -> a Source #

whenFree :: Monoid b => (f (Free f a) -> b) -> Free f a -> b Source #

whenPure :: Monoid b => (a -> b) -> Free f a -> b Source #

both :: (a -> b) -> (a, a) -> (b, b) Source #

Apply a single function to both components of a pair.

both succ (1,2) == (2,3)

Taken From package extra

dup :: a -> (a, a) Source #

Duplicates object into a tuple.

mapPair :: (a -> c, b -> d) -> (a, b) -> (c, d) Source #

From utility-ht for tuple laziness.

stub :: (Applicative f, Monoid a) => f a Source #

pure mempty: Short-curcuit, stub.

(<>~) :: Monoid a => Setter s t a a -> a -> s -> t infixr 4 #

Monoidally append a value to all referenced fields.

(||~) :: Setter s t Bool Bool -> Bool -> s -> t infixr 4 #

(&&~) :: Setter s t Bool Bool -> Bool -> s -> t infixr 4 #

(//~) :: Fractional a => Setter s t a a -> a -> s -> t infixr 4 #

(*~) :: Num a => Setter s t a a -> a -> s -> t infixr 4 #

(-~) :: Num a => Setter s t a a -> a -> s -> t infixr 4 #

(+~) :: Num a => Setter s t a a -> a -> s -> t infixr 4 #

set :: Setter s t a b -> b -> s -> t #

Set all referenced fields to the given value.

(.~) :: Setter s t a b -> b -> s -> t infixr 4 #

Set all referenced fields to the given value.

(%~) :: Setter s t a b -> (a -> b) -> s -> t infixr 4 #

Modify all referenced fields.

over :: Setter s t a b -> (a -> b) -> s -> t #

Demote a setter to a semantic editor combinator.

over :: Prism s t a b -> Reviwer s t a b
over :: Grid s t a b -> Grate s t a b
over :: Adapter s t a b -> Grate s t a b

Covert an AdapterLike optic into a GrateLike optic.

reset :: Resetter s t a b -> b -> s -> t #

Set all referenced fields to the given value.

under :: Resetter s t a b -> (a -> b) -> s -> t #

Demote a resetter to a semantic editor combinator.

under :: Prism s t a b -> Traversal s t a b
under :: Grid s t a b -> Traversal s t a b
under :: Adapter s t a b -> Lens s t a b

Covert an AdapterLike optic into a LensLike optic.

Note: this function is unrelated to the lens package's under function.

degrating :: Grate s t a b -> ((s -> a) -> b) -> t #

Demote a grate to its normal, higher-order function, form.

degrating . grate = id
grate . degrating = id

zipWithOf :: Grate s t a b -> (a -> a -> b) -> s -> s -> t #

Returns a binary instance of a grate.

zipWithOf l f x y = degrating l (k -> f (k x) (k y))

matching :: Traversal s t a b -> s -> Either t a #

Returns Right of the first referenced value. Returns Left the original value when there are no referenced values. In case there are no referenced values, the result might have a fresh type parameter, thereby proving the original value had no referenced values.

(^?) :: s -> Fold s t a b -> Maybe a infixl 8 #

Returns Just the first referenced value. Returns Nothing if there are no referenced values.

(^..) :: s -> Fold s t a b -> [a] infixl 8 #

Returns a list of all of the referenced values in order.

nullOf :: Fold s t a b -> s -> Bool #

Returns true if the number of references in the input is zero.

lengthOf :: Num r => Fold s t a b -> s -> r #

Counts the number of references in a traversal or fold for the input.

productOf :: Num a => Fold s t a b -> s -> a #

Returns the product of all the referenced values.

sumOf :: Num a => Fold s t a b -> s -> a #

Returns the sum of all the referenced values.

lastOf :: Fold s t a b -> s -> Maybe a #

Returns Just the last referenced value. Returns Nothing if there are no referenced values.

firstOf :: Fold s t a b -> s -> Maybe a #

Returns Just the first referenced value. Returns Nothing if there are no referenced values. See ^? for an infix version of firstOf

anyOf :: Fold s t a b -> (a -> Bool) -> s -> Bool #

Returns true if any of the referenced values satisfy the given predicate.

allOf :: Fold s t a b -> (a -> Bool) -> s -> Bool #

Returns true if all of the referenced values satisfy the given predicate.

toListOf :: Fold s t a b -> s -> [a] #

Returns a list of all of the referenced values in order.

folding :: Foldable f => (s -> f a) -> Fold s t a b #

folding promotes a "toList" function to a read-only traversal called a fold.

To demote a traversal or fold to a "toList" function use the section (^..l) or toListOf l.

to :: (s -> a) -> Getter s t a b #

to promotes a projection function to a read-only lens called a getter. To demote a lens to a projection function, use the section (^.l) or view l.

>>> (3 :+ 4, "example")^._1.to(abs)
5.0 :+ 0.0

type Grid s t a b = forall (f :: Type -> Type) (g :: Type -> Type). (Applicative f, Functor g) => AdapterLike f g s t a b #

type Grid' s a = forall (f :: Type -> Type) (g :: Type -> Type). (Applicative f, Functor g) => AdapterLike' f g s a #

type Fold s t a b = forall (f :: Type -> Type). (Phantom f, Applicative f) => LensLike f s t a b #

type Fold' s a = forall (f :: Type -> Type). (Phantom f, Applicative f) => LensLike' f s a #

type Getter s t a b = forall (f :: Type -> Type). Phantom f => LensLike f s t a b #

type Getter' s a = forall (f :: Type -> Type). Phantom f => LensLike' f s a #

type Reviewer s t a b = forall (f :: Type -> Type). Phantom f => GrateLike f s t a b #

type Reviewer' s a = forall (f :: Type -> Type). Phantom f => GrateLike' f s a #

type Adapter s t a b = forall (f :: Type -> Type) (g :: Type -> Type). (Functor f, Functor g) => AdapterLike f g s t a b #

type Adapter' s a = forall (f :: Type -> Type) (g :: Type -> Type). (Functor f, Functor g) => AdapterLike' f g s a #

type Prism s t a b = forall (f :: Type -> Type) (g :: Type -> Type). (Applicative f, Traversable g) => AdapterLike f g s t a b #

type Prism' s a = forall (f :: Type -> Type) (g :: Type -> Type). (Applicative f, Traversable g) => AdapterLike' f g s a #

type Lens s t a b = forall (f :: Type -> Type). Functor f => LensLike f s t a b #

type Lens' s a = forall (f :: Type -> Type). Functor f => LensLike' f s a #

type Traversal s t a b = forall (f :: Type -> Type). Applicative f => LensLike f s t a b #

type Traversal' s a = forall (f :: Type -> Type). Applicative f => LensLike' f s a #

type Setter s t a b = forall (f :: Type -> Type). Identical f => LensLike f s t a b #

type Setter' s a = forall (f :: Type -> Type). Identical f => LensLike' f s a #

type Grate s t a b = forall (g :: Type -> Type). Functor g => GrateLike g s t a b #

type Grate' s a = forall (g :: Type -> Type). Functor g => GrateLike' g s a #

data Constant a (b :: k) #

Constant functor.

Instances

Instances details
Bifunctor (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bimap :: (a -> b) -> (c -> d) -> Constant a c -> Constant b d #

first :: (a -> b) -> Constant a c -> Constant b c #

second :: (b -> c) -> Constant a b -> Constant a c #

Bitraversable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) #

Bifoldable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bifold :: Monoid m => Constant m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Constant a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Constant a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Constant a b -> c #

Eq2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

Ord2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

Read2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

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

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

Show2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Functor (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

fmap :: (a0 -> b) -> Constant a a0 -> Constant a b #

(<$) :: a0 -> Constant a b -> Constant a a0 #

Monoid a => Applicative (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

pure :: a0 -> Constant a a0 #

(<*>) :: Constant a (a0 -> b) -> Constant a a0 -> Constant a b #

liftA2 :: (a0 -> b -> c) -> Constant a a0 -> Constant a b -> Constant a c #

(*>) :: Constant a a0 -> Constant a b -> Constant a b #

(<*) :: Constant a a0 -> Constant a b -> Constant a a0 #

Foldable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

fold :: Monoid m => Constant a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

toList :: Constant a a0 -> [a0] #

null :: Constant a a0 -> Bool #

length :: Constant a a0 -> Int #

elem :: Eq a0 => a0 -> Constant a a0 -> Bool #

maximum :: Ord a0 => Constant a a0 -> a0 #

minimum :: Ord a0 => Constant a a0 -> a0 #

sum :: Num a0 => Constant a a0 -> a0 #

product :: Num a0 => Constant a a0 -> a0 #

Traversable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

sequenceA :: Applicative f => Constant a (f a0) -> f (Constant a a0) #

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

sequence :: Monad m => Constant a (m a0) -> m (Constant a a0) #

Contravariant (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Eq a => Eq1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq :: (a0 -> b -> Bool) -> Constant a a0 -> Constant a b -> Bool #

Ord a => Ord1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare :: (a0 -> b -> Ordering) -> Constant a a0 -> Constant a b -> Ordering #

Read a => Read1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Constant a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Constant a a0] #

Show a => Show1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Phantom (Constant a :: Type -> Type) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Eq a => Eq (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

(==) :: Constant a b -> Constant a b -> Bool #

(/=) :: Constant a b -> Constant a b -> Bool #

Ord a => Ord (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

compare :: Constant a b -> Constant a b -> Ordering #

(<) :: Constant a b -> Constant a b -> Bool #

(<=) :: Constant a b -> Constant a b -> Bool #

(>) :: Constant a b -> Constant a b -> Bool #

(>=) :: Constant a b -> Constant a b -> Bool #

max :: Constant a b -> Constant a b -> Constant a b #

min :: Constant a b -> Constant a b -> Constant a b #

Read a => Read (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Show a => Show (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

showsPrec :: Int -> Constant a b -> ShowS #

show :: Constant a b -> String #

showList :: [Constant a b] -> ShowS #

Semigroup a => Semigroup (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

(<>) :: Constant a b -> Constant a b -> Constant a b #

sconcat :: NonEmpty (Constant a b) -> Constant a b #

stimes :: Integral b0 => b0 -> Constant a b -> Constant a b #

Monoid a => Monoid (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

mappend :: Constant a b -> Constant a b -> Constant a b #

mconcat :: [Constant a b] -> Constant a b #

class (Traversable f, Applicative f) => Identical (f :: Type -> Type) #

Minimal complete definition

extract

Instances

Instances details
Identical Identity 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Identity a -> a

Identical f => Identical (Backwards f) 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Backwards f a -> a

(Identical f, Identical g) => Identical (Compose f g) 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Compose f g a -> a

class Functor f => Phantom (f :: Type -> Type) #

Minimal complete definition

coerce

Instances

Instances details
Phantom (Const a :: Type -> Type) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Const a a0 -> Const a b

Phantom (Constant a :: Type -> Type) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Phantom f => Phantom (Backwards f) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Backwards f a -> Backwards f b

(Phantom f, Functor g) => Phantom (Compose f g) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Compose f g a -> Compose f g b

type GrateLike' (g :: Type -> Type) s a = (g a -> a) -> g s -> s #

type GrateLike (g :: Type -> Type) s t a b = (g a -> b) -> g s -> t #

type LensLike' (f :: Type -> Type) s a = (a -> f a) -> s -> f s #

type LensLike (f :: Type -> Type) s t a b = (a -> f b) -> s -> f t #

type AdapterLike' (f :: Type -> Type) (g :: Type -> Type) s a = (g a -> f a) -> g s -> f s #

type AdapterLike (f :: Type -> Type) (g :: Type -> Type) s t a b = (g a -> f b) -> g s -> f t #

type FoldLike' r s a = LensLike' (Constant r :: Type -> Type) s a #

type FoldLike r s t a b = LensLike (Constant r :: Type -> Type) s t a b #

view :: FoldLike a s t a b -> s -> a #

view :: Getter s t a b -> s -> a

Demote a lens or getter to a projection function.

view :: Monoid a => Fold s t a b -> s -> a

Returns the monoidal summary of a traversal or a fold.

views :: FoldLike r s t a b -> (a -> r) -> s -> r #

views :: Monoid r => Fold s t a b -> (a -> r) -> s -> r

Given a fold or traversal, return the foldMap of all the values using the given function.

views :: Getter s t a b -> (a -> r) -> s -> r

views is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function.

views l f s = f (view l s)

(^.) :: s -> FoldLike a s t a b -> a infixl 8 #

(^.) :: s -> Getter s t a b -> a

Access the value referenced by a getter or lens.

(^.) :: Monoid a => s -> Fold s t a b -> a

Access the monoidal summary referenced by a traversal or a fold.

review :: GrateLike (Constant () :: Type -> Type) s t a b -> b -> t #

review :: Grate s t a b -> b -> t
review :: Reviewer s t a b -> b -> t