Add F version to shorthands

This commit is contained in:
Joe Hermaszewski 2016-06-25 11:48:02 +01:00
parent 5f3903caeb
commit 8c55ce604d
2 changed files with 52 additions and 25 deletions

View File

@ -1,4 +1,7 @@
-- | A bunch of shorthands for making nix expressions.
--
-- Functions with an @F@ suffix return a more general type without the outer
-- 'Fix' wrapper.
module Nix.Expr.Shorthands where
import Prelude
@ -10,8 +13,11 @@ import Nix.Atoms
import Nix.Expr.Types
-- | Make an integer literal expression.
mkInt :: Integer -> NExprF a
mkInt = NConstant . NInt
mkInt :: Integer -> NExpr
mkInt = Fix . mkIntF
mkIntF :: Integer -> NExprF a
mkIntF = NConstant . NInt
-- | Make a regular (double-quoted) string.
mkStr :: Text -> NExpr
@ -26,35 +32,56 @@ mkIndentedStr = Fix . NStr . Indented . \case
x -> [Plain x]
-- | Make a literal URI expression.
mkUri :: Text -> NExprF a
mkUri = NConstant . NUri
mkUri :: Text -> NExpr
mkUri = Fix . mkUriF
mkUriF :: Text -> NExprF a
mkUriF = NConstant . NUri
-- | Make a path. Use 'True' if the path should be read from the
-- environment, else 'False'.
mkPath :: Bool -> FilePath -> NExprF a
mkPath False = NLiteralPath
mkPath True = NEnvPath
mkPath :: Bool -> FilePath -> NExpr
mkPath b = Fix . mkPathF b
mkPathF :: Bool -> FilePath -> NExprF a
mkPathF False = NLiteralPath
mkPathF True = NEnvPath
-- | Make a path expression which pulls from the NIX_PATH env variable.
mkEnvPath :: FilePath -> NExprF a
mkEnvPath = mkPath True
mkEnvPath :: FilePath -> NExpr
mkEnvPath = Fix . mkEnvPathF
mkEnvPathF :: FilePath -> NExprF a
mkEnvPathF = mkPathF True
-- | Make a path expression which references a relative path.
mkRelPath :: FilePath -> NExprF a
mkRelPath = mkPath False
mkRelPath :: FilePath -> NExpr
mkRelPath = Fix . mkRelPathF
mkRelPathF :: FilePath -> NExprF a
mkRelPathF = mkPathF False
-- | Make a variable (symbol)
mkSym :: Text -> NExprF a
mkSym = NSym
mkSym :: Text -> NExpr
mkSym = Fix . mkSymF
mkSymF :: Text -> NExprF a
mkSymF = NSym
mkSelector :: Text -> NAttrPath NExpr
mkSelector = (:[]) . StaticKey
mkBool :: Bool -> NExprF a
mkBool = NConstant . NBool
mkBool :: Bool -> NExpr
mkBool = Fix . mkBoolF
mkNull :: NExprF a
mkNull = NConstant NNull
mkBoolF :: Bool -> NExprF a
mkBoolF = NConstant . NBool
mkNull :: NExpr
mkNull = Fix mkNullF
mkNullF :: NExprF a
mkNullF = NConstant NNull
mkOper :: NUnaryOp -> NExpr -> NExpr
mkOper op = Fix . NUnary op

View File

@ -99,18 +99,18 @@ nixToplevelForm :: Parser NExprLoc
nixToplevelForm = choice [nixLambda, nixLet, nixIf, nixAssert, nixWith]
nixSym :: Parser NExprLoc
nixSym = annotateLocation1 $ mkSym <$> identifier
nixSym = annotateLocation1 $ mkSymF <$> identifier
nixInt :: Parser NExprLoc
nixInt = annotateLocation1 $ mkInt <$> token decimal <?> "integer"
nixInt = annotateLocation1 $ mkIntF <$> token decimal <?> "integer"
nixBool :: Parser NExprLoc
nixBool = annotateLocation1 $ try (true <|> false) <?> "bool" where
true = mkBool True <$ symbol "true"
false = mkBool False <$ symbol "false"
true = mkBoolF True <$ symbol "true"
false = mkBoolF False <$ symbol "false"
nixNull :: Parser NExprLoc
nixNull = annotateLocation1 $ mkNull <$ try (symbol "null") <?> "null"
nixNull = annotateLocation1 $ mkNullF <$ try (symbol "null") <?> "null"
nixParens :: Parser NExprLoc
nixParens = parens nixExprLoc <?> "parens"
@ -127,11 +127,11 @@ slash = try (char '/' <* notFollowedBy (char '/')) <?> "slash"
-- | A path surrounded by angle brackets, indicating that it should be
-- looked up in the NIX_PATH environment variable at evaluation.
nixSPath :: Parser NExprLoc
nixSPath = annotateLocation1 $ mkPath True <$> try (char '<' *> some (oneOf pathChars <|> slash) <* symbolic '>')
nixSPath = annotateLocation1 $ mkPathF True <$> try (char '<' *> some (oneOf pathChars <|> slash) <* symbolic '>')
<?> "spath"
nixPath :: Parser NExprLoc
nixPath = annotateLocation1 $ token $ fmap (mkPath False) $ ((++)
nixPath = annotateLocation1 $ token $ fmap (mkPathF False) $ ((++)
<$> (try ((++) <$> many (oneOf pathChars) <*> fmap (:[]) slash) <?> "path")
<*> fmap concat
( some (some (oneOf pathChars)
@ -173,7 +173,7 @@ uriAfterColonC :: Parser Char
uriAfterColonC = alphaNum <|> oneOf "%/?:@&=+$,-_.!~*'"
nixUri :: Parser NExprLoc
nixUri = annotateLocation1 $ token $ fmap (mkUri . pack) $ (++)
nixUri = annotateLocation1 $ token $ fmap (mkUriF . pack) $ (++)
<$> try ((++) <$> (scheme <* char ':') <*> fmap (\x -> [':',x]) uriAfterColonC)
<*> many uriAfterColonC
where