Merge pull request #28 from jwiegley/fix_quote_escaping

Fix quote escaping
This commit is contained in:
John Wiegley 2015-10-28 09:53:19 -07:00
commit 58ff3fbbfc
6 changed files with 37 additions and 10 deletions

View File

@ -98,7 +98,7 @@ evalExpr = cata phi
evalString :: NValue -> NString (NValue -> IO NValue) -> IO Text
evalString env (NString _ parts)
= Text.concat <$> mapM (runAntiquoted return (fmap valueText . ($ env))) parts
evalString env (NUri t) = return t
evalString _ (NUri t) = return t
evalBinds :: Bool -> NValue -> [Binding (NValue -> IO NValue)] ->
IO (Map.Map Text NValue)
@ -125,6 +125,7 @@ evalBinds allowDynamic env xs = buildResult <$> sequence (concatMap go xs) where
-- TODO: Inherit
go :: Binding (NValue -> IO NValue) -> [IO ([Text], NValue)]
go (NamedVar x y) = [liftM2 (,) (evalSelector allowDynamic env x) (y env)]
go _ = [] -- HACK! But who cares right now
evalSelector :: Bool -> NValue -> NSelector (NValue -> IO NValue) -> IO [Text]
evalSelector dyn e = mapM evalKeyName where

View File

@ -1,7 +1,12 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Nix.Parser (parseNixFile, parseNixString, Result(..)) where
module Nix.Parser (
parseNixFile,
parseNixString,
parseNixText,
Result(..)
) where
import Control.Applicative
import Control.Monad
@ -244,3 +249,6 @@ parseNixFile = parseFromFileEx $ nixExpr <* eof
parseNixString :: String -> Result NExpr
parseNixString = parseFromString $ nixExpr <* eof
parseNixText :: Text -> Result NExpr
parseNixText = parseNixString . unpack

View File

@ -48,9 +48,17 @@ atomText :: NAtom -> Text
atomText (NInt i) = pack (show i)
atomText (NBool b) = if b then "true" else "false"
atomText NNull = "null"
atomText (NPath s p)
| s = pack ("<" ++ p ++ ">")
| otherwise = pack p
atomText (NPath isFromEnv p)
| isFromEnv = pack ("<" ++ p ++ ">")
-- If it's not an absolute path, we need to prefix with ./
| otherwise = case pack p of
"./" -> "./."
"../" -> "../."
".." -> "../."
txt | "/" `T.isPrefixOf` txt -> txt
| "./" `T.isPrefixOf` txt -> txt
| "../" `T.isPrefixOf` txt -> txt
| otherwise -> "./" <> txt
-- | 'Antiquoted' represents an expression that is either
-- antiquoted (surrounded by ${...}) or plain (not antiquoted).

View File

@ -3,4 +3,6 @@ let
haskellPackages = nixpkgs.pkgs.haskell.packages.${compiler};
in
haskellPackages.callPackage ./project.nix {}
haskellPackages.callPackage ./project.nix {
pkgs = nixpkgs;
}

View File

@ -1,5 +1,5 @@
Name: hnix
Version: 0.2.2
Version: 0.2.3
Synopsis: Haskell implementation of the Nix language
Description:
Haskell implementation of the Nix language.

View File

@ -1,11 +1,19 @@
{ mkDerivation, ansi-wl-pprint, base, containers, data-fix, parsers
, stdenv, tasty, tasty-hunit, tasty-th, text, transformers
, trifecta, unordered-containers, cabal-install
, trifecta, unordered-containers, cabal-install, pkgs
}:
let
inherit (builtins) filterSource;
inherit (pkgs.lib) elem;
in
mkDerivation {
pname = "hnix";
version = "0.2.2";
src = ./.;
version = "0.2.3";
src = let
notNamed = list: name: !(elem (baseNameOf name) list);
in filterSource (n: _: notNamed [".git" "dist" "benchmarks"] n) ./.;
isLibrary = true;
isExecutable = true;
buildDepends = [