Skip to content

Commit

Permalink
Parse inherit names with quotes
Browse files Browse the repository at this point in the history
  • Loading branch information
Lucus16 committed Oct 21, 2022
1 parent 33ee5e2 commit adbb326
Show file tree
Hide file tree
Showing 6 changed files with 60 additions and 22 deletions.
45 changes: 28 additions & 17 deletions src/Nixfmt/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
- SPDX-License-Identifier: MPL-2.0
-}

{-# LANGUAGE LambdaCase, OverloadedStrings #-}
{-# LANGUAGE BlockArguments, LambdaCase, OverloadedStrings #-}

module Nixfmt.Parser where

Expand All @@ -26,9 +26,10 @@ import qualified Text.Megaparsec.Char.Lexer as L (decimal, float)

import Nixfmt.Lexer (lexeme)
import Nixfmt.Types
(Ann, Binder(..), Expression(..), File(..), Fixity(..), Leaf, Operator(..),
(Ann(..), Binder(..), Expression(..), File(..), Fixity(..), Leaf, Operator(..),
ParamAttr(..), Parameter(..), Parser, Path, Selector(..), SimpleSelector(..),
String, StringPart(..), Term(..), Token(..), operators, tokenText)
String, StringPart(..), Term(..), Token(..), operators, reservedNames,
toLeading, tokenText)
import Nixfmt.Util
(commonIndentation, identChar, isSpaces, manyP, manyText, pathChar,
schemeChar, someP, someText, uriChar)
Expand All @@ -45,16 +46,6 @@ rawSymbol t = chunk (tokenText t) *> return t
symbol :: Token -> Parser (Ann Token)
symbol = lexeme . rawSymbol

reservedNames :: [Text]
reservedNames =
[ "let", "in"
, "if", "then", "else"
, "assert"
, "with"
, "rec"
, "inherit"
]

reserved :: Token -> Parser (Ann Token)
reserved t = try $ lexeme $ rawSymbol t
<* lookAhead (satisfy (\x -> not $ identChar x || pathChar x))
Expand All @@ -67,13 +58,33 @@ integer = ann Integer L.decimal
float :: Parser (Ann Token)
float = ann Float L.float

rawIdentifier :: Parser Text
rawIdentifier = Text.cons
<$> satisfy (\x -> isAlpha x || x == '_')
<*> manyP identChar

identifier :: Parser (Ann Token)
identifier = ann Identifier $ do
ident <- Text.cons <$> satisfy (\x -> isAlpha x || x == '_')
<*> manyP identChar
identifier = ann Identifier do
ident <- rawIdentifier
guard $ not $ ident `elem` reservedNames
return ident

-- Support all of: { inherit foo "bar" ${"baz"}; }
fancyIdentifier :: Parser (Ann Token)
fancyIdentifier = identifier <|> stringIdentifier <|> curlyIdentifier

stringIdentifier :: Parser (Ann Token)
stringIdentifier = ann Identifier do
rawSymbol TDoubleQuote *> rawIdentifier <* rawSymbol TDoubleQuote

curlyIdentifier :: Parser (Ann Token)
curlyIdentifier = do
(Ann _ trailing1 leading1) <- symbol TInterOpen
(Ann i trailing2 leading2) <- stringIdentifier
(Ann _ trailing3 leading3) <- symbol TInterClose
pure $ Ann i trailing1 $
leading1 <> toLeading trailing2 <> leading2 <> toLeading trailing3 <> leading3

slash :: Parser Text
slash = chunk "/" <* notFollowedBy (char '/')

Expand Down Expand Up @@ -270,7 +281,7 @@ abstraction = try (Abstraction <$>

inherit :: Parser Binder
inherit = Inherit <$> reserved KInherit <*> optional parens <*>
many identifier <*> symbol TSemicolon
many fancyIdentifier <*> symbol TSemicolon

assignment :: Parser Binder
assignment = Assignment <$>
Expand Down
6 changes: 1 addition & 5 deletions src/Nixfmt/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Nixfmt.Predoc
import Nixfmt.Types
(Ann(..), Binder(..), Expression(..), File(..), Leaf, ParamAttr(..),
Parameter(..), Selector(..), SimpleSelector(..), StringPart(..), Term(..),
Token(..), TrailingComment(..), Trivia, Trivium(..), tokenText)
Token(..), TrailingComment(..), Trivium(..), toLeading, tokenText)
import Nixfmt.Util (commonIndentation, isSpaces, replaceMultiple)

prettyCommentLine :: Text -> Doc
Expand Down Expand Up @@ -120,10 +120,6 @@ instance Pretty Term where
pretty l@(List _ _ _) = group $ prettyTerm l
pretty x = prettyTerm x

toLeading :: Maybe TrailingComment -> Trivia
toLeading Nothing = []
toLeading (Just (TrailingComment c)) = [LineComment (" " <> c)]

prettyComma :: Maybe Leaf -> Doc
prettyComma Nothing = mempty
prettyComma (Just comma) = softline' <> pretty comma <> hardspace
Expand Down
16 changes: 16 additions & 0 deletions src/Nixfmt/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,10 @@ type Trivia = [Trivium]

newtype TrailingComment = TrailingComment Text deriving (Eq, Show)

toLeading :: Maybe TrailingComment -> Trivia
toLeading Nothing = []
toLeading (Just (TrailingComment c)) = [LineComment (" " <> c)]

data Ann a
= Ann a (Maybe TrailingComment) Trivia
deriving (Show)
Expand Down Expand Up @@ -204,7 +208,19 @@ operators =
, [ Op InfixL TImplies ]
]

reservedNames :: [Text]
reservedNames =
[ "let", "in"
, "if", "then", "else"
, "assert"
, "with"
, "rec"
, "inherit"
]

tokenText :: Token -> Text
tokenText (Identifier i)
| i `elem` reservedNames = "\"" <> i <> "\""
tokenText (Identifier i) = i
tokenText (Integer i) = pack (show i)
tokenText (Float f) = pack (show f)
Expand Down
1 change: 1 addition & 0 deletions test/correct/quotes-in-inherit.nix
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
{ inherit ({ "in" = 1; }) "in"; }
7 changes: 7 additions & 0 deletions test/improve/quotes-in-inherit.in.nix
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
let
foo = 1;
"bar" = 2;
${"baz"} = 3;
${"in"} = 4;

in { inherit ${"foo"} bar "baz" "in"; }
7 changes: 7 additions & 0 deletions test/improve/quotes-in-inherit.out.nix
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
let
foo = 1;
bar = 2;
baz = 3;
"in" = 4;

in { inherit foo bar baz "in"; }

0 comments on commit adbb326

Please sign in to comment.