hnix-0.17.0: Haskell implementation of the Nix language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Nix.Utils

Description

This is a module of custom Prelude code. It is for import for projects other then HNix. For HNix - this module gets reexported by Prelude, so for HNix please fix-up pass-through there.

Synopsis

Documentation

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

pure mempty: Short-curcuit, stub.

pass :: Applicative f => f () Source #

Alias for stub, since Relude has more specialized pure ().

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

Duplicates object into a tuple.

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

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

Gives tuple laziness.

Takem from utility-ht.

iterateN Source #

Arguments

:: forall a. Int

Recursively apply Int times

-> (a -> a)

the function

-> a

starting from argument

-> a 

nestM Source #

Arguments

:: Monad m 
=> Int

Recursively apply Int times

-> (a -> m a)

function (Kleisli arrow).

-> a

to value

-> m a

& join layers of m

applyAll :: Foldable t => t (a -> a) -> a -> a Source #

In foldr order apply functions.

traverse2 Source #

Arguments

:: (Applicative m, Applicative n, Traversable t) 
=> (a -> m (n b))

Run function that runs 2 Applicative actions

-> t a

on every element in Traversable

-> m (n (t b))

collect the results.

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 #

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

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

whenJust :: Monoid b => (a -> b) -> Maybe a -> b Source #

isPresent :: Foldable t => t a -> Bool Source #

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

maybe-like eliminator, for foldable empty/inhabited structures.

whenText :: a -> (Text -> a) -> Text -> a Source #

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

Lambda analog of maybe or either for Free monad.

newtype Path Source #

Explicit type boundary between FilePath & String.

Constructors

Path FilePath 

Instances

Instances details
FromJSON Path Source # 
Instance details

Defined in Nix.Utils

ToJSON Path Source # 
Instance details

Defined in Nix.Utils

Data Path Source # 
Instance details

Defined in Nix.Utils

Methods

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

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

toConstr :: Path -> Constr #

dataTypeOf :: Path -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Path Source # 
Instance details

Defined in Nix.Utils

Methods

fromString :: String -> Path #

Monoid Path Source # 
Instance details

Defined in Nix.Utils

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

Semigroup Path Source # 
Instance details

Defined in Nix.Utils

Methods

(<>) :: Path -> Path -> Path #

sconcat :: NonEmpty Path -> Path #

stimes :: Integral b => b -> Path -> Path #

Generic Path Source # 
Instance details

Defined in Nix.Utils

Associated Types

type Rep Path :: Type -> Type #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

Read Path Source # 
Instance details

Defined in Nix.Utils

Show Path Source # 
Instance details

Defined in Nix.Utils

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Binary Path Source # 
Instance details

Defined in Nix.Utils

Methods

put :: Path -> Put #

get :: Get Path #

putList :: [Path] -> Put #

NFData Path Source # 
Instance details

Defined in Nix.Utils

Methods

rnf :: Path -> () #

Eq Path Source # 
Instance details

Defined in Nix.Utils

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 
Instance details

Defined in Nix.Utils

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Hashable Path Source # 
Instance details

Defined in Nix.Utils

Methods

hashWithSalt :: Int -> Path -> Int #

hash :: Path -> Int #

ToText Path Source # 
Instance details

Defined in Nix.Utils

Methods

toText :: Path -> Text #

Serialise Path Source # 
Instance details

Defined in Nix.Utils

(Convertible e t f m, MonadValue (NValue t f m) m) => FromValue Path m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

fromValue :: NValue' t f m (NValue t f m) -> m Path Source #

fromValueMay :: NValue' t f m (NValue t f m) -> m (Maybe Path) Source #

Convertible e t f m => ToValue Path m (NValue' t f m (NValue t f m)) Source # 
Instance details

Defined in Nix.Convert

Methods

toValue :: Path -> m (NValue' t f m (NValue t f m)) Source #

Monad m => MonadState (HashMap Path NExprLoc, HashMap Text Text) (StandardTF r m) Source # 
Instance details

Defined in Nix.Standard

type Rep Path Source # 
Instance details

Defined in Nix.Utils

type Rep Path = D1 ('MetaData "Path" "Nix.Utils" "hnix-0.17.0-8saIMbclRB9HPH4JCEpCXn" 'True) (C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

isAbsolute :: Path -> Bool Source #

This set of Path funcs is to control system filepath types & typesafety and to easily migrate from FilePath to anything suitable (like path or so).

Paths isAbsolute.

(</>) :: Path -> Path -> Path infixr 5 Source #

Paths 'FilePath.(/)'.

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

F-algebra defines how to reduce the fixed-point of a functor to a value. > type Alg f a = f a -> a

type Transform f a = TransformF (Fix f) a Source #

Do according transformation.

It is a transformation of a recursion scheme. See TransformF.

type TransformF f a = (f -> a) -> f -> a Source #

Do according transformation.

It is a transformation between functors.

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

adi :: Functor f => Transform f a -> Alg f a -> Fix f -> a Source #

adi is Abstracting Definitional Interpreters:

https://arxiv.org/abs/1707.04755

All ADI does is interleaves every layer of evaluation by inserting intermitten layers between them, in that way the evaluation can be extended/embelished in any way wanted. Look at its use to see great examples.

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

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 (Context m t) SrcSpan Source # 
Instance details

Defined in Nix.Context

Has (Context m t) Frames Source # 
Instance details

Defined in Nix.Context

Has (Context m t) Options Source # 
Instance details

Defined in Nix.Context

Has (a, b) a Source # 
Instance details

Defined in Nix.Utils

Methods

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

Has (a, b) b Source # 
Instance details

Defined in Nix.Utils

Methods

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

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

Defined in Nix.Context

Methods

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

askLocal :: (MonadReader t m, Has t a) => m a Source #

Retrive monad state by Lens'.

type KeyMap = HashMap Text Source #

Hashmap Text -- type synonym

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

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

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.

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

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

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.