Use data-fix for Fix and fix path parsing bug

This commit is contained in:
Benno Fünfstück 2014-09-27 20:11:17 +02:00
parent 7e9b2e534f
commit 1b82727a17
8 changed files with 21 additions and 30 deletions

View File

@ -3,6 +3,7 @@ module Nix.Eval where
import Control.Applicative
import Control.Arrow
import Control.Monad hiding (mapM, sequence)
import Data.Fix
import Data.Foldable (foldl')
import qualified Data.Map as Map
import Data.Text (Text)

View File

@ -5,11 +5,12 @@ module Nix.Parser (parseNixFile, parseNixString, Result(..)) where
import Control.Applicative
import Control.Monad
import Control.Monad.IO.Class
import Data.Foldable
import Data.Fix
import Data.Foldable hiding (concat)
import qualified Data.Map as Map
import Data.Text hiding (head, map, foldl1', foldl')
import Nix.Types
import Data.Text hiding (head, map, foldl1', foldl', concat)
import Nix.Parser.Library
import Nix.Types
import Prelude hiding (elem)
-- | The lexer for this parser is defined in 'Nix.Parser.Library'.
@ -95,7 +96,11 @@ nixSPath = mkPath True <$> try (char '<' *> some (oneOf pathChars <|> slash) <*
nixPath :: Parser NExpr
nixPath = token $ fmap (mkPath False) $ ((++)
<$> (try ((++) <$> many (oneOf pathChars) <*> fmap (:[]) slash) <?> "path")
<*> some (oneOf pathChars <|> slash))
<*> fmap concat
( some (some (oneOf pathChars)
<|> liftA2 (:) slash (some (oneOf pathChars)))
)
)
<?> "path"
nixLet :: Parser NExpr

View File

@ -1,5 +1,6 @@
module Nix.Pretty where
import Data.Fix
import Data.Map (toList)
import Data.Maybe (isJust)
import Data.Text (Text, unpack, replace, strip)

View File

@ -1,7 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
@ -12,6 +11,7 @@ module Nix.Types where
import Control.Applicative
import Control.Monad hiding (forM_, mapM, sequence)
import Data.Data
import Data.Fix
import Data.Foldable
import Data.List (intercalate)
import Data.Map (Map)
@ -27,14 +27,6 @@ import GHC.Generics
import Prelude hiding (readFile, concat, concatMap, elem, mapM,
sequence, minimum, foldr)
newtype Fix (f :: * -> *) = Fix { outF :: f (Fix f) }
cata :: Functor f => (f a -> a) -> Fix f -> a
cata f = f . fmap (cata f) . outF
cataM :: (Traversable f, Monad m) => (f a -> m a) -> Fix f -> m a
cataM f = f <=< mapM (cataM f) . outF
-- | Atoms are values that evaluate to themselves. This means that they appear in both
-- the parsed AST (in the form of literals) and the evaluated form.
data NAtom
@ -287,14 +279,6 @@ data Formals r
| FormalRightAt (FormalParamSet r) Text
deriving (Ord, Eq, Generic, Typeable, Data, Functor, Show, Foldable, Traversable)
-- | @formalsAsMap@ combines the outer and inner name bindings of
-- 'Formals'
formalsAsMap :: Formals r -> Map Text (Maybe r)
formalsAsMap (FormalName n) = Map.singleton n Nothing
formalsAsMap (FormalSet (FormalParamSet s)) = s
formalsAsMap (FormalLeftAt n (FormalParamSet s)) = Map.insert n Nothing s
formalsAsMap (FormalRightAt (FormalParamSet s) n) = Map.insert n Nothing s
data NExprF r
-- value types
= NConstant NAtom
@ -321,10 +305,6 @@ data NExprF r
type NExpr = Fix NExprF
instance Show (Fix NExprF) where showsPrec p (Fix f) = showsPrec p f
instance Eq (Fix NExprF) where Fix x == Fix y = x == y
instance Ord (Fix NExprF) where compare (Fix x) (Fix y) = compare x y
mkInt :: Integer -> NExpr
mkInt = Fix . NConstant . NInt
@ -379,7 +359,6 @@ instance Show f => Show (NValueF f) where
showsCon1 con a d = showParen (d > 10) $ showString (con ++ " ") . showsPrec 11 a
type NValue = Fix NValueF
instance Show (Fix NValueF) where showsPrec p (Fix f) = showsPrec p f
valueText :: NValue -> Text
valueText = cata phi where

View File

@ -1,5 +1,5 @@
{ cabal, parsers, trifecta, text, ansiWlPprint, parsec, transformers
, tasty, tastyHunit, tastyTh, unorderedContainers
, tasty, tastyHunit, tastyTh, unorderedContainers, dataFix
, useParsec ? true
}:
@ -11,7 +11,7 @@ cabal.mkDerivation (self: rec {
isExecutable = true;
noHaddock = true;
buildDepends = [
ansiWlPprint text transformers parsers
ansiWlPprint text transformers parsers dataFix
] ++ (if useParsec then [ parsec ] else [ trifecta ]);
testDepends = [
tasty tastyHunit tastyTh unorderedContainers

View File

@ -49,6 +49,7 @@ Library
, transformers
, parsers >= 0.10
, unordered-containers
, data-fix
if flag(parsec)
Cpp-options: -DUSE_PARSEC
Build-depends: parsec
@ -80,6 +81,7 @@ Executable hnix
, hnix
, containers
, ansi-wl-pprint
, data-fix
Ghc-options: -Wall
Test-suite hnix-tests
@ -93,6 +95,7 @@ Test-suite hnix-tests
base >= 4.3 && < 5
, containers
, text
, data-fix
, hnix
, tasty
, tasty-th

View File

@ -5,9 +5,10 @@ import Nix.Pretty
import Nix.Eval
import Nix.Types
import Text.PrettyPrint.ANSI.Leijen
import Data.Fix
import System.Environment
import System.IO
import Text.PrettyPrint.ANSI.Leijen
import qualified Data.Map as Map

View File

@ -2,10 +2,11 @@
{-# LANGUAGE OverloadedStrings #-}
module ParserTests (tests) where
import Data.Fix
import Data.Text (pack)
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import Data.Text (pack)
import qualified Data.Map as Map