Switch from pretty to ansi-wl-pprint

This commit is contained in:
John Wiegley 2014-07-18 04:42:06 -05:00
parent 74e85e44f8
commit 92cf6eecf9
4 changed files with 17 additions and 20 deletions

5
Nix.hs
View File

@ -5,8 +5,9 @@ import Nix.Eval
import Nix.Parser
import Nix.Pretty
import Nix.Types
import Text.PrettyPrint.HughesPJ
import Text.PrettyPrint.ANSI.Leijen
import System.Environment
import System.IO
nix :: FilePath -> IO ()
nix path = do
@ -14,7 +15,7 @@ nix path = do
case res of
Failure e -> error $ "Parse failed: " ++ show e
Success n -> do
putStrLn $ render (prettyNix n)
displayIO stdout $ renderPretty 0.4 80 (prettyNix n)
top <- evalExpr n (Fix (NVSet Map.empty)) -- evaluate top level
print top

View File

@ -1,9 +1,9 @@
module Nix.Pretty where
import Text.PrettyPrint.HughesPJ
import Nix.Types
import Data.Map (toList)
import Data.Text (Text, unpack)
import Nix.Types
import Text.PrettyPrint.ANSI.Leijen
prettyBind :: (NExpr, NExpr) -> Doc
prettyBind (n, v) = prettyNix n <+> equals <+> prettyNix v <> semi
@ -39,32 +39,31 @@ prettyOper (NDiv r1 r2) = infixOper r1 "/" r2
prettyOper (NConcat r1 r2) = infixOper r1 "++" r2
prettyAtom :: NAtom -> Doc
prettyAtom (NStr s) = doubleQuotes $ text $ unpack $ s
prettyAtom (NStr s) = dquotes $ text $ unpack s
prettyAtom atom = text $ unpack $ atomText atom
prettyNix :: NExpr -> Doc
prettyNix (Fix expr) = go expr where
go (NConstant atom) = prettyAtom atom
go (NOper oper) = prettyOper oper
go (NList list) = lbrack <+> (fsep $ map prettyNix list) <+> rbrack
go (NOper oper) = prettyOper oper
go (NList xs) = lbracket <+> fillSep (map prettyNix xs) <+> rbracket
go (NArgSet args) = lbrace <+> (vcat $ map prettySetArg $ toList args) <+> rbrace
go (NArgSet args) = lbrace <+> vcat (map prettySetArg $ toList args) <+> rbrace
go (NSet rec list) =
go (NSet rec xs) =
(case rec of Rec -> "rec"; NonRec -> empty)
<+> lbrace <+> (vcat $ map prettyBind list) <+> rbrace
<+> lbrace <+> vcat (map prettyBind xs) <+> rbrace
go (NLet binds body) = text "let"
go (NLet _binds _body) = text "let"
go (NIf cond trueBody falseBody) =
(text "if" <+> prettyNix cond)
$$ (text "then" <+> prettyNix trueBody)
$$ (text "else" <+> prettyNix falseBody)
<$$> (text "then" <+> prettyNix trueBody)
<$$> (text "else" <+> prettyNix falseBody)
go (NWith scope body) = text "with" <+> prettyNix scope <> semi <+> prettyNix body
go (NAssert cond body) = text "assert" <+> prettyNix cond <> semi <+> prettyNix body
go (NInherit attrs) = text "inherit"
go (NInherit _attrs) = text "inherit"
go (NVar e) = prettyNix e
go (NApp fun arg) = prettyNix fun <+> parens (prettyNix arg)
go (NAbs args body) = (prettyNix args <> colon) $$ prettyNix body
go (NAbs args body) = (prettyNix args <> colon) <$$> prettyNix body

View File

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

View File

@ -45,7 +45,6 @@ Library
base >= 4.3 && < 5
, ansi-wl-pprint
, containers
, pretty
, text
, transformers
if flag(parsec)
@ -81,7 +80,6 @@ executable hnix
, hnix
, ansi-wl-pprint
, containers
, pretty
, text
, transformers
if flag(parsec)