| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Nix.Path
Synopsis
- data Path
 - path :: Iso' Path [Identifier]
 
Documentation
Paths are non-empty lists of identifiers in Nix.
>>>path # [ident # "yo"]Path [Identifier "yo"]
Any attempt to construct the empty path throws an error:
>>>:set -XScopedTypeVariables>>>either (\(_::SomeException) -> "empty paths are illegal") show <$> Excpt.try (evaluate (path # []))"empty paths are illegal"
Paths can be pretty-printed and parsed with the Text class:
>>>parse "Path" "foo.\"foo.bar\".bar" :: PathPath [Identifier "foo",Identifier "foo.bar",Identifier "bar"]>>>pPrint (parse "Path" "foo.\"foo\".\"bar\".bar" :: Path)foo.foo.bar.bar
\p -> Just (p :: Path) == parseM "Path" (prettyShow p)
Paths are instances of strings and can be implicitly converted:
>>>:set -XOverloadedStrings>>>pPrint $ ("yo.bar" :: Path)yo.bar>>>pPrint $ (" yo . bar" :: Path)yo.bar
Freaky quoted identifiers are fine throughout:
>>>pPrint $ path # ["yo","b\"ar"]yo."b\"ar">>>pPrint ("\"5ident\"" :: Path)"5ident">>>pPrint $ path # ["5ident","foo.bar","foo\nbar"]"5ident"."foo.bar"."foo\nbar"
Instances
| Eq Path Source # | |
| Ord Path Source # | |
| Show Path Source # | |
| IsString Path Source # | |
Defined in Language.Nix.Path Methods fromString :: String -> Path #  | |
| Generic Path Source # | |
| Arbitrary Path Source # | |
| CoArbitrary Path Source # | |
Defined in Language.Nix.Path Methods coarbitrary :: Path -> Gen b -> Gen b #  | |
| NFData Path Source # | |
Defined in Language.Nix.Path  | |
| HasParser Path Source # | |
Defined in Language.Nix.Path Methods parser :: CharParser st input m Path #  | |
| Pretty Path Source # | |
Defined in Language.Nix.Path Methods pPrintPrec :: PrettyLevel -> Rational -> Path -> Doc # pPrintList :: PrettyLevel -> [Path] -> Doc #  | |
| type Rep Path Source # | |
Defined in Language.Nix.Path type Rep Path = D1 (MetaData "Path" "Language.Nix.Path" "language-nix-2.2.0-4V8HiyuJODaH1hiGHTNPvO" True) (C1 (MetaCons "Path" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Identifier])))  | |