hnix-0.6.1: Haskell implementation of the Nix language

Safe HaskellNone
LanguageHaskell2010

Nix.String

Synopsis

Documentation

data NixString Source #

Instances
Eq NixString Source # 
Instance details

Defined in Nix.String

Ord NixString Source # 
Instance details

Defined in Nix.String

Show NixString Source # 
Instance details

Defined in Nix.String

Generic NixString Source # 
Instance details

Defined in Nix.String

Associated Types

type Rep NixString :: Type -> Type #

Hashable NixString Source # 
Instance details

Defined in Nix.String

FromValue NixString m (Symbolic m) Source # 
Instance details

Defined in Nix.Lint

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

Defined in Nix.Convert

Methods

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

(Convertible e t f m, MonadValue (NValue t f m) m, MonadEffects t f m) => FromValue NixString 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 NixString Source #

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

type Rep NixString Source # 
Instance details

Defined in Nix.String

type Rep NixString = D1 (MetaData "NixString" "Nix.String" "hnix-0.6.1-1597pjcbiB2Cib3HzwJZxT" False) (C1 (MetaCons "NixString" PrefixI True) (S1 (MetaSel (Just "nsContents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "nsContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashSet StringContext))))

principledMakeNixString :: Text -> HashSet StringContext -> NixString Source #

Create a NixString from a Text and context

principledMempty :: NixString Source #

Combine two NixStrings using mappend

data StringContext Source #

Constructors

StringContext 
Instances
Eq StringContext Source # 
Instance details

Defined in Nix.String

Ord StringContext Source # 
Instance details

Defined in Nix.String

Show StringContext Source # 
Instance details

Defined in Nix.String

Generic StringContext Source # 
Instance details

Defined in Nix.String

Associated Types

type Rep StringContext :: Type -> Type #

Hashable StringContext Source # 
Instance details

Defined in Nix.String

Monad m => MonadWriter (HashSet StringContext) (WithStringContextT m) Source # 
Instance details

Defined in Nix.String

type Rep StringContext Source # 
Instance details

Defined in Nix.String

type Rep StringContext = D1 (MetaData "StringContext" "Nix.String" "hnix-0.6.1-1597pjcbiB2Cib3HzwJZxT" False) (C1 (MetaCons "StringContext" PrefixI True) (S1 (MetaSel (Just "scPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "scFlavor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ContextFlavor)))

data ContextFlavor Source #

A ContextFlavor describes the sum of possible derivations for string contexts

Instances
Eq ContextFlavor Source # 
Instance details

Defined in Nix.String

Ord ContextFlavor Source # 
Instance details

Defined in Nix.String

Show ContextFlavor Source # 
Instance details

Defined in Nix.String

Generic ContextFlavor Source # 
Instance details

Defined in Nix.String

Associated Types

type Rep ContextFlavor :: Type -> Type #

Hashable ContextFlavor Source # 
Instance details

Defined in Nix.String

type Rep ContextFlavor Source # 
Instance details

Defined in Nix.String

type Rep ContextFlavor = D1 (MetaData "ContextFlavor" "Nix.String" "hnix-0.6.1-1597pjcbiB2Cib3HzwJZxT" False) (C1 (MetaCons "DirectPath" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AllOutputs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DerivationOutput" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

newtype NixLikeContext Source #

data NixLikeContextValue Source #

Constructors

NixLikeContextValue 
Instances
Eq NixLikeContextValue Source # 
Instance details

Defined in Nix.String

Ord NixLikeContextValue Source # 
Instance details

Defined in Nix.String

Show NixLikeContextValue Source # 
Instance details

Defined in Nix.String

Generic NixLikeContextValue Source # 
Instance details

Defined in Nix.String

Associated Types

type Rep NixLikeContextValue :: Type -> Type #

Semigroup NixLikeContextValue Source # 
Instance details

Defined in Nix.String

Monoid NixLikeContextValue Source # 
Instance details

Defined in Nix.String

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

Defined in Nix.Convert

Methods

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

type Rep NixLikeContextValue Source # 
Instance details

Defined in Nix.String

type Rep NixLikeContextValue = D1 (MetaData "NixLikeContextValue" "Nix.String" "hnix-0.6.1-1597pjcbiB2Cib3HzwJZxT" False) (C1 (MetaCons "NixLikeContextValue" PrefixI True) (S1 (MetaSel (Just "nlcvPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "nlcvAllOutputs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "nlcvOutputs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))

stringHasContext :: NixString -> Bool Source #

Returns True if the NixString has an associated context

principledIntercalateNixString :: NixString -> [NixString] -> NixString Source #

Combine NixStrings with a separator

hackyGetStringNoContext :: NixString -> Maybe Text Source #

Extract the string contents from a NixString that has no context

principledGetStringNoContext :: NixString -> Maybe Text Source #

Extract the string contents from a NixString that has no context

principledStringIgnoreContext :: NixString -> Text Source #

Extract the string contents from a NixString even if the NixString has an associated context

hackyStringIgnoreContext :: NixString -> Text Source #

Extract the string contents from a NixString even if the NixString has an associated context

hackyMakeNixStringWithoutContext :: Text -> NixString Source #

Constructs a NixString without a context

principledMakeNixStringWithoutContext :: Text -> NixString Source #

Constructs a NixString without a context

principledMakeNixStringWithSingletonContext :: Text -> StringContext -> NixString Source #

Create a NixString using a singleton context

principledModifyNixContents :: (Text -> Text) -> NixString -> NixString Source #

Modify the string part of the NixString, leaving the context unchanged

principledStringMappend :: NixString -> NixString -> NixString Source #

Combine two NixStrings using mappend

principledStringMempty :: NixString Source #

Empty string with empty context.

principledStringMConcat :: [NixString] -> NixString Source #

Combine NixStrings using mconcat

newtype WithStringContextT m a Source #

A monad for accumulating string context while producing a result string.

Instances
MonadTrans WithStringContextT Source # 
Instance details

Defined in Nix.String

Methods

lift :: Monad m => m a -> WithStringContextT m a #

Monad m => Monad (WithStringContextT m) Source # 
Instance details

Defined in Nix.String

Functor m => Functor (WithStringContextT m) Source # 
Instance details

Defined in Nix.String

Methods

fmap :: (a -> b) -> WithStringContextT m a -> WithStringContextT m b #

(<$) :: a -> WithStringContextT m b -> WithStringContextT m a #

Applicative m => Applicative (WithStringContextT m) Source # 
Instance details

Defined in Nix.String

Monad m => MonadWriter (HashSet StringContext) (WithStringContextT m) Source # 
Instance details

Defined in Nix.String

extractNixString :: Monad m => NixString -> WithStringContextT m Text Source #

Get the contents of a NixString and write its context into the resulting set.

runWithStringContextT :: Monad m => WithStringContextT m Text -> m NixString Source #

Run an action producing a string with a context and put those into a NixString.

runWithStringContext :: WithStringContextT Identity Text -> NixString Source #

Run an action producing a string with a context and put those into a NixString.