language-nix-2.3.0: Data types and functions to represent the Nix language
Safe HaskellNone
LanguageHaskell2010

Language.Nix.Identifier

Synopsis

Type-safe Identifiers

data Identifier Source #

Identifiers in Nix are essentially strings. They can be constructed (and viewed) with the ident isomorphism. For the sake of convenience, Identifiers are an instance of the IsString class.

It is usually wise to only use identifiers of the form [a-zA-Z_][a-zA-Z0-9_'-]*, because these don't need quoting. Consequently, they can appear almost anywhere in a Nix expression (whereas quoted identifiers e.g. can't be used in function patterns). The methods of the Pretty class can be used to print an identifier with proper quoting:

>>> pPrint (ident # "test")
test
>>> pPrint (ident # "foo.bar")
"foo.bar"

The HasParser class allows parsing rendered identifiers even if they are quoted:

>>> parseM "Identifier" "hello" :: Maybe Identifier
Just (Identifier "hello")
>>> parseM "Identifier" "\"3rd party\"" :: Maybe Identifier
Just (Identifier "3rd party")

Warning: Identifiers may not contain '\0', but this is not checked during construction!

See also https://nix.dev/manual/nix/2.30/language/identifiers.html.

Instances

Instances details
Arbitrary Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

CoArbitrary Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

Methods

coarbitrary :: Identifier -> Gen b -> Gen b #

IsString Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

Generic Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

Associated Types

type Rep Identifier 
Instance details

Defined in Language.Nix.Identifier

type Rep Identifier = D1 ('MetaData "Identifier" "Language.Nix.Identifier" "language-nix-2.3.0-BQfWxwWwmA8FL2B3cqaatd" 'True) (C1 ('MetaCons "Identifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))
Show Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

NFData Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

Methods

rnf :: Identifier -> () #

Eq Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

Ord Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

HasParser Identifier Source #

Note that this parser is more lenient than Nix w.r.t. simple identifiers, since it will accept nixKeywords.

Naturally, it does not support string interpolation, but does not reject strings that contain them. E.g. the string literal "hello ${world}" will contain ${world} verbatim after parsing. Do not rely on this behavior, as it may be changed in the future.

Instance details

Defined in Language.Nix.Identifier

Methods

parser :: forall st input (m :: Type -> Type). CharParser st input m Identifier #

Pretty Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

type Rep Identifier Source # 
Instance details

Defined in Language.Nix.Identifier

type Rep Identifier = D1 ('MetaData "Identifier" "Language.Nix.Identifier" "language-nix-2.3.0-BQfWxwWwmA8FL2B3cqaatd" 'True) (C1 ('MetaCons "Identifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

ident :: Iso' Identifier String Source #

An isomorphism that allows conversion of Identifier from/to the standard String type via review.

>>> ident # "hello"
Identifier "hello"
>>> from ident # fromString "hello"
"hello"

parseSimpleIdentifier :: forall st tok (m :: Type -> Type). CharParser st tok m Identifier Source #

Parsec parser for simple identifiers, i.e. those that don't need quoting. The parser is equivalent to the regular expression ^[a-zA-Z_][a-zA-Z0-9_'-]*$ which the Nix parser uses.

Note that this parser will accept keywords which would not be parsed as identifiers by Nix, see nixKeywords.

parseQuotedIdentifier :: forall st tok (m :: Type -> Type). CharParser st tok m Identifier Source #

ReadP parser for quoted identifiers, i.e. those that do need quoting.

String Predicates

needsQuoting :: String -> Bool Source #

Checks whether a given string needs quoting when interpreted as an Identifier.

Internals

nixKeywords :: [String] Source #

List of strings that are parseable as simple identifiers (see parseSimpleIdentifier) in isolation, but won't be accepted by Nix because keywords take precedence.

quote :: String -> String Source #

Helper function to quote a given identifier string if necessary. Usually, one should use the Pretty instance of Identifier instead.

>>> putStrLn (quote "abc")
abc
>>> putStrLn (quote "abc.def")
"abc.def"
>>> putStrLn (quote "$foo")
"$foo"
>>> putStrLn (quote "${foo}")
"\${foo}"