{-# language CPP #-}
{-# language DeriveAnyClass #-}

{-# options_ghc -fno-warn-name-shadowing #-}

-- | Main module for parsing Nix expressions.
module Nix.Parser
  ( parseNixFile
  , parseNixFileLoc
  , parseNixText
  , parseNixTextLoc
  , parseExpr
  , parseFromFileEx
  , Parser
  , parseFromText
  , Result
  , reservedNames
  , OperatorInfo(..)
  , NSpecialOp(..)
  , NAssoc(..)
  , NOperatorDef
  , getUnaryOperator
  , getBinaryOperator
  , getSpecialOperator
  , nixExpr
  , nixExprAlgebra
  , nixSet
  , nixBinders
  , nixSelector
  , nixSym
  , nixPath
  , nixString
  , nixUri
  , nixSearchPath
  , nixFloat
  , nixInt
  , nixBool
  , nixNull
  , whiteSpace
  )
where

import           Nix.Prelude             hiding ( (<|>)
                                                , some
                                                , many
                                                )
import           Data.Foldable                  ( foldr1 )

import           Control.Monad                  ( msum )
import           Control.Monad.Combinators.Expr ( makeExprParser
                                                , Operator( Postfix
                                                          , InfixN
                                                          , InfixR
                                                          , Prefix
                                                          , InfixL
                                                          )
                                                )
import           Data.Char                      ( isAlpha
                                                , isDigit
                                                , isSpace
                                                )
import           Data.Data                      ( Data(..) )
import           Data.Fix                       ( Fix(..) )
import qualified Data.HashSet                  as HashSet
import qualified Data.Map                      as Map
import qualified Data.Text                     as Text
import           Nix.Expr.Types
import           Nix.Expr.Shorthands     hiding ( ($>) )
import           Nix.Expr.Types.Annotated
import           Nix.Expr.Strings               ( escapeCodes
                                                , stripIndent
                                                , mergePlain
                                                , removeEmptyPlains
                                                )
import           Nix.Render                     ( MonadFile() )
import           Prettyprinter                  ( Doc
                                                , pretty
                                                )
-- `parser-combinators` ships performance enhanced & MonadPlus-aware combinators.
-- For example `some` and `many` impoted here.
import           Text.Megaparsec         hiding ( (<|>)
                                                , State
                                                )
import           Text.Megaparsec.Char           ( space1
                                                , letterChar
                                                , char
                                                )
import qualified Text.Megaparsec.Char.Lexer    as Lexer


type Parser = ParsecT Void Text (State SourcePos)

-- * Utils

-- | Different to @isAlphaNum@
isAlphanumeric :: Char -> Bool
isAlphanumeric :: Char -> Bool
isAlphanumeric Char
x = Char -> Bool
isAlpha Char
x Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
x
{-# inline isAlphanumeric #-}

-- | @<|>@ with additional preservation of @MonadPlus@ constraint.
infixl 3 <|>
(<|>) :: MonadPlus m => m a -> m a -> m a
<|> :: m a -> m a -> m a
(<|>) = m a -> m a -> m a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus

-- ** Annotated

annotateLocation1 :: Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 :: Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 Parser a
p =
  do
    SourcePos
begin <- ParsecT Void Text (State SourcePos) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
    a
res <- Parser a
p
    SourcePos
end   <- ParsecT Void Text (State SourcePos) SourcePos
forall s (m :: * -> *). MonadState s m => m s
get -- The state set before the last whitespace

    pure $ SrcSpan -> a -> AnnUnit SrcSpan a
forall ann expr. ann -> expr -> AnnUnit ann expr
AnnUnit (SourcePos -> SourcePos -> SrcSpan
SrcSpan SourcePos
begin SourcePos
end) a
res

annotateLocation :: Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation :: Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation = (AnnUnit SrcSpan (NExprF NExprLoc) -> NExprLoc
forall ann (f :: * -> *). AnnUnit ann (f (Ann ann f)) -> Ann ann f
annUnitToAnn (AnnUnit SrcSpan (NExprF NExprLoc) -> NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NExprF NExprLoc))
-> Parser NExprLoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (ParsecT
   Void Text (State SourcePos) (AnnUnit SrcSpan (NExprF NExprLoc))
 -> Parser NExprLoc)
-> (Parser (NExprF NExprLoc)
    -> ParsecT
         Void Text (State SourcePos) (AnnUnit SrcSpan (NExprF NExprLoc)))
-> Parser (NExprF NExprLoc)
-> Parser NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser (NExprF NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NExprF NExprLoc))
forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1

annotateNamedLocation :: String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation :: String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
name = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc)
-> Parser NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
name


-- ** Grammar

reservedNames :: HashSet VarName
reservedNames :: HashSet VarName
reservedNames =
  [VarName] -> HashSet VarName
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList
    [VarName
"let", VarName
"in", VarName
"if", VarName
"then", VarName
"else", VarName
"assert", VarName
"with", VarName
"rec", VarName
"inherit"]

reservedEnd :: Char -> Bool
reservedEnd :: Char -> Bool
reservedEnd Char
x =
  Char -> Bool
isSpace Char
x Bool -> Bool -> Bool
|| (Char -> String -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` (String
"{([})];:.\"'," :: String)) Char
x
{-# inline reservedEnd #-}

reserved :: Text -> Parser ()
reserved :: Text -> Parser ()
reserved Text
n =
  Parser () -> Parser ()
forall a. Parser a -> Parser a
lexeme (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Text
Tokens Text
n ParsecT Void Text (State SourcePos) Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (ParsecT Void Text (State SourcePos) Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ((Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
reservedEnd) Parser () -> Parser () -> Parser ()
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)

exprAfterP :: Parser a -> Parser NExprLoc
exprAfterP :: Parser a -> Parser NExprLoc
exprAfterP Parser a
p = Parser a
p Parser a -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixExpr

exprAfterSymbol :: Char -> Parser NExprLoc
exprAfterSymbol :: Char -> Parser NExprLoc
exprAfterSymbol Char
p = ParsecT Void Text (State SourcePos) Char -> Parser NExprLoc
forall a. Parser a -> Parser NExprLoc
exprAfterP (ParsecT Void Text (State SourcePos) Char -> Parser NExprLoc)
-> ParsecT Void Text (State SourcePos) Char -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
p

exprAfterReservedWord :: Text -> Parser NExprLoc
exprAfterReservedWord :: Text -> Parser NExprLoc
exprAfterReservedWord Text
word = Parser () -> Parser NExprLoc
forall a. Parser a -> Parser NExprLoc
exprAfterP (Parser () -> Parser NExprLoc) -> Parser () -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Text -> Parser ()
reserved Text
word

-- | A literal copy of @megaparsec@ one but with addition of the @\r@ for Windows EOL case (@\r\n@).
-- Overall, parser should simply @\r\n -> \n@.
skipLineComment' :: Tokens Text -> Parser ()
skipLineComment' :: Tokens Text -> Parser ()
skipLineComment' Tokens Text
prefix =
  Tokens Text -> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Tokens Text
prefix ParsecT Void Text (State SourcePos) Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text (State SourcePos) Text -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Maybe String
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (String -> Maybe String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"character") ((Token Text -> Bool)
 -> ParsecT Void Text (State SourcePos) (Tokens Text))
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall a b. (a -> b) -> a -> b
$ \Token Text
x -> Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n' Bool -> Bool -> Bool
&& Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\r')

whiteSpace :: Parser ()
whiteSpace :: Parser ()
whiteSpace =
  do
    SourcePos -> Parser ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (SourcePos -> Parser ())
-> ParsecT Void Text (State SourcePos) SourcePos -> Parser ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Void Text (State SourcePos) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
    Parser () -> Parser () -> Parser () -> Parser ()
forall e s (m :: * -> *).
MonadParsec e s m =>
m () -> m () -> m () -> m ()
Lexer.space Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
space1 Parser ()
lineCmnt Parser ()
blockCmnt
 where
  lineCmnt :: Parser ()
lineCmnt  = Tokens Text -> Parser ()
skipLineComment' Tokens Text
"#"
  blockCmnt :: Parser ()
blockCmnt = Tokens Text -> Tokens Text -> Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Tokens s -> Tokens s -> m ()
Lexer.skipBlockComment Tokens Text
"/*" Tokens Text
"*/"

-- | Lexeme is a unit of the language.
-- Convention is that after lexeme an arbitrary amount of empty entities (space, comments, line breaks) are allowed.
-- This lexeme definition just skips over superflous @megaparsec: lexeme@ abstraction.
lexeme :: Parser a -> Parser a
lexeme :: Parser a -> Parser a
lexeme Parser a
p = Parser a
p Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
whiteSpace

symbol :: Char -> Parser Char
symbol :: Char -> ParsecT Void Text (State SourcePos) Char
symbol = ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a. Parser a -> Parser a
lexeme (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> (Char -> ParsecT Void Text (State SourcePos) Char)
-> Char
-> ParsecT Void Text (State SourcePos) Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char

symbols :: Text -> Parser Text
symbols :: Text -> ParsecT Void Text (State SourcePos) Text
symbols = ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall a. Parser a -> Parser a
lexeme (ParsecT Void Text (State SourcePos) Text
 -> ParsecT Void Text (State SourcePos) Text)
-> (Text -> ParsecT Void Text (State SourcePos) Text)
-> Text
-> ParsecT Void Text (State SourcePos) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ParsecT Void Text (State SourcePos) Text
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk

-- We restrict the type of 'parens' and 'brackets' here because if they were to
-- take a @Parser NExprLoc@ argument they would parse additional text which
-- wouldn't be captured in the source location annotation.
--
-- Braces and angles in hnix don't enclose a single expression so this type
-- restriction would not be useful.
parens :: Parser (NExprF f) -> Parser (NExprF f)
parens :: Parser (NExprF f) -> Parser (NExprF f)
parens   = (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char
 -> Parser (NExprF f)
 -> Parser (NExprF f))
-> (Char -> ParsecT Void Text (State SourcePos) Char)
-> Char
-> Char
-> Parser (NExprF f)
-> Parser (NExprF f)
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
-> Parser (NExprF f)
-> Parser (NExprF f)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'(' Char
')'

braces :: Parser a -> Parser a
braces :: Parser a -> Parser a
braces   = (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char
 -> Parser a
 -> Parser a)
-> (Char -> ParsecT Void Text (State SourcePos) Char)
-> Char
-> Char
-> Parser a
-> Parser a
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char -> Parser a -> Parser a
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'{' Char
'}'

brackets :: Parser (NExprF f) -> Parser (NExprF f)
brackets :: Parser (NExprF f) -> Parser (NExprF f)
brackets = (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char
 -> Parser (NExprF f)
 -> Parser (NExprF f))
-> (Char -> ParsecT Void Text (State SourcePos) Char)
-> Char
-> Char
-> Parser (NExprF f)
-> Parser (NExprF f)
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
-> Parser (NExprF f)
-> Parser (NExprF f)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'[' Char
']'

antiquotedIsHungryForTrailingSpaces :: Bool -> Parser (Antiquoted v NExprLoc)
antiquotedIsHungryForTrailingSpaces :: Bool -> Parser (Antiquoted v NExprLoc)
antiquotedIsHungryForTrailingSpaces Bool
hungry = NExprLoc -> Antiquoted v NExprLoc
forall v r. r -> Antiquoted v r
Antiquoted (NExprLoc -> Antiquoted v NExprLoc)
-> Parser NExprLoc -> Parser (Antiquoted v NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text (State SourcePos) Text
antiStart ParsecT Void Text (State SourcePos) Text
-> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixExpr Parser NExprLoc
-> ParsecT Void Text (State SourcePos) Char -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text (State SourcePos) Char
antiEnd)
 where
  antiStart :: Parser Text
  antiStart :: ParsecT Void Text (State SourcePos) Text
antiStart = String
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"${" (ParsecT Void Text (State SourcePos) Text
 -> ParsecT Void Text (State SourcePos) Text)
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT Void Text (State SourcePos) Text
symbols Text
"${"

  antiEnd :: Parser Char
  antiEnd :: ParsecT Void Text (State SourcePos) Char
antiEnd = String
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"}" (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a b. (a -> b) -> a -> b
$
    (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> (ParsecT Void Text (State SourcePos) Char
    -> ParsecT Void Text (State SourcePos) Char)
-> Bool
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a. a -> a -> Bool -> a
bool
      ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a. a -> a
id
      ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a. Parser a -> Parser a
lexeme
      Bool
hungry
      (Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'}')

antiquotedLexeme :: Parser (Antiquoted v NExprLoc)
antiquotedLexeme :: Parser (Antiquoted v NExprLoc)
antiquotedLexeme = Bool -> Parser (Antiquoted v NExprLoc)
forall v. Bool -> Parser (Antiquoted v NExprLoc)
antiquotedIsHungryForTrailingSpaces Bool
True

antiquoted :: Parser (Antiquoted v NExprLoc)
antiquoted :: Parser (Antiquoted v NExprLoc)
antiquoted = Bool -> Parser (Antiquoted v NExprLoc)
forall v. Bool -> Parser (Antiquoted v NExprLoc)
antiquotedIsHungryForTrailingSpaces Bool
False

---------------------------------------------------------------------------------

-- * Parser parts

-- ** Constrants

nixNull :: Parser NExprLoc
nixNull :: Parser NExprLoc
nixNull =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"null" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    NExprF NExprLoc
forall a. NExprF a
mkNullF NExprF NExprLoc -> Parser () -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser ()
reserved Text
"null"

nixBool :: Parser NExprLoc
nixBool :: Parser NExprLoc
nixBool =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"bool" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    (Parser (NExprF NExprLoc)
 -> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> ((Bool, Text) -> Parser (NExprF NExprLoc))
-> (Bool, Text)
-> (Bool, Text)
-> Parser (NExprF NExprLoc)
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Parser (NExprF NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
(<|>) (Bool, Text) -> Parser (NExprF NExprLoc)
forall a.
(Bool, Text) -> ParsecT Void Text (State SourcePos) (NExprF a)
lmkBool (Bool
True, Text
"true") (Bool
False, Text
"false")
 where
  lmkBool :: (Bool, Text) -> ParsecT Void Text (State SourcePos) (NExprF a)
lmkBool (Bool
b, Text
txt) = Bool -> NExprF a
forall a. Bool -> NExprF a
mkBoolF Bool
b NExprF a
-> Parser () -> ParsecT Void Text (State SourcePos) (NExprF a)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser ()
reserved Text
txt

integer :: Parser Integer
integer :: Parser Integer
integer = Parser Integer -> Parser Integer
forall a. Parser a -> Parser a
lexeme Parser Integer
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
Lexer.decimal

nixInt :: Parser NExprLoc
nixInt :: Parser NExprLoc
nixInt =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"integer" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Integer -> NExprF NExprLoc
forall a. Integer -> NExprF a
mkIntF (Integer -> NExprF NExprLoc)
-> Parser Integer -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Integer
integer

float :: Parser Double
float :: Parser Double
float = Parser Double -> Parser Double
forall a. Parser a -> Parser a
lexeme Parser Double
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, RealFloat a) =>
m a
Lexer.float

nixFloat :: Parser NExprLoc
nixFloat :: Parser NExprLoc
nixFloat =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"float" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$
      Float -> NExprF NExprLoc
forall a. Float -> NExprF a
mkFloatF (Float -> NExprF NExprLoc)
-> (Double -> Float) -> Double -> NExprF NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> NExprF NExprLoc)
-> Parser Double -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Double
float

nixUri :: Parser NExprLoc
nixUri :: Parser NExprLoc
nixUri =
  Parser NExprLoc -> Parser NExprLoc
forall a. Parser a -> Parser a
lexeme (Parser NExprLoc -> Parser NExprLoc)
-> Parser NExprLoc -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
      Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$
        do
          Char
start    <- ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
letterChar
          Text
protocol <-
            Maybe String
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe String
forall a. Monoid a => a
mempty ((Token Text -> Bool)
 -> ParsecT Void Text (State SourcePos) (Tokens Text))
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall a b. (a -> b) -> a -> b
$
              \ Token Text
x ->
                Char -> Bool
isAlphanumeric Char
Token Text
x
                Bool -> Bool -> Bool
|| (Char -> String -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` (String
"+-." :: String)) Char
Token Text
x
          Char
_       <- Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Token s -> m (Token s)
single Char
Token Text
':'
          Text
address <-
            Maybe String
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P Maybe String
forall a. Monoid a => a
mempty ((Token Text -> Bool)
 -> ParsecT Void Text (State SourcePos) (Tokens Text))
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall a b. (a -> b) -> a -> b
$
                \ Token Text
x ->
                  Char -> Bool
isAlphanumeric Char
Token Text
x
                  Bool -> Bool -> Bool
|| (Char -> String -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` (String
"%/?:@&=+$,-_.!~*'" :: String)) Char
Token Text
x
          NExprF NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NExprF NExprLoc -> Parser (NExprF NExprLoc))
-> (Text -> NExprF NExprLoc) -> Text -> Parser (NExprF NExprLoc)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NString NExprLoc -> NExprF NExprLoc
forall r. NString r -> NExprF r
NStr (NString NExprLoc -> NExprF NExprLoc)
-> (Text -> NString NExprLoc) -> Text -> NExprF NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text NExprLoc] -> NString NExprLoc
forall r. [Antiquoted Text r] -> NString r
DoubleQuoted ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> (Text -> [Antiquoted Text NExprLoc]) -> Text -> NString NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Antiquoted Text NExprLoc -> [Antiquoted Text NExprLoc]
forall x. One x => OneItem x -> x
one (Antiquoted Text NExprLoc -> [Antiquoted Text NExprLoc])
-> (Text -> Antiquoted Text NExprLoc)
-> Text
-> [Antiquoted Text NExprLoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Antiquoted Text NExprLoc
forall v r. v -> Antiquoted v r
Plain (Text -> Parser (NExprF NExprLoc))
-> Text -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$ Char
start Char -> Text -> Text
`Text.cons` Text
protocol Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
address


-- ** Strings

nixAntiquoted :: Parser a -> Parser (Antiquoted a NExprLoc)
nixAntiquoted :: Parser a -> Parser (Antiquoted a NExprLoc)
nixAntiquoted Parser a
p =
  String
-> Parser (Antiquoted a NExprLoc) -> Parser (Antiquoted a NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"anti-quotation" (Parser (Antiquoted a NExprLoc) -> Parser (Antiquoted a NExprLoc))
-> Parser (Antiquoted a NExprLoc) -> Parser (Antiquoted a NExprLoc)
forall a b. (a -> b) -> a -> b
$
    Parser (Antiquoted a NExprLoc)
forall v. Parser (Antiquoted v NExprLoc)
antiquotedLexeme
    Parser (Antiquoted a NExprLoc)
-> Parser (Antiquoted a NExprLoc) -> Parser (Antiquoted a NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> a -> Antiquoted a NExprLoc
forall v r. v -> Antiquoted v r
Plain (a -> Antiquoted a NExprLoc)
-> Parser a -> Parser (Antiquoted a NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser a
p

escapeCode :: Parser Char
escapeCode :: ParsecT Void Text (State SourcePos) Char
escapeCode =
  [ParsecT Void Text (State SourcePos) Char]
-> ParsecT Void Text (State SourcePos) Char
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
    [ Char
c Char
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
e | (Char
c, Char
e) <- [(Char, Char)]
escapeCodes ]
  ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle

stringChar
  :: Parser ()
  -> Parser ()
  -> Parser (Antiquoted Text NExprLoc)
  -> Parser (Antiquoted Text NExprLoc)
stringChar :: Parser ()
-> Parser ()
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
stringChar Parser ()
end Parser ()
escStart Parser (Antiquoted Text NExprLoc)
esc =
  Parser (Antiquoted Text NExprLoc)
forall v. Parser (Antiquoted v NExprLoc)
antiquoted
  Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Text -> Antiquoted Text NExprLoc
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text NExprLoc)
-> (Char -> Text) -> Char -> Antiquoted Text NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
forall x. One x => OneItem x -> x
one (Char -> Antiquoted Text NExprLoc)
-> ParsecT Void Text (State SourcePos) Char
-> Parser (Antiquoted Text NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'$'
  Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (Antiquoted Text NExprLoc)
esc
  Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Text -> Antiquoted Text NExprLoc
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text NExprLoc)
-> (String -> Text) -> String -> Antiquoted Text NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString (String -> Antiquoted Text NExprLoc)
-> ParsecT Void Text (State SourcePos) String
-> Parser (Antiquoted Text NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ParsecT Void Text (State SourcePos) Char
plainChar
  where
  plainChar :: Parser Char
  plainChar :: ParsecT Void Text (State SourcePos) Char
plainChar =
    Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Parser ()
end Parser () -> Parser () -> Parser ()
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> ParsecT Void Text (State SourcePos) Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'$') Parser () -> Parser () -> Parser ()
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser ()
escStart) Parser ()
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle

doubleQuoted :: Parser (NString NExprLoc)
doubleQuoted :: Parser (NString NExprLoc)
doubleQuoted =
  String -> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"double quoted string" (Parser (NString NExprLoc) -> Parser (NString NExprLoc))
-> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall a b. (a -> b) -> a -> b
$
    [Antiquoted Text NExprLoc] -> NString NExprLoc
forall r. [Antiquoted Text r] -> NString r
DoubleQuoted ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> ([Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc])
-> [Antiquoted Text NExprLoc]
-> NString NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
removeEmptyPlains ([Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc])
-> ([Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc])
-> [Antiquoted Text NExprLoc]
-> [Antiquoted Text NExprLoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
-> Parser (NString NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
forall a. Parser a -> Parser a
inQuotationMarks (Parser (Antiquoted Text NExprLoc)
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (Parser (Antiquoted Text NExprLoc)
 -> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc])
-> Parser (Antiquoted Text NExprLoc)
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
forall a b. (a -> b) -> a -> b
$ Parser ()
-> Parser ()
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
stringChar Parser ()
quotationMark (ParsecT Void Text (State SourcePos) Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text (State SourcePos) Char -> Parser ())
-> ParsecT Void Text (State SourcePos) Char -> Parser ()
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\\') Parser (Antiquoted Text NExprLoc)
forall r. Parser (Antiquoted Text r)
doubleEscape)
  where
  inQuotationMarks :: Parser a -> Parser a
  inQuotationMarks :: Parser a -> Parser a
inQuotationMarks Parser a
expr = Parser ()
quotationMark Parser () -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
expr Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
quotationMark

  quotationMark :: Parser ()
  quotationMark :: Parser ()
quotationMark = ParsecT Void Text (State SourcePos) Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text (State SourcePos) Char -> Parser ())
-> ParsecT Void Text (State SourcePos) Char -> Parser ()
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'"'

  doubleEscape :: Parser (Antiquoted Text r)
  doubleEscape :: Parser (Antiquoted Text r)
doubleEscape = Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text r)
-> (Char -> Text) -> Char -> Antiquoted Text r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
forall x. One x => OneItem x -> x
one (Char -> Antiquoted Text r)
-> ParsecT Void Text (State SourcePos) Char
-> Parser (Antiquoted Text r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\\' ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text (State SourcePos) Char
escapeCode)


indented :: Parser (NString NExprLoc)
indented :: Parser (NString NExprLoc)
indented =
  String -> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"indented string" (Parser (NString NExprLoc) -> Parser (NString NExprLoc))
-> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall a b. (a -> b) -> a -> b
$
    [Antiquoted Text NExprLoc] -> NString NExprLoc
forall r. [Antiquoted Text r] -> NString r
stripIndent ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
-> Parser (NString NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
forall a. Parser a -> Parser a
inIndentedQuotation (Parser (Antiquoted Text NExprLoc)
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (Parser (Antiquoted Text NExprLoc)
 -> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc])
-> Parser (Antiquoted Text NExprLoc)
-> ParsecT Void Text (State SourcePos) [Antiquoted Text NExprLoc]
forall a b. (a -> b) -> a -> b
$ (Parser ()
 -> Parser ()
 -> Parser (Antiquoted Text NExprLoc)
 -> Parser (Antiquoted Text NExprLoc))
-> Parser ()
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Parser ()
-> Parser ()
-> Parser (Antiquoted Text NExprLoc)
-> Parser (Antiquoted Text NExprLoc)
stringChar Parser ()
indentedQuotationMark Parser (Antiquoted Text NExprLoc)
forall r. Parser (Antiquoted Text r)
indentedEscape)
 where
  -- | Read escaping inside of the "'' <expr> ''"
  indentedEscape :: Parser (Antiquoted Text r)
  indentedEscape :: Parser (Antiquoted Text r)
indentedEscape =
    Parser (Antiquoted Text r) -> Parser (Antiquoted Text r)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (Antiquoted Text r) -> Parser (Antiquoted Text r))
-> Parser (Antiquoted Text r) -> Parser (Antiquoted Text r)
forall a b. (a -> b) -> a -> b
$
      do
        Parser ()
indentedQuotationMark
        (Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text r)
-> ParsecT Void Text (State SourcePos) Text
-> Parser (Antiquoted Text r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text
"''" Text
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\'' ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Text
"$" Text
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'$'))
          Parser (Antiquoted Text r)
-> Parser (Antiquoted Text r) -> Parser (Antiquoted Text r)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|>
            do
              Char
_ <- Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'\\'
              Char
c <- ParsecT Void Text (State SourcePos) Char
escapeCode

              pure $
                Antiquoted Text r -> Antiquoted Text r -> Bool -> Antiquoted Text r
forall a. a -> a -> Bool -> a
bool
                  Antiquoted Text r
forall v r. Antiquoted v r
EscapedNewline
                  (Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text r) -> Text -> Antiquoted Text r
forall a b. (a -> b) -> a -> b
$ OneItem Text -> Text
forall x. One x => OneItem x -> x
one Char
OneItem Text
c)
                  (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n')

  -- | Enclosed into indented quatation "'' <expr> ''"
  inIndentedQuotation :: Parser a -> Parser a
  inIndentedQuotation :: Parser a -> Parser a
inIndentedQuotation Parser a
expr = Parser ()
indentedQuotationMark Parser () -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser a
expr Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
indentedQuotationMark

  -- | Symbol "''"
  indentedQuotationMark :: Parser ()
  indentedQuotationMark :: Parser ()
indentedQuotationMark = String -> Parser () -> Parser ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"\"''\"" (Parser () -> Parser ())
-> (ParsecT Void Text (State SourcePos) Text -> Parser ())
-> ParsecT Void Text (State SourcePos) Text
-> Parser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Void Text (State SourcePos) Text -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text (State SourcePos) Text -> Parser ())
-> ParsecT Void Text (State SourcePos) Text -> Parser ()
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Tokens Text
"''"


nixString' :: Parser (NString NExprLoc)
nixString' :: Parser (NString NExprLoc)
nixString' = String -> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"string" (Parser (NString NExprLoc) -> Parser (NString NExprLoc))
-> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall a b. (a -> b) -> a -> b
$ Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall a. Parser a -> Parser a
lexeme (Parser (NString NExprLoc) -> Parser (NString NExprLoc))
-> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall a b. (a -> b) -> a -> b
$ Parser (NString NExprLoc)
doubleQuoted Parser (NString NExprLoc)
-> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (NString NExprLoc)
indented

nixString :: Parser NExprLoc
nixString :: Parser NExprLoc
nixString = AnnUnit SrcSpan (NString NExprLoc) -> NExprLoc
annNStr (AnnUnit SrcSpan (NString NExprLoc) -> NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NString NExprLoc))
-> Parser NExprLoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (NString NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NString NExprLoc))
forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 Parser (NString NExprLoc)
nixString'


-- ** Names (variables aka symbols)

identifier :: Parser VarName
identifier :: Parser VarName
identifier =
  Parser VarName -> Parser VarName
forall a. Parser a -> Parser a
lexeme (Parser VarName -> Parser VarName)
-> Parser VarName -> Parser VarName
forall a b. (a -> b) -> a -> b
$
    Parser VarName -> Parser VarName
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser VarName -> Parser VarName)
-> Parser VarName -> Parser VarName
forall a b. (a -> b) -> a -> b
$
      do
        (Text -> VarName
coerce -> VarName
iD) <-
          (Char -> Text -> Text)
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Char -> Text -> Text
Text.cons
            ((Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy (\Token Text
x -> Char -> Bool
isAlpha Char
Token Text
x Bool -> Bool -> Bool
|| Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'))
            (Maybe String
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe String
forall a. Monoid a => a
mempty Char -> Bool
Token Text -> Bool
identLetter)
        Bool -> Parser ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Parser ()) -> Bool -> Parser ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ VarName
iD VarName -> HashSet VarName -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HashSet.member` HashSet VarName
reservedNames
        pure VarName
iD
 where
  identLetter :: Char -> Bool
identLetter Char
x = Char -> Bool
isAlphanumeric Char
x Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\'' Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'

nixSym :: Parser NExprLoc
nixSym :: Parser NExprLoc
nixSym = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Text -> NExprF NExprLoc
forall a. Text -> NExprF a
mkSymF (Text -> NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) Text
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser VarName -> ParsecT Void Text (State SourcePos) Text
coerce Parser VarName
identifier


-- ** ( ) parens

-- | 'nixExpr' returns an expression annotated with a source position,
-- however this position doesn't include the parsed parentheses, so remove the
-- "inner" location annotateion and annotate again, including the parentheses.
nixParens :: Parser NExprLoc
nixParens :: Parser NExprLoc
nixParens =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"parens" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall f. Parser (NExprF f) -> Parser (NExprF f)
parens (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$ AnnF SrcSpan NExprF NExprLoc -> NExprF NExprLoc
forall ann (f :: * -> *) r. AnnF ann f r -> f r
stripAnnF (AnnF SrcSpan NExprF NExprLoc -> NExprF NExprLoc)
-> (NExprLoc -> AnnF SrcSpan NExprF NExprLoc)
-> NExprLoc
-> NExprF NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NExprLoc -> AnnF SrcSpan NExprF NExprLoc
forall (f :: * -> *). Fix f -> f (Fix f)
unFix (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NExprLoc
nixExpr


-- ** [ ] list

nixList :: Parser NExprLoc
nixList :: Parser NExprLoc
nixList =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"list" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall f. Parser (NExprF f) -> Parser (NExprF f)
brackets (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$ [NExprLoc] -> NExprF NExprLoc
forall r. [r] -> NExprF r
NList ([NExprLoc] -> NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) [NExprLoc]
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NExprLoc -> ParsecT Void Text (State SourcePos) [NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many Parser NExprLoc
nixTerm


-- ** { } set

nixBinders :: Parser [Binding NExprLoc]
nixBinders :: Parser [Binding NExprLoc]
nixBinders = (ParsecT Void Text (State SourcePos) (Binding NExprLoc)
inherit ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
namedVar) ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) Char
-> Parser [Binding NExprLoc]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`endBy` Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
';' where
  inherit :: ParsecT Void Text (State SourcePos) (Binding NExprLoc)
inherit =
    do
      -- We can't use 'reserved' here because it would consume the whitespace
      -- after the keyword, which is not exactly the semantics of C++ Nix.
      Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Tokens Text
"inherit" ParsecT Void Text (State SourcePos) Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (ParsecT Void Text (State SourcePos) Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text (State SourcePos) Char -> Parser ())
-> ParsecT Void Text (State SourcePos) Char -> Parser ()
forall a b. (a -> b) -> a -> b
$ (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
reservedEnd)
      SourcePos
p <- ParsecT Void Text (State SourcePos) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
      Maybe NExprLoc
x <- Parser ()
whiteSpace Parser ()
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser NExprLoc
scope
      String
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"inherited binding" (ParsecT Void Text (State SourcePos) (Binding NExprLoc)
 -> ParsecT Void Text (State SourcePos) (Binding NExprLoc))
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall a b. (a -> b) -> a -> b
$
        ([VarName] -> SourcePos -> Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) [VarName]
-> ParsecT Void Text (State SourcePos) SourcePos
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Maybe NExprLoc -> [VarName] -> SourcePos -> Binding NExprLoc
forall r. Maybe r -> [VarName] -> SourcePos -> Binding r
Inherit Maybe NExprLoc
x)
          (Parser VarName -> ParsecT Void Text (State SourcePos) [VarName]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many Parser VarName
identifier)
          (SourcePos -> ParsecT Void Text (State SourcePos) SourcePos
forall (f :: * -> *) a. Applicative f => a -> f a
pure SourcePos
p)
  namedVar :: ParsecT Void Text (State SourcePos) (Binding NExprLoc)
namedVar =
    do
      SourcePos
p <- ParsecT Void Text (State SourcePos) SourcePos
forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
      String
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"variable binding" (ParsecT Void Text (State SourcePos) (Binding NExprLoc)
 -> ParsecT Void Text (State SourcePos) (Binding NExprLoc))
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall a b. (a -> b) -> a -> b
$
        (NAttrPath NExprLoc -> NExprLoc -> SourcePos -> Binding NExprLoc)
-> ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
-> Parser NExprLoc
-> ParsecT Void Text (State SourcePos) SourcePos
-> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 NAttrPath NExprLoc -> NExprLoc -> SourcePos -> Binding NExprLoc
forall r. NAttrPath r -> r -> SourcePos -> Binding r
NamedVar
          (AnnUnit SrcSpan (NAttrPath NExprLoc) -> NAttrPath NExprLoc
forall ann expr. AnnUnit ann expr -> expr
annotated (AnnUnit SrcSpan (NAttrPath NExprLoc) -> NAttrPath NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector)
          (Char -> Parser NExprLoc
exprAfterSymbol Char
'=')
          (SourcePos -> ParsecT Void Text (State SourcePos) SourcePos
forall (f :: * -> *) a. Applicative f => a -> f a
pure SourcePos
p)
  scope :: Parser NExprLoc
scope = String -> Parser NExprLoc -> Parser NExprLoc
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"inherit scope" Parser NExprLoc
nixParens

nixSet :: Parser NExprLoc
nixSet :: Parser NExprLoc
nixSet =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"set" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    ParsecT
  Void Text (State SourcePos) ([Binding NExprLoc] -> NExprF NExprLoc)
forall r.
ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
isRec ParsecT
  Void Text (State SourcePos) ([Binding NExprLoc] -> NExprF NExprLoc)
-> Parser [Binding NExprLoc] -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [Binding NExprLoc] -> Parser [Binding NExprLoc]
forall a. Parser a -> Parser a
braces Parser [Binding NExprLoc]
nixBinders
 where
  isRec :: ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
isRec =
    String
-> ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
-> ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"recursive set" (Text -> Parser ()
reserved Text
"rec" Parser ()
-> ([Binding r] -> NExprF r)
-> ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Recursivity -> [Binding r] -> NExprF r
forall r. Recursivity -> [Binding r] -> NExprF r
NSet Recursivity
Recursive)
    ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
-> ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
-> ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> ([Binding r] -> NExprF r)
-> ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Recursivity -> [Binding r] -> NExprF r
forall r. Recursivity -> [Binding r] -> NExprF r
NSet Recursivity
forall a. Monoid a => a
mempty)

-- ** /x/y/z literal Path

pathChar :: Char -> Bool
pathChar :: Char -> Bool
pathChar Char
x =
  Char -> Bool
isAlphanumeric Char
x Bool -> Bool -> Bool
|| (Char -> String -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` (String
"._-+~" :: String)) Char
x

slash :: Parser Char
slash :: ParsecT Void Text (State SourcePos) Char
slash =
  String
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"slash " (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a b. (a -> b) -> a -> b
$
    ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall a b. (a -> b) -> a -> b
$
      Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'/' ParsecT Void Text (State SourcePos) Char
-> Parser () -> ParsecT Void Text (State SourcePos) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text (State SourcePos) Char -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy ((Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy ((Token Text -> Bool)
 -> ParsecT Void Text (State SourcePos) (Token Text))
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Token Text)
forall a b. (a -> b) -> a -> b
$ \Token Text
x -> Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/' Bool -> Bool -> Bool
|| Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'*' Bool -> Bool -> Bool
|| Char -> Bool
isSpace Char
Token Text
x)

pathStr :: Parser Path
pathStr :: Parser Path
pathStr =
  Parser Path -> Parser Path
forall a. Parser a -> Parser a
lexeme (Parser Path -> Parser Path) -> Parser Path -> Parser Path
forall a b. (a -> b) -> a -> b
$ String -> Path
coerce (String -> Path) -> (Text -> String) -> Text -> Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
forall a. ToString a => a -> String
toString (Text -> Path)
-> ParsecT Void Text (State SourcePos) Text -> Parser Path
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
    (Text -> Text -> Text)
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>)
      (Maybe String
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe String
forall a. Monoid a => a
mempty Char -> Bool
Token Text -> Bool
pathChar)
      ([Text] -> Text
Text.concat ([Text] -> Text)
-> ParsecT Void Text (State SourcePos) [Text]
-> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
        ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) [Text]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some
          ((Char -> Text -> Text)
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Char -> Text -> Text
Text.cons
            ParsecT Void Text (State SourcePos) Char
slash
            (Maybe String
-> (Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P Maybe String
forall a. Monoid a => a
mempty Char -> Bool
Token Text -> Bool
pathChar)
          )
      )

nixPath :: Parser NExprLoc
nixPath :: Parser NExprLoc
nixPath =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"path" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$ Bool -> String -> NExprF NExprLoc
forall a. Bool -> String -> NExprF a
mkPathF Bool
False (String -> NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) String
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Path -> ParsecT Void Text (State SourcePos) String
coerce Parser Path
pathStr


-- ** <<x>> environment path

-- | A path surrounded by angle brackets, indicating that it should be
-- looked up in the NIX_PATH environment variable at evaluation.
nixSearchPath :: Parser NExprLoc
nixSearchPath :: Parser NExprLoc
nixSearchPath =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"spath" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Bool -> String -> NExprF NExprLoc
forall a. Bool -> String -> NExprF a
mkPathF Bool
True (String -> NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) String
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text (State SourcePos) String
-> ParsecT Void Text (State SourcePos) String
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text (State SourcePos) String
-> ParsecT Void Text (State SourcePos) String
forall a. Parser a -> Parser a
lexeme (ParsecT Void Text (State SourcePos) String
 -> ParsecT Void Text (State SourcePos) String)
-> ParsecT Void Text (State SourcePos) String
-> ParsecT Void Text (State SourcePos) String
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'<' ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) String
-> ParsecT Void Text (State SourcePos) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ((Token Text -> Bool)
-> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
pathChar ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> ParsecT Void Text (State SourcePos) Char
slash) ParsecT Void Text (State SourcePos) String
-> ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'>')


-- ** Operators

data NSpecialOp = NHasAttrOp | NSelectOp
  deriving (NSpecialOp -> NSpecialOp -> Bool
(NSpecialOp -> NSpecialOp -> Bool)
-> (NSpecialOp -> NSpecialOp -> Bool) -> Eq NSpecialOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NSpecialOp -> NSpecialOp -> Bool
$c/= :: NSpecialOp -> NSpecialOp -> Bool
== :: NSpecialOp -> NSpecialOp -> Bool
$c== :: NSpecialOp -> NSpecialOp -> Bool
Eq, Eq NSpecialOp
Eq NSpecialOp
-> (NSpecialOp -> NSpecialOp -> Ordering)
-> (NSpecialOp -> NSpecialOp -> Bool)
-> (NSpecialOp -> NSpecialOp -> Bool)
-> (NSpecialOp -> NSpecialOp -> Bool)
-> (NSpecialOp -> NSpecialOp -> Bool)
-> (NSpecialOp -> NSpecialOp -> NSpecialOp)
-> (NSpecialOp -> NSpecialOp -> NSpecialOp)
-> Ord NSpecialOp
NSpecialOp -> NSpecialOp -> Bool
NSpecialOp -> NSpecialOp -> Ordering
NSpecialOp -> NSpecialOp -> NSpecialOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NSpecialOp -> NSpecialOp -> NSpecialOp
$cmin :: NSpecialOp -> NSpecialOp -> NSpecialOp
max :: NSpecialOp -> NSpecialOp -> NSpecialOp
$cmax :: NSpecialOp -> NSpecialOp -> NSpecialOp
>= :: NSpecialOp -> NSpecialOp -> Bool
$c>= :: NSpecialOp -> NSpecialOp -> Bool
> :: NSpecialOp -> NSpecialOp -> Bool
$c> :: NSpecialOp -> NSpecialOp -> Bool
<= :: NSpecialOp -> NSpecialOp -> Bool
$c<= :: NSpecialOp -> NSpecialOp -> Bool
< :: NSpecialOp -> NSpecialOp -> Bool
$c< :: NSpecialOp -> NSpecialOp -> Bool
compare :: NSpecialOp -> NSpecialOp -> Ordering
$ccompare :: NSpecialOp -> NSpecialOp -> Ordering
$cp1Ord :: Eq NSpecialOp
Ord, (forall x. NSpecialOp -> Rep NSpecialOp x)
-> (forall x. Rep NSpecialOp x -> NSpecialOp) -> Generic NSpecialOp
forall x. Rep NSpecialOp x -> NSpecialOp
forall x. NSpecialOp -> Rep NSpecialOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NSpecialOp x -> NSpecialOp
$cfrom :: forall x. NSpecialOp -> Rep NSpecialOp x
Generic, Typeable, Typeable NSpecialOp
DataType
Constr
Typeable NSpecialOp
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> NSpecialOp -> c NSpecialOp)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NSpecialOp)
-> (NSpecialOp -> Constr)
-> (NSpecialOp -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c NSpecialOp))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c NSpecialOp))
-> ((forall b. Data b => b -> b) -> NSpecialOp -> NSpecialOp)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r)
-> (forall u. (forall d. Data d => d -> u) -> NSpecialOp -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NSpecialOp -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp)
-> Data NSpecialOp
NSpecialOp -> DataType
NSpecialOp -> Constr
(forall b. Data b => b -> b) -> NSpecialOp -> NSpecialOp
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NSpecialOp -> c NSpecialOp
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NSpecialOp
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NSpecialOp -> u
forall u. (forall d. Data d => d -> u) -> NSpecialOp -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NSpecialOp
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NSpecialOp -> c NSpecialOp
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NSpecialOp)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NSpecialOp)
$cNSelectOp :: Constr
$cNHasAttrOp :: Constr
$tNSpecialOp :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
gmapMp :: (forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
gmapM :: (forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NSpecialOp -> m NSpecialOp
gmapQi :: Int -> (forall d. Data d => d -> u) -> NSpecialOp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NSpecialOp -> u
gmapQ :: (forall d. Data d => d -> u) -> NSpecialOp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NSpecialOp -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NSpecialOp -> r
gmapT :: (forall b. Data b => b -> b) -> NSpecialOp -> NSpecialOp
$cgmapT :: (forall b. Data b => b -> b) -> NSpecialOp -> NSpecialOp
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NSpecialOp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NSpecialOp)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NSpecialOp)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NSpecialOp)
dataTypeOf :: NSpecialOp -> DataType
$cdataTypeOf :: NSpecialOp -> DataType
toConstr :: NSpecialOp -> Constr
$ctoConstr :: NSpecialOp -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NSpecialOp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NSpecialOp
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NSpecialOp -> c NSpecialOp
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NSpecialOp -> c NSpecialOp
$cp1Data :: Typeable NSpecialOp
Data, Int -> NSpecialOp -> ShowS
[NSpecialOp] -> ShowS
NSpecialOp -> String
(Int -> NSpecialOp -> ShowS)
-> (NSpecialOp -> String)
-> ([NSpecialOp] -> ShowS)
-> Show NSpecialOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NSpecialOp] -> ShowS
$cshowList :: [NSpecialOp] -> ShowS
show :: NSpecialOp -> String
$cshow :: NSpecialOp -> String
showsPrec :: Int -> NSpecialOp -> ShowS
$cshowsPrec :: Int -> NSpecialOp -> ShowS
Show, NSpecialOp -> ()
(NSpecialOp -> ()) -> NFData NSpecialOp
forall a. (a -> ()) -> NFData a
rnf :: NSpecialOp -> ()
$crnf :: NSpecialOp -> ()
NFData)

data NAssoc = NAssocNone | NAssocLeft | NAssocRight
  deriving (NAssoc -> NAssoc -> Bool
(NAssoc -> NAssoc -> Bool)
-> (NAssoc -> NAssoc -> Bool) -> Eq NAssoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NAssoc -> NAssoc -> Bool
$c/= :: NAssoc -> NAssoc -> Bool
== :: NAssoc -> NAssoc -> Bool
$c== :: NAssoc -> NAssoc -> Bool
Eq, Eq NAssoc
Eq NAssoc
-> (NAssoc -> NAssoc -> Ordering)
-> (NAssoc -> NAssoc -> Bool)
-> (NAssoc -> NAssoc -> Bool)
-> (NAssoc -> NAssoc -> Bool)
-> (NAssoc -> NAssoc -> Bool)
-> (NAssoc -> NAssoc -> NAssoc)
-> (NAssoc -> NAssoc -> NAssoc)
-> Ord NAssoc
NAssoc -> NAssoc -> Bool
NAssoc -> NAssoc -> Ordering
NAssoc -> NAssoc -> NAssoc
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NAssoc -> NAssoc -> NAssoc
$cmin :: NAssoc -> NAssoc -> NAssoc
max :: NAssoc -> NAssoc -> NAssoc
$cmax :: NAssoc -> NAssoc -> NAssoc
>= :: NAssoc -> NAssoc -> Bool
$c>= :: NAssoc -> NAssoc -> Bool
> :: NAssoc -> NAssoc -> Bool
$c> :: NAssoc -> NAssoc -> Bool
<= :: NAssoc -> NAssoc -> Bool
$c<= :: NAssoc -> NAssoc -> Bool
< :: NAssoc -> NAssoc -> Bool
$c< :: NAssoc -> NAssoc -> Bool
compare :: NAssoc -> NAssoc -> Ordering
$ccompare :: NAssoc -> NAssoc -> Ordering
$cp1Ord :: Eq NAssoc
Ord, (forall x. NAssoc -> Rep NAssoc x)
-> (forall x. Rep NAssoc x -> NAssoc) -> Generic NAssoc
forall x. Rep NAssoc x -> NAssoc
forall x. NAssoc -> Rep NAssoc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NAssoc x -> NAssoc
$cfrom :: forall x. NAssoc -> Rep NAssoc x
Generic, Typeable, Typeable NAssoc
DataType
Constr
Typeable NAssoc
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> NAssoc -> c NAssoc)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NAssoc)
-> (NAssoc -> Constr)
-> (NAssoc -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c NAssoc))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAssoc))
-> ((forall b. Data b => b -> b) -> NAssoc -> NAssoc)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NAssoc -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NAssoc -> r)
-> (forall u. (forall d. Data d => d -> u) -> NAssoc -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> NAssoc -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc)
-> Data NAssoc
NAssoc -> DataType
NAssoc -> Constr
(forall b. Data b => b -> b) -> NAssoc -> NAssoc
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAssoc -> c NAssoc
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAssoc
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NAssoc -> u
forall u. (forall d. Data d => d -> u) -> NAssoc -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAssoc
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAssoc -> c NAssoc
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NAssoc)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAssoc)
$cNAssocRight :: Constr
$cNAssocLeft :: Constr
$cNAssocNone :: Constr
$tNAssoc :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
gmapMp :: (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
gmapM :: (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NAssoc -> m NAssoc
gmapQi :: Int -> (forall d. Data d => d -> u) -> NAssoc -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NAssoc -> u
gmapQ :: (forall d. Data d => d -> u) -> NAssoc -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NAssoc -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r
gmapT :: (forall b. Data b => b -> b) -> NAssoc -> NAssoc
$cgmapT :: (forall b. Data b => b -> b) -> NAssoc -> NAssoc
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAssoc)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAssoc)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NAssoc)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NAssoc)
dataTypeOf :: NAssoc -> DataType
$cdataTypeOf :: NAssoc -> DataType
toConstr :: NAssoc -> Constr
$ctoConstr :: NAssoc -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAssoc
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAssoc
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAssoc -> c NAssoc
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAssoc -> c NAssoc
$cp1Data :: Typeable NAssoc
Data, Int -> NAssoc -> ShowS
[NAssoc] -> ShowS
NAssoc -> String
(Int -> NAssoc -> ShowS)
-> (NAssoc -> String) -> ([NAssoc] -> ShowS) -> Show NAssoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NAssoc] -> ShowS
$cshowList :: [NAssoc] -> ShowS
show :: NAssoc -> String
$cshow :: NAssoc -> String
showsPrec :: Int -> NAssoc -> ShowS
$cshowsPrec :: Int -> NAssoc -> ShowS
Show, NAssoc -> ()
(NAssoc -> ()) -> NFData NAssoc
forall a. (a -> ()) -> NFData a
rnf :: NAssoc -> ()
$crnf :: NAssoc -> ()
NFData)

data NOperatorDef
  = NUnaryDef          NUnaryOp   Text
  | NBinaryDef  NAssoc NBinaryOp  Text
  | NSpecialDef NAssoc NSpecialOp Text
  deriving (NOperatorDef -> NOperatorDef -> Bool
(NOperatorDef -> NOperatorDef -> Bool)
-> (NOperatorDef -> NOperatorDef -> Bool) -> Eq NOperatorDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NOperatorDef -> NOperatorDef -> Bool
$c/= :: NOperatorDef -> NOperatorDef -> Bool
== :: NOperatorDef -> NOperatorDef -> Bool
$c== :: NOperatorDef -> NOperatorDef -> Bool
Eq, Eq NOperatorDef
Eq NOperatorDef
-> (NOperatorDef -> NOperatorDef -> Ordering)
-> (NOperatorDef -> NOperatorDef -> Bool)
-> (NOperatorDef -> NOperatorDef -> Bool)
-> (NOperatorDef -> NOperatorDef -> Bool)
-> (NOperatorDef -> NOperatorDef -> Bool)
-> (NOperatorDef -> NOperatorDef -> NOperatorDef)
-> (NOperatorDef -> NOperatorDef -> NOperatorDef)
-> Ord NOperatorDef
NOperatorDef -> NOperatorDef -> Bool
NOperatorDef -> NOperatorDef -> Ordering
NOperatorDef -> NOperatorDef -> NOperatorDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NOperatorDef -> NOperatorDef -> NOperatorDef
$cmin :: NOperatorDef -> NOperatorDef -> NOperatorDef
max :: NOperatorDef -> NOperatorDef -> NOperatorDef
$cmax :: NOperatorDef -> NOperatorDef -> NOperatorDef
>= :: NOperatorDef -> NOperatorDef -> Bool
$c>= :: NOperatorDef -> NOperatorDef -> Bool
> :: NOperatorDef -> NOperatorDef -> Bool
$c> :: NOperatorDef -> NOperatorDef -> Bool
<= :: NOperatorDef -> NOperatorDef -> Bool
$c<= :: NOperatorDef -> NOperatorDef -> Bool
< :: NOperatorDef -> NOperatorDef -> Bool
$c< :: NOperatorDef -> NOperatorDef -> Bool
compare :: NOperatorDef -> NOperatorDef -> Ordering
$ccompare :: NOperatorDef -> NOperatorDef -> Ordering
$cp1Ord :: Eq NOperatorDef
Ord, (forall x. NOperatorDef -> Rep NOperatorDef x)
-> (forall x. Rep NOperatorDef x -> NOperatorDef)
-> Generic NOperatorDef
forall x. Rep NOperatorDef x -> NOperatorDef
forall x. NOperatorDef -> Rep NOperatorDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NOperatorDef x -> NOperatorDef
$cfrom :: forall x. NOperatorDef -> Rep NOperatorDef x
Generic, Typeable, Typeable NOperatorDef
DataType
Constr
Typeable NOperatorDef
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> NOperatorDef -> c NOperatorDef)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NOperatorDef)
-> (NOperatorDef -> Constr)
-> (NOperatorDef -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c NOperatorDef))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c NOperatorDef))
-> ((forall b. Data b => b -> b) -> NOperatorDef -> NOperatorDef)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r)
-> (forall u. (forall d. Data d => d -> u) -> NOperatorDef -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NOperatorDef -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef)
-> Data NOperatorDef
NOperatorDef -> DataType
NOperatorDef -> Constr
(forall b. Data b => b -> b) -> NOperatorDef -> NOperatorDef
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOperatorDef -> c NOperatorDef
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOperatorDef
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NOperatorDef -> u
forall u. (forall d. Data d => d -> u) -> NOperatorDef -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOperatorDef
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOperatorDef -> c NOperatorDef
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOperatorDef)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NOperatorDef)
$cNSpecialDef :: Constr
$cNBinaryDef :: Constr
$cNUnaryDef :: Constr
$tNOperatorDef :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
gmapMp :: (forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
gmapM :: (forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOperatorDef -> m NOperatorDef
gmapQi :: Int -> (forall d. Data d => d -> u) -> NOperatorDef -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NOperatorDef -> u
gmapQ :: (forall d. Data d => d -> u) -> NOperatorDef -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NOperatorDef -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOperatorDef -> r
gmapT :: (forall b. Data b => b -> b) -> NOperatorDef -> NOperatorDef
$cgmapT :: (forall b. Data b => b -> b) -> NOperatorDef -> NOperatorDef
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NOperatorDef)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NOperatorDef)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NOperatorDef)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOperatorDef)
dataTypeOf :: NOperatorDef -> DataType
$cdataTypeOf :: NOperatorDef -> DataType
toConstr :: NOperatorDef -> Constr
$ctoConstr :: NOperatorDef -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOperatorDef
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOperatorDef
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOperatorDef -> c NOperatorDef
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOperatorDef -> c NOperatorDef
$cp1Data :: Typeable NOperatorDef
Data, Int -> NOperatorDef -> ShowS
[NOperatorDef] -> ShowS
NOperatorDef -> String
(Int -> NOperatorDef -> ShowS)
-> (NOperatorDef -> String)
-> ([NOperatorDef] -> ShowS)
-> Show NOperatorDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NOperatorDef] -> ShowS
$cshowList :: [NOperatorDef] -> ShowS
show :: NOperatorDef -> String
$cshow :: NOperatorDef -> String
showsPrec :: Int -> NOperatorDef -> ShowS
$cshowsPrec :: Int -> NOperatorDef -> ShowS
Show, NOperatorDef -> ()
(NOperatorDef -> ()) -> NFData NOperatorDef
forall a. (a -> ()) -> NFData a
rnf :: NOperatorDef -> ()
$crnf :: NOperatorDef -> ()
NFData)

manyUnaryOp :: MonadPlus f => f (a -> a) -> f (a -> a)
manyUnaryOp :: f (a -> a) -> f (a -> a)
manyUnaryOp f (a -> a)
f = ((a -> a) -> (a -> a) -> a -> a) -> [a -> a] -> a -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ([a -> a] -> a -> a) -> f [a -> a] -> f (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (a -> a) -> f [a -> a]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some f (a -> a)
f

operator :: Text -> Parser Text
operator :: Text -> ParsecT Void Text (State SourcePos) Text
operator Text
op =
  case Text
op of
    c :: Text
c@Text
"-" -> Text
c Text -> Char -> ParsecT Void Text (State SourcePos) Text
`without` Char
'>'
    c :: Text
c@Text
"/" -> Text
c Text -> Char -> ParsecT Void Text (State SourcePos) Text
`without` Char
'/'
    c :: Text
c@Text
"<" -> Text
c Text -> Char -> ParsecT Void Text (State SourcePos) Text
`without` Char
'='
    c :: Text
c@Text
">" -> Text
c Text -> Char -> ParsecT Void Text (State SourcePos) Text
`without` Char
'='
    Text
n   -> Text -> ParsecT Void Text (State SourcePos) Text
symbols Text
n
 where
  without :: Text -> Char -> Parser Text
  without :: Text -> Char -> ParsecT Void Text (State SourcePos) Text
without Text
opChar Char
noNextChar =
    ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall a. Parser a -> Parser a
lexeme (ParsecT Void Text (State SourcePos) Text
 -> ParsecT Void Text (State SourcePos) Text)
-> (ParsecT Void Text (State SourcePos) Text
    -> ParsecT Void Text (State SourcePos) Text)
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text (State SourcePos) Text
 -> ParsecT Void Text (State SourcePos) Text)
-> ParsecT Void Text (State SourcePos) Text
-> ParsecT Void Text (State SourcePos) Text
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text (State SourcePos) (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Text
Tokens Text
opChar ParsecT Void Text (State SourcePos) Text
-> Parser () -> ParsecT Void Text (State SourcePos) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text (State SourcePos) Char -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
noNextChar)

opWithLoc :: (AnnUnit SrcSpan o -> a) -> o -> Text -> Parser a
opWithLoc :: (AnnUnit SrcSpan o -> a) -> o -> Text -> Parser a
opWithLoc AnnUnit SrcSpan o -> a
f o
op Text
name =
  do
    AnnUnit SrcSpan
ann Text
_ <-
      ParsecT Void Text (State SourcePos) Text
-> Parser (AnnUnit SrcSpan Text)
forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 (ParsecT Void Text (State SourcePos) Text
 -> Parser (AnnUnit SrcSpan Text))
-> ParsecT Void Text (State SourcePos) Text
-> Parser (AnnUnit SrcSpan Text)
forall a b. (a -> b) -> a -> b
$
        Text -> ParsecT Void Text (State SourcePos) Text
operator Text
name

    a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Parser a)
-> (AnnUnit SrcSpan o -> a) -> AnnUnit SrcSpan o -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnUnit SrcSpan o -> a
f (AnnUnit SrcSpan o -> Parser a) -> AnnUnit SrcSpan o -> Parser a
forall a b. (a -> b) -> a -> b
$ SrcSpan -> o -> AnnUnit SrcSpan o
forall ann expr. ann -> expr -> AnnUnit ann expr
AnnUnit SrcSpan
ann o
op

binary
  :: NAssoc
  -> (Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b)
  -> NBinaryOp
  -> Text
  -> (NOperatorDef, b)
binary :: NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b)
-> NBinaryOp
-> Text
-> (NOperatorDef, b)
binary NAssoc
assoc Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b
fixity NBinaryOp
op Text
name =
  (NAssoc -> NBinaryOp -> Text -> NOperatorDef
NBinaryDef NAssoc
assoc NBinaryOp
op Text
name, Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b
fixity (Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b)
-> Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b
forall a b. (a -> b) -> a -> b
$ (AnnUnit SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc)
-> NBinaryOp -> Text -> Parser (NExprLoc -> NExprLoc -> NExprLoc)
forall o a. (AnnUnit SrcSpan o -> a) -> o -> Text -> Parser a
opWithLoc AnnUnit SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
annNBinary NBinaryOp
op Text
name)

binaryN, binaryL, binaryR :: NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryN :: NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryN =
  NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc)
    -> Operator Parser NExprLoc)
-> NBinaryOp
-> Text
-> (NOperatorDef, Operator Parser NExprLoc)
forall b.
NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b)
-> NBinaryOp
-> Text
-> (NOperatorDef, b)
binary NAssoc
NAssocNone Parser (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixN
binaryL :: NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL =
  NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc)
    -> Operator Parser NExprLoc)
-> NBinaryOp
-> Text
-> (NOperatorDef, Operator Parser NExprLoc)
forall b.
NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b)
-> NBinaryOp
-> Text
-> (NOperatorDef, b)
binary NAssoc
NAssocLeft Parser (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixL
binaryR :: NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryR =
  NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc)
    -> Operator Parser NExprLoc)
-> NBinaryOp
-> Text
-> (NOperatorDef, Operator Parser NExprLoc)
forall b.
NAssoc
-> (Parser (NExprLoc -> NExprLoc -> NExprLoc) -> b)
-> NBinaryOp
-> Text
-> (NOperatorDef, b)
binary NAssoc
NAssocRight Parser (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixR

prefix :: NUnaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
prefix :: NUnaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
prefix NUnaryOp
op Text
name =
  (NUnaryOp -> Text -> NOperatorDef
NUnaryDef NUnaryOp
op Text
name, ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall (m :: * -> *) a. m (a -> a) -> Operator m a
Prefix (ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
 -> Operator Parser NExprLoc)
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
forall (f :: * -> *) a. MonadPlus f => f (a -> a) -> f (a -> a)
manyUnaryOp (ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
 -> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc))
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
forall a b. (a -> b) -> a -> b
$ (AnnUnit SrcSpan NUnaryOp -> NExprLoc -> NExprLoc)
-> NUnaryOp
-> Text
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
forall o a. (AnnUnit SrcSpan o -> a) -> o -> Text -> Parser a
opWithLoc AnnUnit SrcSpan NUnaryOp -> NExprLoc -> NExprLoc
annNUnary NUnaryOp
op Text
name)
-- postfix name op = (NUnaryDef name op,
--                    Postfix (opWithLoc name op annNUnary))

nixOperators
  :: Parser (AnnUnit SrcSpan (NAttrPath NExprLoc))
  -> [[ ( NOperatorDef
       , Operator Parser NExprLoc
       )
    ]]
nixOperators :: ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef, Operator Parser NExprLoc)]]
nixOperators ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
selector =
  [ -- This is not parsed here, even though technically it's part of the
    -- expression table. The problem is that in some cases, such as list
    -- membership, it's also a term. And since terms are effectively the
    -- highest precedence entities parsed by the expression parser, it ends up
    -- working out that we parse them as a kind of "meta-term".

    -- {-  1 -}
    -- [ ( NSpecialDef "." NSelectOp NAssocLeft
    --   , Postfix $
    --       do
    --         sel <- seldot *> selector
    --         mor <- optional (reserved "or" *> term)
    --         pure $ \x -> annNSelect x sel mor)
    -- ]

    {-  2 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one
      ( NAssoc -> NBinaryOp -> Text -> NOperatorDef
NBinaryDef NAssoc
NAssocLeft NBinaryOp
NApp Text
" "
      ,
        -- Thanks to Brent Yorgey for showing me this trick!
        Parser (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixL (Parser (NExprLoc -> NExprLoc -> NExprLoc)
 -> Operator Parser NExprLoc)
-> Parser (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ NExprLoc -> NExprLoc -> NExprLoc
annNApp (NExprLoc -> NExprLoc -> NExprLoc)
-> ParsecT Void Text (State SourcePos) Text
-> Parser (NExprLoc -> NExprLoc -> NExprLoc)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Void Text (State SourcePos) Text
symbols Text
forall a. Monoid a => a
mempty
      )
  , {-  3 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NUnaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
prefix  NUnaryOp
NNeg Text
"-"
  , {-  4 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one
      ( NAssoc -> NSpecialOp -> Text -> NOperatorDef
NSpecialDef NAssoc
NAssocLeft NSpecialOp
NHasAttrOp Text
"?"
      , ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall (m :: * -> *) a. m (a -> a) -> Operator m a
Postfix (ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
 -> Operator Parser NExprLoc)
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> Operator Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'?' ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ((NExprLoc -> AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc)
-> AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc -> NExprLoc
forall a b c. (a -> b -> c) -> b -> a -> c
flip NExprLoc -> AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc
annNHasAttr (AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc -> NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> ParsecT Void Text (State SourcePos) (NExprLoc -> NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
selector)
      )
  , {-  5 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryR NBinaryOp
NConcat Text
"++"
  , {-  6 -}
    [ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NMult Text
"*"
    , NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NDiv  Text
"/"
    ]
  , {-  7 -}
    [ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NPlus Text
"+"
    , NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NMinus Text
"-"
    ]
  , {-  8 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NUnaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
prefix  NUnaryOp
NNot Text
"!"
  , {-  9 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryR NBinaryOp
NUpdate Text
"//"
  , {- 10 -}
    [ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NLt Text
"<"
    , NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NGt Text
">"
    , NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NLte Text
"<="
    , NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NGte Text
">="
    ]
  , {- 11 -}
    [ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryN NBinaryOp
NEq Text
"=="
    , NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryN NBinaryOp
NNEq Text
"!="
    ]
  , {- 12 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NAnd Text
"&&"
  , {- 13 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryL NBinaryOp
NOr Text
"||"
  , {- 14 -}
    OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall x. One x => OneItem x -> x
one (OneItem [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(NOperatorDef, Operator Parser NExprLoc)])
-> OneItem [(NOperatorDef, Operator Parser NExprLoc)]
-> [(NOperatorDef, Operator Parser NExprLoc)]
forall a b. (a -> b) -> a -> b
$ NBinaryOp -> Text -> (NOperatorDef, Operator Parser NExprLoc)
binaryR NBinaryOp
NImpl Text
"->"
  ]

--  2021-11-09: NOTE: rename OperatorInfo accessors to `get*`
--  2021-08-10: NOTE:
--  All this is a sidecar:
--  * This type
--  * detectPrecedence
--  * getUnaryOperation
--  * getBinaryOperation
--  * getSpecialOperation
--  can reduced in favour of adding precedence field into @NOperatorDef@.
-- details: https://github.com/haskell-nix/hnix/issues/982
data OperatorInfo =
  OperatorInfo
    { OperatorInfo -> Int
precedence    :: Int
    , OperatorInfo -> NAssoc
associativity :: NAssoc
    , OperatorInfo -> Text
operatorName  :: Text
    }
 deriving (OperatorInfo -> OperatorInfo -> Bool
(OperatorInfo -> OperatorInfo -> Bool)
-> (OperatorInfo -> OperatorInfo -> Bool) -> Eq OperatorInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperatorInfo -> OperatorInfo -> Bool
$c/= :: OperatorInfo -> OperatorInfo -> Bool
== :: OperatorInfo -> OperatorInfo -> Bool
$c== :: OperatorInfo -> OperatorInfo -> Bool
Eq, Eq OperatorInfo
Eq OperatorInfo
-> (OperatorInfo -> OperatorInfo -> Ordering)
-> (OperatorInfo -> OperatorInfo -> Bool)
-> (OperatorInfo -> OperatorInfo -> Bool)
-> (OperatorInfo -> OperatorInfo -> Bool)
-> (OperatorInfo -> OperatorInfo -> Bool)
-> (OperatorInfo -> OperatorInfo -> OperatorInfo)
-> (OperatorInfo -> OperatorInfo -> OperatorInfo)
-> Ord OperatorInfo
OperatorInfo -> OperatorInfo -> Bool
OperatorInfo -> OperatorInfo -> Ordering
OperatorInfo -> OperatorInfo -> OperatorInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OperatorInfo -> OperatorInfo -> OperatorInfo
$cmin :: OperatorInfo -> OperatorInfo -> OperatorInfo
max :: OperatorInfo -> OperatorInfo -> OperatorInfo
$cmax :: OperatorInfo -> OperatorInfo -> OperatorInfo
>= :: OperatorInfo -> OperatorInfo -> Bool
$c>= :: OperatorInfo -> OperatorInfo -> Bool
> :: OperatorInfo -> OperatorInfo -> Bool
$c> :: OperatorInfo -> OperatorInfo -> Bool
<= :: OperatorInfo -> OperatorInfo -> Bool
$c<= :: OperatorInfo -> OperatorInfo -> Bool
< :: OperatorInfo -> OperatorInfo -> Bool
$c< :: OperatorInfo -> OperatorInfo -> Bool
compare :: OperatorInfo -> OperatorInfo -> Ordering
$ccompare :: OperatorInfo -> OperatorInfo -> Ordering
$cp1Ord :: Eq OperatorInfo
Ord, (forall x. OperatorInfo -> Rep OperatorInfo x)
-> (forall x. Rep OperatorInfo x -> OperatorInfo)
-> Generic OperatorInfo
forall x. Rep OperatorInfo x -> OperatorInfo
forall x. OperatorInfo -> Rep OperatorInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OperatorInfo x -> OperatorInfo
$cfrom :: forall x. OperatorInfo -> Rep OperatorInfo x
Generic, Typeable, Typeable OperatorInfo
DataType
Constr
Typeable OperatorInfo
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> OperatorInfo -> c OperatorInfo)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OperatorInfo)
-> (OperatorInfo -> Constr)
-> (OperatorInfo -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OperatorInfo))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OperatorInfo))
-> ((forall b. Data b => b -> b) -> OperatorInfo -> OperatorInfo)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r)
-> (forall u. (forall d. Data d => d -> u) -> OperatorInfo -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OperatorInfo -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo)
-> Data OperatorInfo
OperatorInfo -> DataType
OperatorInfo -> Constr
(forall b. Data b => b -> b) -> OperatorInfo -> OperatorInfo
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OperatorInfo -> c OperatorInfo
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OperatorInfo
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> OperatorInfo -> u
forall u. (forall d. Data d => d -> u) -> OperatorInfo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OperatorInfo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OperatorInfo -> c OperatorInfo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OperatorInfo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OperatorInfo)
$cOperatorInfo :: Constr
$tOperatorInfo :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
gmapMp :: (forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
gmapM :: (forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OperatorInfo -> m OperatorInfo
gmapQi :: Int -> (forall d. Data d => d -> u) -> OperatorInfo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OperatorInfo -> u
gmapQ :: (forall d. Data d => d -> u) -> OperatorInfo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OperatorInfo -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OperatorInfo -> r
gmapT :: (forall b. Data b => b -> b) -> OperatorInfo -> OperatorInfo
$cgmapT :: (forall b. Data b => b -> b) -> OperatorInfo -> OperatorInfo
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OperatorInfo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OperatorInfo)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OperatorInfo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OperatorInfo)
dataTypeOf :: OperatorInfo -> DataType
$cdataTypeOf :: OperatorInfo -> DataType
toConstr :: OperatorInfo -> Constr
$ctoConstr :: OperatorInfo -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OperatorInfo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OperatorInfo
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OperatorInfo -> c OperatorInfo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OperatorInfo -> c OperatorInfo
$cp1Data :: Typeable OperatorInfo
Data, Int -> OperatorInfo -> ShowS
[OperatorInfo] -> ShowS
OperatorInfo -> String
(Int -> OperatorInfo -> ShowS)
-> (OperatorInfo -> String)
-> ([OperatorInfo] -> ShowS)
-> Show OperatorInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperatorInfo] -> ShowS
$cshowList :: [OperatorInfo] -> ShowS
show :: OperatorInfo -> String
$cshow :: OperatorInfo -> String
showsPrec :: Int -> OperatorInfo -> ShowS
$cshowsPrec :: Int -> OperatorInfo -> ShowS
Show)

detectPrecedence
  :: Ord a
  => ( Int
    -> (NOperatorDef, Operator Parser NExprLoc)
    -> [(a, OperatorInfo)]
    )
  -> a
  -> OperatorInfo
detectPrecedence :: (Int
 -> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
-> a -> OperatorInfo
detectPrecedence Int
-> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)]
spec = (Map a OperatorInfo
mapOfOpWithPrecedence Map a OperatorInfo -> a -> OperatorInfo
forall k a. Ord k => Map k a -> k -> a
Map.!)
 where
  mapOfOpWithPrecedence :: Map a OperatorInfo
mapOfOpWithPrecedence =
    [(a, OperatorInfo)] -> Map a OperatorInfo
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(a, OperatorInfo)] -> Map a OperatorInfo)
-> [(a, OperatorInfo)] -> Map a OperatorInfo
forall a b. (a -> b) -> a -> b
$
      [[(a, OperatorInfo)]] -> [(a, OperatorInfo)]
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([[(a, OperatorInfo)]] -> [(a, OperatorInfo)])
-> [[(a, OperatorInfo)]] -> [(a, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$
        (Int
 -> [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(a, OperatorInfo)])
-> [Int]
-> [[(NOperatorDef, Operator Parser NExprLoc)]]
-> [[(a, OperatorInfo)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
          (((NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
-> [(NOperatorDef, Operator Parser NExprLoc)]
-> [(a, OperatorInfo)]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (((NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
 -> [(NOperatorDef, Operator Parser NExprLoc)]
 -> [(a, OperatorInfo)])
-> (Int
    -> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
-> Int
-> [(NOperatorDef, Operator Parser NExprLoc)]
-> [(a, OperatorInfo)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)]
spec)
          [Int
1 ..]
          [[(NOperatorDef, Operator Parser NExprLoc)]]
l
   where
    l :: [[(NOperatorDef, Operator Parser NExprLoc)]]
    l :: [[(NOperatorDef, Operator Parser NExprLoc)]]
l = ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef, Operator Parser NExprLoc)]]
nixOperators (ParsecT
   Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
 -> [[(NOperatorDef, Operator Parser NExprLoc)]])
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef, Operator Parser NExprLoc)]]
forall a b. (a -> b) -> a -> b
$ String
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unused"

getUnaryOperator :: NUnaryOp -> OperatorInfo
getUnaryOperator :: NUnaryOp -> OperatorInfo
getUnaryOperator = (Int
 -> (NOperatorDef, Operator Parser NExprLoc)
 -> [(NUnaryOp, OperatorInfo)])
-> NUnaryOp -> OperatorInfo
forall a.
Ord a =>
(Int
 -> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
-> a -> OperatorInfo
detectPrecedence Int
-> (NOperatorDef, Operator Parser NExprLoc)
-> [(NUnaryOp, OperatorInfo)]
forall b. Int -> (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)]
spec
 where
  spec :: Int -> (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)]
  spec :: Int -> (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)]
spec Int
i =
    \case
      (NUnaryDef NUnaryOp
op Text
name, b
_) -> OneItem [(NUnaryOp, OperatorInfo)] -> [(NUnaryOp, OperatorInfo)]
forall x. One x => OneItem x -> x
one (NUnaryOp
op, Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
i NAssoc
NAssocNone Text
name)
      (NOperatorDef, b)
_                      -> [(NUnaryOp, OperatorInfo)]
forall a. Monoid a => a
mempty

getBinaryOperator :: NBinaryOp -> OperatorInfo
getBinaryOperator :: NBinaryOp -> OperatorInfo
getBinaryOperator = (Int
 -> (NOperatorDef, Operator Parser NExprLoc)
 -> [(NBinaryOp, OperatorInfo)])
-> NBinaryOp -> OperatorInfo
forall a.
Ord a =>
(Int
 -> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
-> a -> OperatorInfo
detectPrecedence Int
-> (NOperatorDef, Operator Parser NExprLoc)
-> [(NBinaryOp, OperatorInfo)]
forall b. Int -> (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)]
spec
 where
  spec :: Int -> (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)]
  spec :: Int -> (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)]
spec Int
i =
    \case
      (NBinaryDef NAssoc
assoc NBinaryOp
op Text
name, b
_) -> OneItem [(NBinaryOp, OperatorInfo)] -> [(NBinaryOp, OperatorInfo)]
forall x. One x => OneItem x -> x
one (NBinaryOp
op, Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
i NAssoc
assoc Text
name)
      (NOperatorDef, b)
_                             -> [(NBinaryOp, OperatorInfo)]
forall a. Monoid a => a
mempty

getSpecialOperator :: NSpecialOp -> OperatorInfo
getSpecialOperator :: NSpecialOp -> OperatorInfo
getSpecialOperator NSpecialOp
NSelectOp = Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
1 NAssoc
NAssocLeft Text
"."
getSpecialOperator NSpecialOp
o         = (Int
 -> (NOperatorDef, Operator Parser NExprLoc)
 -> [(NSpecialOp, OperatorInfo)])
-> NSpecialOp -> OperatorInfo
forall a.
Ord a =>
(Int
 -> (NOperatorDef, Operator Parser NExprLoc) -> [(a, OperatorInfo)])
-> a -> OperatorInfo
detectPrecedence Int
-> (NOperatorDef, Operator Parser NExprLoc)
-> [(NSpecialOp, OperatorInfo)]
forall b. Int -> (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)]
spec NSpecialOp
o
 where
  spec :: Int -> (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)]
  spec :: Int -> (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)]
spec Int
i =
      \case
        (NSpecialDef NAssoc
assoc NSpecialOp
op Text
name, b
_) -> OneItem [(NSpecialOp, OperatorInfo)]
-> [(NSpecialOp, OperatorInfo)]
forall x. One x => OneItem x -> x
one (NSpecialOp
op, Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
i NAssoc
assoc Text
name)
        (NOperatorDef, b)
_                              -> [(NSpecialOp, OperatorInfo)]
forall a. Monoid a => a
mempty

-- ** x: y lambda function

-- | Gets all of the arguments for a function.
argExpr :: Parser (Params NExprLoc)
argExpr :: Parser (Params NExprLoc)
argExpr =
  [Parser (Params NExprLoc)] -> Parser (Params NExprLoc)
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
    [ Parser (Params NExprLoc)
atLeft
    , Parser (Params NExprLoc)
forall r. ParsecT Void Text (State SourcePos) (Params r)
onlyname
    , Parser (Params NExprLoc)
atRight
    ]
  Parser (Params NExprLoc)
-> ParsecT Void Text (State SourcePos) Char
-> Parser (Params NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
':'
 where
  -- An argument not in curly braces. There's some potential ambiguity
  -- in the case of, for example `x:y`. Is it a lambda function `x: y`, or
  -- a URI `x:y`? Nix syntax says it's the latter. So we need to fail if
  -- there's a valid URI parse here.
  onlyname :: ParsecT Void Text (State SourcePos) (Params r)
onlyname =
    [ParsecT Void Text (State SourcePos) (Params r)]
-> ParsecT Void Text (State SourcePos) (Params r)
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
      [ Parser NExprLoc
nixUri Parser NExprLoc
-> ParsecT Void Text (State SourcePos) (Params r)
-> ParsecT Void Text (State SourcePos) (Params r)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ErrorItem (Token Text)
-> ParsecT Void Text (State SourcePos) (Params r)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
ErrorItem (Token s) -> m a
unexpected (NonEmpty Char -> ErrorItem Char
forall t. NonEmpty Char -> ErrorItem t
Label (NonEmpty Char -> ErrorItem Char)
-> NonEmpty Char -> ErrorItem Char
forall a b. (a -> b) -> a -> b
$ [Item (NonEmpty Char)] -> NonEmpty Char
forall l. IsList l => [Item l] -> l
fromList [Item (NonEmpty Char)]
"valid uri" )
      , VarName -> Params r
forall r. VarName -> Params r
Param (VarName -> Params r)
-> Parser VarName -> ParsecT Void Text (State SourcePos) (Params r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser VarName
identifier
      ]

  -- Parameters named by an identifier on the left (`args @ {x, y}`)
  atLeft :: Parser (Params NExprLoc)
atLeft =
    Parser (Params NExprLoc) -> Parser (Params NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (Params NExprLoc) -> Parser (Params NExprLoc))
-> Parser (Params NExprLoc) -> Parser (Params NExprLoc)
forall a b. (a -> b) -> a -> b
$
      do
        VarName
name             <- Parser VarName
identifier Parser VarName
-> ParsecT Void Text (State SourcePos) Char -> Parser VarName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'@'
        ([(VarName, Maybe NExprLoc)]
pset, Variadic
variadic) <- Parser ([(VarName, Maybe NExprLoc)], Variadic)
params
        pure $ Maybe VarName
-> Variadic -> [(VarName, Maybe NExprLoc)] -> Params NExprLoc
forall r. Maybe VarName -> Variadic -> ParamSet r -> Params r
ParamSet (VarName -> Maybe VarName
forall (f :: * -> *) a. Applicative f => a -> f a
pure VarName
name) Variadic
variadic [(VarName, Maybe NExprLoc)]
pset

  -- Parameters named by an identifier on the right, or none (`{x, y} @ args`)
  atRight :: Parser (Params NExprLoc)
atRight =
    do
      ([(VarName, Maybe NExprLoc)]
pset, Variadic
variadic) <- Parser ([(VarName, Maybe NExprLoc)], Variadic)
params
      Maybe VarName
name             <- Parser VarName
-> ParsecT Void Text (State SourcePos) (Maybe VarName)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser VarName
 -> ParsecT Void Text (State SourcePos) (Maybe VarName))
-> Parser VarName
-> ParsecT Void Text (State SourcePos) (Maybe VarName)
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'@' ParsecT Void Text (State SourcePos) Char
-> Parser VarName -> Parser VarName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser VarName
identifier
      pure $ Maybe VarName
-> Variadic -> [(VarName, Maybe NExprLoc)] -> Params NExprLoc
forall r. Maybe VarName -> Variadic -> ParamSet r -> Params r
ParamSet Maybe VarName
name Variadic
variadic [(VarName, Maybe NExprLoc)]
pset

  -- Return the parameters set.
  params :: Parser ([(VarName, Maybe NExprLoc)], Variadic)
params = Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall a. Parser a -> Parser a
braces Parser ([(VarName, Maybe NExprLoc)], Variadic)
getParams

  -- Collects the parameters within curly braces. Returns the parameters and
  -- an flag indication if the parameters are variadic.
  getParams :: Parser ([(VarName, Maybe NExprLoc)], Variadic)
getParams = [(VarName, Maybe NExprLoc)]
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
go [(VarName, Maybe NExprLoc)]
forall a. Monoid a => a
mempty
   where
    -- Attempt to parse `...`. If this succeeds, stop and return True.
    -- Otherwise, attempt to parse an argument, optionally with a
    -- default. If this fails, then return what has been accumulated
    -- so far.
    go :: [(VarName, Maybe NExprLoc)]
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
go [(VarName, Maybe NExprLoc)]
acc = (([(VarName, Maybe NExprLoc)]
acc, Variadic
Variadic) ([(VarName, Maybe NExprLoc)], Variadic)
-> ParsecT Void Text (State SourcePos) Text
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Void Text (State SourcePos) Text
symbols Text
"...") Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser ([(VarName, Maybe NExprLoc)], Variadic)
getMore
     where
      getMore :: Parser ([(VarName, Maybe NExprLoc)], Variadic)
      getMore :: Parser ([(VarName, Maybe NExprLoc)], Variadic)
getMore =
        -- Could be nothing, in which just return what we have so far.
        ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option ([(VarName, Maybe NExprLoc)]
acc, Variadic
forall a. Monoid a => a
mempty) (Parser ([(VarName, Maybe NExprLoc)], Variadic)
 -> Parser ([(VarName, Maybe NExprLoc)], Variadic))
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall a b. (a -> b) -> a -> b
$
          do
            -- Get an argument name and an optional default.
            (VarName, Maybe NExprLoc)
pair <-
              (VarName -> Maybe NExprLoc -> (VarName, Maybe NExprLoc))
-> Parser VarName
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
-> ParsecT Void Text (State SourcePos) (VarName, Maybe NExprLoc)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,)
                Parser VarName
identifier
                (Parser NExprLoc
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser NExprLoc
 -> ParsecT Void Text (State SourcePos) (Maybe NExprLoc))
-> Parser NExprLoc
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
forall a b. (a -> b) -> a -> b
$ Char -> Parser NExprLoc
exprAfterSymbol Char
'?')

            let args :: [(VarName, Maybe NExprLoc)]
args = [(VarName, Maybe NExprLoc)]
acc [(VarName, Maybe NExprLoc)]
-> [(VarName, Maybe NExprLoc)] -> [(VarName, Maybe NExprLoc)]
forall a. Semigroup a => a -> a -> a
<> OneItem [(VarName, Maybe NExprLoc)] -> [(VarName, Maybe NExprLoc)]
forall x. One x => OneItem x -> x
one (VarName, Maybe NExprLoc)
OneItem [(VarName, Maybe NExprLoc)]
pair

            -- Either return this, or attempt to get a comma and restart.
            ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option ([(VarName, Maybe NExprLoc)]
args, Variadic
forall a. Monoid a => a
mempty) (Parser ([(VarName, Maybe NExprLoc)], Variadic)
 -> Parser ([(VarName, Maybe NExprLoc)], Variadic))
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
',' ParsecT Void Text (State SourcePos) Char
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [(VarName, Maybe NExprLoc)]
-> Parser ([(VarName, Maybe NExprLoc)], Variadic)
go [(VarName, Maybe NExprLoc)]
args

nixLambda :: Parser NExprLoc
nixLambda :: Parser NExprLoc
nixLambda =
  (AnnUnit SrcSpan (Params NExprLoc) -> NExprLoc -> NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (Params NExprLoc))
-> Parser NExprLoc
-> Parser NExprLoc
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 AnnUnit SrcSpan (Params NExprLoc) -> NExprLoc -> NExprLoc
annNAbs
    (Parser (Params NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (Params NExprLoc))
forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 (Parser (Params NExprLoc)
 -> ParsecT
      Void Text (State SourcePos) (AnnUnit SrcSpan (Params NExprLoc)))
-> Parser (Params NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (Params NExprLoc))
forall a b. (a -> b) -> a -> b
$ Parser (Params NExprLoc) -> Parser (Params NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser (Params NExprLoc)
argExpr)
    Parser NExprLoc
nixExpr


-- ** let expression

nixLet :: Parser NExprLoc
nixLet :: Parser NExprLoc
nixLet =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"let block" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    Text -> Parser ()
reserved Text
"let" Parser () -> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Parser (NExprF NExprLoc)
letBody Parser (NExprF NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (NExprF NExprLoc)
letBinders)
 where
  letBinders :: Parser (NExprF NExprLoc)
letBinders =
    ([Binding NExprLoc] -> NExprLoc -> NExprF NExprLoc)
-> Parser [Binding NExprLoc]
-> Parser NExprLoc
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 [Binding NExprLoc] -> NExprLoc -> NExprF NExprLoc
forall r. [Binding r] -> r -> NExprF r
NLet
      Parser [Binding NExprLoc]
nixBinders
      (Text -> Parser NExprLoc
exprAfterReservedWord Text
"in")
  -- Let expressions `let {..., body = ...}' are just desugared
  -- into `(rec {..., body = ...}).body'.
  letBody :: Parser (NExprF NExprLoc)
letBody    = (\NExprLoc
x -> Maybe NExprLoc -> NExprLoc -> NAttrPath NExprLoc -> NExprF NExprLoc
forall r. Maybe r -> r -> NAttrPath r -> NExprF r
NSelect Maybe NExprLoc
forall a. Maybe a
Nothing NExprLoc
x (OneItem (NAttrPath NExprLoc) -> NAttrPath NExprLoc
forall x. One x => OneItem x -> x
one (OneItem (NAttrPath NExprLoc) -> NAttrPath NExprLoc)
-> OneItem (NAttrPath NExprLoc) -> NAttrPath NExprLoc
forall a b. (a -> b) -> a -> b
$ VarName -> NKeyName NExprLoc
forall r. VarName -> NKeyName r
StaticKey VarName
"body")) (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NExprLoc
aset
  aset :: Parser NExprLoc
aset       = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Recursivity -> [Binding NExprLoc] -> NExprF NExprLoc
forall r. Recursivity -> [Binding r] -> NExprF r
NSet Recursivity
Recursive ([Binding NExprLoc] -> NExprF NExprLoc)
-> Parser [Binding NExprLoc] -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [Binding NExprLoc] -> Parser [Binding NExprLoc]
forall a. Parser a -> Parser a
braces Parser [Binding NExprLoc]
nixBinders

-- ** if then else

nixIf :: Parser NExprLoc
nixIf :: Parser NExprLoc
nixIf =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"if" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    (NExprLoc -> NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc
-> Parser NExprLoc
-> Parser NExprLoc
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 NExprLoc -> NExprLoc -> NExprLoc -> NExprF NExprLoc
forall r. r -> r -> r -> NExprF r
NIf
      (Text -> Parser ()
reserved Text
"if"   Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixExprAlgebra)
      (Text -> Parser NExprLoc
exprAfterReservedWord Text
"then")
      (Text -> Parser NExprLoc
exprAfterReservedWord Text
"else")

-- ** with

nixWith :: Parser NExprLoc
nixWith :: Parser NExprLoc
nixWith =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"with" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    (NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 NExprLoc -> NExprLoc -> NExprF NExprLoc
forall r. r -> r -> NExprF r
NWith
      (Text -> Parser NExprLoc
exprAfterReservedWord Text
"with")
      (Char -> Parser NExprLoc
exprAfterSymbol       Char
';'   )


-- ** assert

nixAssert :: Parser NExprLoc
nixAssert :: Parser NExprLoc
nixAssert =
  String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation String
"assert" (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$
    (NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 NExprLoc -> NExprLoc -> NExprF NExprLoc
forall r. r -> r -> NExprF r
NAssert
      (Text -> Parser NExprLoc
exprAfterReservedWord Text
"assert")
      (Char -> Parser NExprLoc
exprAfterSymbol       Char
';'     )

-- ** . - reference (selector) into attr

selDot :: Parser ()
selDot :: Parser ()
selDot = String -> Parser () -> Parser ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"." (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Char -> ParsecT Void Text (State SourcePos) Char
symbol Char
'.' ParsecT Void Text (State SourcePos) Char -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy Parser NExprLoc
nixPath)

keyName :: Parser (NKeyName NExprLoc)
keyName :: Parser (NKeyName NExprLoc)
keyName = Parser (NKeyName NExprLoc)
dynamicKey Parser (NKeyName NExprLoc)
-> Parser (NKeyName NExprLoc) -> Parser (NKeyName NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (NKeyName NExprLoc)
forall r. ParsecT Void Text (State SourcePos) (NKeyName r)
staticKey
 where
  staticKey :: ParsecT Void Text (State SourcePos) (NKeyName r)
staticKey  = VarName -> NKeyName r
forall r. VarName -> NKeyName r
StaticKey (VarName -> NKeyName r)
-> Parser VarName
-> ParsecT Void Text (State SourcePos) (NKeyName r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser VarName
identifier
  dynamicKey :: Parser (NKeyName NExprLoc)
dynamicKey = Antiquoted (NString NExprLoc) NExprLoc -> NKeyName NExprLoc
forall r. Antiquoted (NString r) r -> NKeyName r
DynamicKey (Antiquoted (NString NExprLoc) NExprLoc -> NKeyName NExprLoc)
-> ParsecT
     Void
     Text
     (State SourcePos)
     (Antiquoted (NString NExprLoc) NExprLoc)
-> Parser (NKeyName NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (NString NExprLoc)
-> ParsecT
     Void
     Text
     (State SourcePos)
     (Antiquoted (NString NExprLoc) NExprLoc)
forall a. Parser a -> Parser (Antiquoted a NExprLoc)
nixAntiquoted Parser (NString NExprLoc)
nixString'

nixSelector :: Parser (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector :: ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector =
  ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 (ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
 -> ParsecT
      Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc)))
-> ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
forall a b. (a -> b) -> a -> b
$
    do
      (NKeyName NExprLoc
x : [NKeyName NExprLoc]
xs) <- Parser (NKeyName NExprLoc)
keyName Parser (NKeyName NExprLoc)
-> Parser ()
-> ParsecT Void Text (State SourcePos) [NKeyName NExprLoc]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy1` Parser ()
selDot
      NAttrPath NExprLoc
-> ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NAttrPath NExprLoc
 -> ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc))
-> NAttrPath NExprLoc
-> ParsecT Void Text (State SourcePos) (NAttrPath NExprLoc)
forall a b. (a -> b) -> a -> b
$ NKeyName NExprLoc
x NKeyName NExprLoc -> [NKeyName NExprLoc] -> NAttrPath NExprLoc
forall a. a -> [a] -> NonEmpty a
:| [NKeyName NExprLoc]
xs

nixSelect :: Parser NExprLoc -> Parser NExprLoc
nixSelect :: Parser NExprLoc -> Parser NExprLoc
nixSelect Parser NExprLoc
term =
  do
    NExprLoc
res <-
      (NExprLoc
 -> Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
 -> NExprLoc)
-> Parser NExprLoc
-> ParsecT
     Void
     Text
     (State SourcePos)
     (Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
-> Parser NExprLoc
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 NExprLoc
-> Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> NExprLoc
build
        Parser NExprLoc
term
        (ParsecT
  Void
  Text
  (State SourcePos)
  (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> ParsecT
     Void
     Text
     (State SourcePos)
     (Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT
   Void
   Text
   (State SourcePos)
   (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
 -> ParsecT
      Void
      Text
      (State SourcePos)
      (Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)))
-> ParsecT
     Void
     Text
     (State SourcePos)
     (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> ParsecT
     Void
     Text
     (State SourcePos)
     (Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
forall a b. (a -> b) -> a -> b
$
          (AnnUnit SrcSpan (NAttrPath NExprLoc)
 -> Maybe NExprLoc
 -> (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
-> ParsecT
     Void
     Text
     (State SourcePos)
     (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,)
            (Parser ()
selDot Parser ()
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> ParsecT
     Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector)
            (Parser NExprLoc
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser NExprLoc
 -> ParsecT Void Text (State SourcePos) (Maybe NExprLoc))
-> Parser NExprLoc
-> ParsecT Void Text (State SourcePos) (Maybe NExprLoc)
forall a b. (a -> b) -> a -> b
$ Text -> Parser ()
reserved Text
"or" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixTerm)
        )
    Maybe ()
continues <- Parser () -> ParsecT Void Text (State SourcePos) (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser () -> ParsecT Void Text (State SourcePos) (Maybe ()))
-> Parser () -> ParsecT Void Text (State SourcePos) (Maybe ())
forall a b. (a -> b) -> a -> b
$ Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead Parser ()
selDot

    (Parser NExprLoc -> Parser NExprLoc)
-> (() -> Parser NExprLoc -> Parser NExprLoc)
-> Maybe ()
-> Parser NExprLoc
-> Parser NExprLoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      Parser NExprLoc -> Parser NExprLoc
forall a. a -> a
id
      ((Parser NExprLoc -> Parser NExprLoc)
-> () -> Parser NExprLoc -> Parser NExprLoc
forall a b. a -> b -> a
const Parser NExprLoc -> Parser NExprLoc
nixSelect)
      Maybe ()
continues
      (NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a. Applicative f => a -> f a
pure NExprLoc
res)
 where
  build
    :: NExprLoc
    -> Maybe
      ( AnnUnit SrcSpan (NAttrPath NExprLoc)
      , Maybe NExprLoc
      )
    -> NExprLoc
  build :: NExprLoc
-> Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> NExprLoc
build NExprLoc
t =
    NExprLoc
-> ((AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
    -> NExprLoc)
-> Maybe (AnnUnit SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> NExprLoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      NExprLoc
t
      (\ (AnnUnit SrcSpan (NAttrPath NExprLoc)
a, Maybe NExprLoc
m) -> (Maybe NExprLoc
-> NExprLoc -> AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc
`annNSelect` NExprLoc
t) Maybe NExprLoc
m AnnUnit SrcSpan (NAttrPath NExprLoc)
a)


-- ** _ - syntax hole

nixSynHole :: Parser NExprLoc
nixSynHole :: Parser NExprLoc
nixSynHole = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Text -> NExprF NExprLoc
forall a. Text -> NExprF a
mkSynHoleF (Text -> NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) Text
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser VarName -> ParsecT Void Text (State SourcePos) Text
coerce (Token Text -> ParsecT Void Text (State SourcePos) (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'^' ParsecT Void Text (State SourcePos) Char
-> Parser VarName -> Parser VarName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser VarName
identifier)


-- ** Expr & its constituents (Language term, expr algebra)

nixTerm :: Parser NExprLoc
nixTerm :: Parser NExprLoc
nixTerm =
  do
    Char
c <- ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> ((Char -> Bool) -> ParsecT Void Text (State SourcePos) Char)
-> (Char -> Bool)
-> ParsecT Void Text (State SourcePos) Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Void Text (State SourcePos) Char
-> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (ParsecT Void Text (State SourcePos) Char
 -> ParsecT Void Text (State SourcePos) Char)
-> ((Char -> Bool) -> ParsecT Void Text (State SourcePos) Char)
-> (Char -> Bool)
-> ParsecT Void Text (State SourcePos) Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ParsecT Void Text (State SourcePos) Char
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy ((Char -> Bool) -> ParsecT Void Text (State SourcePos) Char)
-> (Char -> Bool) -> ParsecT Void Text (State SourcePos) Char
forall a b. (a -> b) -> a -> b
$
      \Char
x -> (Char -> String -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` (String
"({[</\"'^" :: String)) Char
x Bool -> Bool -> Bool
|| Char -> Bool
pathChar Char
x
    case Char
c of
      Char
'('  -> Parser NExprLoc -> Parser NExprLoc
nixSelect Parser NExprLoc
nixParens
      Char
'{'  -> Parser NExprLoc -> Parser NExprLoc
nixSelect Parser NExprLoc
nixSet
      Char
'['  -> Parser NExprLoc
nixList
      Char
'<'  -> Parser NExprLoc
nixSearchPath
      Char
'/'  -> Parser NExprLoc
nixPath
      Char
'"'  -> Parser NExprLoc
nixString
      Char
'\'' -> Parser NExprLoc
nixString
      Char
'^'  -> Parser NExprLoc
nixSynHole
      Char
_ ->
        [Parser NExprLoc] -> Parser NExprLoc
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
          ([Parser NExprLoc] -> Parser NExprLoc)
-> [Parser NExprLoc] -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$  [ Parser NExprLoc -> Parser NExprLoc
nixSelect Parser NExprLoc
nixSet | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'r' ]
          [Parser NExprLoc] -> [Parser NExprLoc] -> [Parser NExprLoc]
forall a. Semigroup a => a -> a -> a
<> [ Parser NExprLoc
nixPath | Char -> Bool
pathChar Char
c ]
          [Parser NExprLoc] -> [Parser NExprLoc] -> [Parser NExprLoc]
forall a. Semigroup a => a -> a -> a
<> if Char -> Bool
isDigit Char
c
              then [ Parser NExprLoc
nixFloat, Parser NExprLoc
nixInt ]
              else
                [ Parser NExprLoc
nixUri | Char -> Bool
isAlpha Char
c ]
                [Parser NExprLoc] -> [Parser NExprLoc] -> [Parser NExprLoc]
forall a. Semigroup a => a -> a -> a
<> [ Parser NExprLoc
nixBool | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
't' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'f' ]
                [Parser NExprLoc] -> [Parser NExprLoc] -> [Parser NExprLoc]
forall a. Semigroup a => a -> a -> a
<> [ Parser NExprLoc
nixNull | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'n' ]
                [Parser NExprLoc] -> [Parser NExprLoc] -> [Parser NExprLoc]
forall a. Semigroup a => a -> a -> a
<> OneItem [Parser NExprLoc] -> [Parser NExprLoc]
forall x. One x => OneItem x -> x
one (Parser NExprLoc -> Parser NExprLoc
nixSelect Parser NExprLoc
nixSym)

-- | Nix expression algebra parser.
-- "Expression algebra" is to explain @megaparsec@ use of the term "Expression" (parser for language algebraic coperators without any statements (without @let@ etc.)), which is essentially an algebra inside the language.
nixExprAlgebra :: Parser NExprLoc
nixExprAlgebra :: Parser NExprLoc
nixExprAlgebra =
  Parser NExprLoc -> [[Operator Parser NExprLoc]] -> Parser NExprLoc
forall (m :: * -> *) a.
MonadPlus m =>
m a -> [[Operator m a]] -> m a
makeExprParser
    Parser NExprLoc
nixTerm
    ((NOperatorDef, Operator Parser NExprLoc)
-> Operator Parser NExprLoc
forall a b. (a, b) -> b
snd ((NOperatorDef, Operator Parser NExprLoc)
 -> Operator Parser NExprLoc)
-> [[(NOperatorDef, Operator Parser NExprLoc)]]
-> [[Operator Parser NExprLoc]]
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> f (g a) -> f (g b)
<<$>>
      ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef, Operator Parser NExprLoc)]]
nixOperators ParsecT
  Void Text (State SourcePos) (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector
    )

nixExpr :: Parser NExprLoc
nixExpr :: Parser NExprLoc
nixExpr = Parser NExprLoc
keywords Parser NExprLoc -> Parser NExprLoc -> Parser NExprLoc
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser NExprLoc
nixLambda Parser NExprLoc -> Parser NExprLoc -> Parser NExprLoc
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser NExprLoc
nixExprAlgebra
 where
  keywords :: Parser NExprLoc
keywords = Parser NExprLoc
nixLet Parser NExprLoc -> Parser NExprLoc -> Parser NExprLoc
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser NExprLoc
nixIf Parser NExprLoc -> Parser NExprLoc -> Parser NExprLoc
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser NExprLoc
nixAssert Parser NExprLoc -> Parser NExprLoc -> Parser NExprLoc
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser NExprLoc
nixWith


-- * Parse

type Result a = Either (Doc Void) a

parseFromFileEx :: MonadFile m => Parser a -> Path -> m (Result a)
parseFromFileEx :: Parser a -> Path -> m (Result a)
parseFromFileEx Parser a
parser Path
file =
  do
    Text
input <- IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Path -> IO Text
readFile Path
file

    pure $
      (ParseErrorBundle Text Void -> Result a)
-> (a -> Result a)
-> Either (ParseErrorBundle Text Void) a
-> Result a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
        (Doc Void -> Result a
forall a b. a -> Either a b
Left (Doc Void -> Result a)
-> (ParseErrorBundle Text Void -> Doc Void)
-> ParseErrorBundle Text Void
-> Result a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc Void
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc Void)
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> Doc Void
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty)
        a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
        (Either (ParseErrorBundle Text Void) a -> Result a)
-> Either (ParseErrorBundle Text Void) a -> Result a
forall a b. (a -> b) -> a -> b
$ (State SourcePos (Either (ParseErrorBundle Text Void) a)
-> SourcePos -> Either (ParseErrorBundle Text Void) a
forall s a. State s a -> s -> a
`evalState` String -> SourcePos
initialPos (Path -> String
coerce Path
file)) (State SourcePos (Either (ParseErrorBundle Text Void) a)
 -> Either (ParseErrorBundle Text Void) a)
-> State SourcePos (Either (ParseErrorBundle Text Void) a)
-> Either (ParseErrorBundle Text Void) a
forall a b. (a -> b) -> a -> b
$ Parser a
-> String
-> Text
-> State SourcePos (Either (ParseErrorBundle Text Void) a)
forall (m :: * -> *) e s a.
Monad m =>
ParsecT e s m a
-> String -> s -> m (Either (ParseErrorBundle s e) a)
runParserT Parser a
parser (Path -> String
coerce Path
file) Text
input

parseFromText :: Parser a -> Text -> Result a
parseFromText :: Parser a -> Text -> Result a
parseFromText Parser a
parser Text
input =
  let stub :: String
stub = String
"<string>" in
  (ParseErrorBundle Text Void -> Result a)
-> (a -> Result a)
-> Either (ParseErrorBundle Text Void) a
-> Result a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
    (Doc Void -> Result a
forall a b. a -> Either a b
Left (Doc Void -> Result a)
-> (ParseErrorBundle Text Void -> Doc Void)
-> ParseErrorBundle Text Void
-> Result a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc Void
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc Void)
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> Doc Void
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty)
    a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    (Either (ParseErrorBundle Text Void) a -> Result a)
-> Either (ParseErrorBundle Text Void) a -> Result a
forall a b. (a -> b) -> a -> b
$ (State SourcePos (Either (ParseErrorBundle Text Void) a)
-> SourcePos -> Either (ParseErrorBundle Text Void) a
forall s a. State s a -> s -> a
`evalState` String -> SourcePos
initialPos String
stub) (State SourcePos (Either (ParseErrorBundle Text Void) a)
 -> Either (ParseErrorBundle Text Void) a)
-> State SourcePos (Either (ParseErrorBundle Text Void) a)
-> Either (ParseErrorBundle Text Void) a
forall a b. (a -> b) -> a -> b
$ (Parser a
-> String
-> Text
-> State SourcePos (Either (ParseErrorBundle Text Void) a)
forall (m :: * -> *) e s a.
Monad m =>
ParsecT e s m a
-> String -> s -> m (Either (ParseErrorBundle s e) a)
`runParserT` String
stub) Parser a
parser Text
input

fullContent :: Parser NExprLoc
fullContent :: Parser NExprLoc
fullContent = Parser ()
whiteSpace Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixExpr Parser NExprLoc -> Parser () -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof

parseNixFile' :: MonadFile m => (Parser NExprLoc -> Parser a) -> Path -> m (Result a)
parseNixFile' :: (Parser NExprLoc -> Parser a) -> Path -> m (Result a)
parseNixFile' Parser NExprLoc -> Parser a
f =
  Parser a -> Path -> m (Result a)
forall (m :: * -> *) a.
MonadFile m =>
Parser a -> Path -> m (Result a)
parseFromFileEx (Parser a -> Path -> m (Result a))
-> Parser a -> Path -> m (Result a)
forall a b. (a -> b) -> a -> b
$ Parser NExprLoc -> Parser a
f Parser NExprLoc
fullContent

parseNixFile :: MonadFile m => Path -> m (Result NExpr)
parseNixFile :: Path -> m (Result NExpr)
parseNixFile =
  (Parser NExprLoc -> Parser NExpr) -> Path -> m (Result NExpr)
forall (m :: * -> *) a.
MonadFile m =>
(Parser NExprLoc -> Parser a) -> Path -> m (Result a)
parseNixFile' (NExprLoc -> NExpr
forall (f :: * -> *) ann. Functor f => Ann ann f -> Fix f
stripAnnotation (NExprLoc -> NExpr) -> Parser NExprLoc -> Parser NExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)

parseNixFileLoc :: MonadFile m => Path -> m (Result NExprLoc)
parseNixFileLoc :: Path -> m (Result NExprLoc)
parseNixFileLoc =
  (Parser NExprLoc -> Parser NExprLoc) -> Path -> m (Result NExprLoc)
forall (m :: * -> *) a.
MonadFile m =>
(Parser NExprLoc -> Parser a) -> Path -> m (Result a)
parseNixFile' Parser NExprLoc -> Parser NExprLoc
forall a. a -> a
id

parseNixText' :: (Parser NExprLoc -> Parser a) -> Text -> Result a
parseNixText' :: (Parser NExprLoc -> Parser a) -> Text -> Result a
parseNixText' Parser NExprLoc -> Parser a
f =
  Parser a -> Text -> Result a
forall a. Parser a -> Text -> Result a
parseFromText (Parser a -> Text -> Result a) -> Parser a -> Text -> Result a
forall a b. (a -> b) -> a -> b
$ Parser NExprLoc -> Parser a
f Parser NExprLoc
fullContent

parseNixText :: Text -> Result NExpr
parseNixText :: Text -> Result NExpr
parseNixText =
  (Parser NExprLoc -> Parser NExpr) -> Text -> Result NExpr
forall a. (Parser NExprLoc -> Parser a) -> Text -> Result a
parseNixText' (NExprLoc -> NExpr
forall (f :: * -> *) ann. Functor f => Ann ann f -> Fix f
stripAnnotation (NExprLoc -> NExpr) -> Parser NExprLoc -> Parser NExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)

parseNixTextLoc :: Text -> Result NExprLoc
parseNixTextLoc :: Text -> Result NExprLoc
parseNixTextLoc =
  (Parser NExprLoc -> Parser NExprLoc) -> Text -> Result NExprLoc
forall a. (Parser NExprLoc -> Parser a) -> Text -> Result a
parseNixText' Parser NExprLoc -> Parser NExprLoc
forall a. a -> a
id

parseExpr :: (MonadFail m) => Text -> m NExpr
parseExpr :: Text -> m NExpr
parseExpr =
  (Doc Void -> m NExpr)
-> (NExpr -> m NExpr) -> Result NExpr -> m NExpr
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
    (String -> m NExpr
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m NExpr) -> (Doc Void -> String) -> Doc Void -> m NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Void -> String
forall b a. (Show a, IsString b) => a -> b
show)
    NExpr -> m NExpr
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    (Result NExpr -> m NExpr)
-> (Text -> Result NExpr) -> Text -> m NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Result NExpr
parseNixText