{-# 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
  , NAssoc(..)
  , NOpPrecedence(..)
  , NOpName(..)
  , NSpecialOp(..)
  , NOperatorDef(..)
  , nixExpr
  , nixExprAlgebra
  , nixSet
  , nixBinders
  , nixSelector
  , nixSym
  , nixPath
  , nixString
  , nixUri
  , nixSearchPath
  , nixFloat
  , nixInt
  , nixBool
  , nixNull
  , whiteSpace

  --  2022-01-26: NOTE: Try to hide it after OperatorInfo is removed
  , NOp(..)
  , appOpDef
  )
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.List.Extra                ( groupSort )
import           Data.Fix                       ( Fix(..) )
import qualified Data.HashSet                  as HashSet
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 #-}

-- | Alternative "<|>" with additional preservation of 'MonadPlus' constraint.
infixl 3 <|>
(<|>) :: MonadPlus m => m a -> m a -> m a
<|> :: forall (m :: * -> *) a. MonadPlus m => 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 :: forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 Parser a
p =
  do
    SourcePos
begin <- forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
    a
res   <- Parser a
p
    SourcePos
end   <- forall s (m :: * -> *). MonadState s m => m s
get -- The state set before the last whitespace

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

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

annotateNamedLocation :: String -> Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateNamedLocation :: String
-> Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateNamedLocation String
name = Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateLocation forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 =
  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
|| (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 =
  forall a. Parser a -> Parser a
lexeme forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Text
n forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
reservedEnd) forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)

exprAfterSymbol :: Char -> Parser NExprLoc
exprAfterSymbol :: Char -> ParsecT Void Text (State SourcePos) NExprLoc
exprAfterSymbol Char
p = Char -> Parser Char
symbol Char
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text (State SourcePos) NExprLoc
nixExpr

exprAfterReservedWord :: Text -> Parser NExprLoc
exprAfterReservedWord :: Text -> ParsecT Void Text (State SourcePos) NExprLoc
exprAfterReservedWord Text
word = Text -> Parser ()
reserved Text
word forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text (State SourcePos) NExprLoc
nixExpr

-- | 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 =
  forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Tokens Text
prefix forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"character") forall a b. (a -> b) -> a -> b
$ \Token Text
x -> Token Text
x forall a. Eq a => a -> a -> Bool
/= Char
'\n' Bool -> Bool -> Bool
&& Token Text
x forall a. Eq a => a -> a -> Bool
/= Char
'\r')

whiteSpace :: Parser ()
whiteSpace :: Parser ()
whiteSpace =
  do
    forall s (m :: * -> *). MonadState s m => s -> m ()
put forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
    forall e s (m :: * -> *).
MonadParsec e s m =>
m () -> m () -> m () -> m ()
Lexer.space 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' Text
"#"
  blockCmnt :: Parser ()
blockCmnt = forall e s (m :: * -> *).
MonadParsec e s m =>
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 :: forall a. Parser a -> Parser a
lexeme Parser a
p = Parser a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
whiteSpace

symbol :: Char -> Parser Char
symbol :: Char -> Parser Char
symbol = forall a. Parser a -> Parser a
lexeme forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = forall a. Parser a -> Parser a
lexeme forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 :: forall f. Parser (NExprF f) -> Parser (NExprF f)
parens   = forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between Char -> Parser Char
symbol Char
'(' Char
')'

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

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

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

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

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

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

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

-- * Parser parts

-- ** Constrants

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

nixBool :: Parser NExprLoc
nixBool :: ParsecT Void Text (State SourcePos) NExprLoc
nixBool =
  String
-> Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateNamedLocation String
"bool" forall a b. (a -> b) -> a -> b
$
    forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
(<|>) 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) = forall a. Bool -> NExprF a
mkBoolF Bool
b forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser ()
reserved Text
txt

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

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

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

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

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


-- ** Strings

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

escapeCode :: Parser Char
escapeCode :: Parser Char
escapeCode =
  forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
    [ Char
c forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
e | (Char
c, Char
e) <- [(Char, Char)]
escapeCodes ]
  forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> 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 =
  forall v. Parser (Antiquoted v NExprLoc)
antiquoted
  forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> forall v r. v -> Antiquoted v r
Plain forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. One x => OneItem x -> x
one forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'$'
  forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (Antiquoted Text NExprLoc)
esc
  forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> forall v r. v -> Antiquoted v r
Plain forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some Parser Char
plainChar
  where
  plainChar :: Parser Char
  plainChar :: Parser Char
plainChar =
    forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Parser ()
end forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'$') forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser ()
escStart) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle

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

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

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


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

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

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

  -- | Symbol "''"
  indentedQuotationMark :: Parser ()
  indentedQuotationMark :: Parser ()
indentedQuotationMark = forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"\"''\"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ 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' = forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"string" forall a b. (a -> b) -> a -> b
$ forall a. Parser a -> Parser a
lexeme forall a b. (a -> b) -> a -> b
$ Parser (NString NExprLoc)
doubleQuoted forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (NString NExprLoc)
indented

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


-- ** Names (variables aka symbols)

identifier :: Parser VarName
identifier :: Parser VarName
identifier =
  forall a. Parser a -> Parser a
lexeme forall a b. (a -> b) -> a -> b
$
    forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$
      do
        (coerce :: forall a b. Coercible a b => a -> b
coerce -> VarName
iD) <-
          forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Char -> Text -> Text
Text.cons
            (forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy (\Token Text
x -> Char -> Bool
isAlpha Token Text
x Bool -> Bool -> Bool
|| Token Text
x forall a. Eq a => a -> a -> Bool
== Char
'_'))
            (forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP forall a. Monoid a => a
mempty Char -> Bool
identLetter)
        forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ VarName
iD 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 forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
x forall a. Eq a => a -> a -> Bool
== Char
'\'' Bool -> Bool -> Bool
|| Char
x forall a. Eq a => a -> a -> Bool
== Char
'-'

nixSym :: Parser NExprLoc
nixSym :: ParsecT Void Text (State SourcePos) NExprLoc
nixSym = Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateLocation forall a b. (a -> b) -> a -> b
$ forall a. Text -> NExprF a
mkSymF forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> coerce :: forall a b. Coercible a b => a -> b
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 :: ParsecT Void Text (State SourcePos) NExprLoc
nixParens =
  String
-> Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateNamedLocation String
"parens" forall a b. (a -> b) -> a -> b
$
    forall f. Parser (NExprF f) -> Parser (NExprF f)
parens forall a b. (a -> b) -> a -> b
$ forall ann (f :: * -> *) r. AnnF ann f r -> f r
stripAnnF forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Fix f -> f (Fix f)
unFix forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text (State SourcePos) NExprLoc
nixExpr


-- ** [ ] list

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


-- ** { } set

nixBinders :: Parser [Binding NExprLoc]
nixBinders :: Parser [Binding NExprLoc]
nixBinders = (ParsecT Void Text (State SourcePos) (Binding NExprLoc)
inherit forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> ParsecT Void Text (State SourcePos) (Binding NExprLoc)
namedVar) forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`endBy` Char -> Parser 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.
      forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Tokens Text
"inherit" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
reservedEnd)
      SourcePos
p <- forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
      Maybe NExprLoc
x <- Parser ()
whiteSpace forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text (State SourcePos) NExprLoc
scope
      forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"inherited binding" forall a b. (a -> b) -> a -> b
$
        forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (forall r. Maybe r -> [VarName] -> NSourcePos -> Binding r
Inherit Maybe NExprLoc
x)
          (forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many Parser VarName
identifier)
          (forall (f :: * -> *) a. Applicative f => a -> f a
pure (SourcePos -> NSourcePos
toNSourcePos SourcePos
p))
  namedVar :: ParsecT Void Text (State SourcePos) (Binding NExprLoc)
namedVar =
    do
      SourcePos
p <- forall s e (m :: * -> *).
(TraversableStream s, MonadParsec e s m) =>
m SourcePos
getSourcePos
      forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"variable binding" forall a b. (a -> b) -> a -> b
$
        forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 forall r. NAttrPath r -> r -> NSourcePos -> Binding r
NamedVar
          (forall ann expr. AnnUnit ann expr -> expr
annotated forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector)
          (Char -> ParsecT Void Text (State SourcePos) NExprLoc
exprAfterSymbol Char
'=')
          (forall (f :: * -> *) a. Applicative f => a -> f a
pure (SourcePos -> NSourcePos
toNSourcePos SourcePos
p))
  scope :: ParsecT Void Text (State SourcePos) NExprLoc
scope = forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"inherit scope" ParsecT Void Text (State SourcePos) NExprLoc
nixParens

nixSet :: Parser NExprLoc
nixSet :: ParsecT Void Text (State SourcePos) NExprLoc
nixSet =
  String
-> Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateNamedLocation String
"set" forall a b. (a -> b) -> a -> b
$
    forall {r}.
ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
isRec forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Parser a -> Parser a
braces Parser [Binding NExprLoc]
nixBinders
 where
  isRec :: ParsecT Void Text (State SourcePos) ([Binding r] -> NExprF r)
isRec =
    forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"recursive set" (Text -> Parser ()
reserved Text
"rec" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall r. Recursivity -> [Binding r] -> NExprF r
NSet Recursivity
Recursive)
    forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall r. Recursivity -> [Binding r] -> NExprF r
NSet 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
|| (forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` (String
"._-+~" :: String)) Char
x

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

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

nixPath :: Parser NExprLoc
nixPath :: ParsecT Void Text (State SourcePos) NExprLoc
nixPath =
  String
-> Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateNamedLocation String
"path" forall a b. (a -> b) -> a -> b
$
    forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall a. Bool -> String -> NExprF a
mkPathF Bool
False forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> coerce :: forall a b. Coercible a b => a -> b
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 :: ParsecT Void Text (State SourcePos) NExprLoc
nixSearchPath =
  String
-> Parser (NExprF NExprLoc)
-> ParsecT Void Text (State SourcePos) NExprLoc
annotateNamedLocation String
"spath" forall a b. (a -> b) -> a -> b
$
    forall a. Bool -> String -> NExprF a
mkPathF Bool
True forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (forall a. Parser a -> Parser a
lexeme forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'<' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
pathChar forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser Char
slash) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'>')


-- ** Operators

--  2022-01-26: NOTE: Rename to 'literal'
newtype NOpName = NOpName Text
  deriving
    (NOpName -> NOpName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NOpName -> NOpName -> Bool
$c/= :: NOpName -> NOpName -> Bool
== :: NOpName -> NOpName -> Bool
$c== :: NOpName -> NOpName -> Bool
Eq, Eq NOpName
NOpName -> NOpName -> Bool
NOpName -> NOpName -> Ordering
NOpName -> NOpName -> NOpName
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 :: NOpName -> NOpName -> NOpName
$cmin :: NOpName -> NOpName -> NOpName
max :: NOpName -> NOpName -> NOpName
$cmax :: NOpName -> NOpName -> NOpName
>= :: NOpName -> NOpName -> Bool
$c>= :: NOpName -> NOpName -> Bool
> :: NOpName -> NOpName -> Bool
$c> :: NOpName -> NOpName -> Bool
<= :: NOpName -> NOpName -> Bool
$c<= :: NOpName -> NOpName -> Bool
< :: NOpName -> NOpName -> Bool
$c< :: NOpName -> NOpName -> Bool
compare :: NOpName -> NOpName -> Ordering
$ccompare :: NOpName -> NOpName -> Ordering
Ord, forall x. Rep NOpName x -> NOpName
forall x. NOpName -> Rep NOpName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NOpName x -> NOpName
$cfrom :: forall x. NOpName -> Rep NOpName x
Generic, Typeable, Typeable NOpName
NOpName -> DataType
NOpName -> Constr
(forall b. Data b => b -> b) -> NOpName -> NOpName
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) -> NOpName -> u
forall u. (forall d. Data d => d -> u) -> NOpName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOpName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOpName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOpName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOpName -> c NOpName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOpName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NOpName)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOpName -> m NOpName
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NOpName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NOpName -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NOpName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NOpName -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOpName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOpName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOpName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOpName -> r
gmapT :: (forall b. Data b => b -> b) -> NOpName -> NOpName
$cgmapT :: (forall b. Data b => b -> b) -> NOpName -> NOpName
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NOpName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NOpName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOpName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOpName)
dataTypeOf :: NOpName -> DataType
$cdataTypeOf :: NOpName -> DataType
toConstr :: NOpName -> Constr
$ctoConstr :: NOpName -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOpName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOpName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOpName -> c NOpName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOpName -> c NOpName
Data, Int -> NOpName -> ShowS
[NOpName] -> ShowS
NOpName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NOpName] -> ShowS
$cshowList :: [NOpName] -> ShowS
show :: NOpName -> String
$cshow :: NOpName -> String
showsPrec :: Int -> NOpName -> ShowS
$cshowsPrec :: Int -> NOpName -> ShowS
Show, NOpName -> ()
forall a. (a -> ()) -> NFData a
rnf :: NOpName -> ()
$crnf :: NOpName -> ()
NFData)

instance IsString NOpName where
  fromString :: String -> NOpName
fromString = coerce :: forall a b. Coercible a b => a -> b
coerce forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString @Text

instance ToString NOpName where
  toString :: NOpName -> String
toString = forall a. ToString a => a -> String
toString @Text forall b c a. (b -> c) -> (a -> b) -> a -> c
. coerce :: forall a b. Coercible a b => a -> b
coerce

operator :: NOpName -> Parser Text
operator :: NOpName -> ParsecT Void Text (State SourcePos) Text
operator (coerce :: forall a b. Coercible a b => a -> b
coerce -> 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 =
    forall a. Parser a -> Parser a
lexeme forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
chunk Text
opChar forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
noNextChar)

opWithLoc :: (AnnUnit SrcSpan o -> a) -> o -> NOpName -> Parser a
opWithLoc :: forall o a. (AnnUnit SrcSpan o -> a) -> o -> NOpName -> Parser a
opWithLoc AnnUnit SrcSpan o -> a
f o
op NOpName
name = AnnUnit SrcSpan o -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. (o
op forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 (NOpName -> ParsecT Void Text (State SourcePos) Text
operator NOpName
name)

--  2022-01-26: NOTE: Make presedence free and type safe by moving it into type level:
--  https://youtu.be/qaPdg0mZavM?t=1757
--  https://wiki.haskell.org/The_Monad.Reader/Issue5/Number_Param_Types
newtype NOpPrecedence = NOpPrecedence Int
  deriving (NOpPrecedence -> NOpPrecedence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NOpPrecedence -> NOpPrecedence -> Bool
$c/= :: NOpPrecedence -> NOpPrecedence -> Bool
== :: NOpPrecedence -> NOpPrecedence -> Bool
$c== :: NOpPrecedence -> NOpPrecedence -> Bool
Eq, Eq NOpPrecedence
NOpPrecedence -> NOpPrecedence -> Bool
NOpPrecedence -> NOpPrecedence -> Ordering
NOpPrecedence -> NOpPrecedence -> NOpPrecedence
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 :: NOpPrecedence -> NOpPrecedence -> NOpPrecedence
$cmin :: NOpPrecedence -> NOpPrecedence -> NOpPrecedence
max :: NOpPrecedence -> NOpPrecedence -> NOpPrecedence
$cmax :: NOpPrecedence -> NOpPrecedence -> NOpPrecedence
>= :: NOpPrecedence -> NOpPrecedence -> Bool
$c>= :: NOpPrecedence -> NOpPrecedence -> Bool
> :: NOpPrecedence -> NOpPrecedence -> Bool
$c> :: NOpPrecedence -> NOpPrecedence -> Bool
<= :: NOpPrecedence -> NOpPrecedence -> Bool
$c<= :: NOpPrecedence -> NOpPrecedence -> Bool
< :: NOpPrecedence -> NOpPrecedence -> Bool
$c< :: NOpPrecedence -> NOpPrecedence -> Bool
compare :: NOpPrecedence -> NOpPrecedence -> Ordering
$ccompare :: NOpPrecedence -> NOpPrecedence -> Ordering
Ord, forall x. Rep NOpPrecedence x -> NOpPrecedence
forall x. NOpPrecedence -> Rep NOpPrecedence x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NOpPrecedence x -> NOpPrecedence
$cfrom :: forall x. NOpPrecedence -> Rep NOpPrecedence x
Generic, NOpPrecedence
forall a. a -> a -> Bounded a
maxBound :: NOpPrecedence
$cmaxBound :: NOpPrecedence
minBound :: NOpPrecedence
$cminBound :: NOpPrecedence
Bounded, Typeable, Typeable NOpPrecedence
NOpPrecedence -> DataType
NOpPrecedence -> Constr
(forall b. Data b => b -> b) -> NOpPrecedence -> NOpPrecedence
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) -> NOpPrecedence -> u
forall u. (forall d. Data d => d -> u) -> NOpPrecedence -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOpPrecedence -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOpPrecedence -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOpPrecedence
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOpPrecedence -> c NOpPrecedence
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOpPrecedence)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NOpPrecedence)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NOpPrecedence -> m NOpPrecedence
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NOpPrecedence -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NOpPrecedence -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NOpPrecedence -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NOpPrecedence -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOpPrecedence -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NOpPrecedence -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOpPrecedence -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NOpPrecedence -> r
gmapT :: (forall b. Data b => b -> b) -> NOpPrecedence -> NOpPrecedence
$cgmapT :: (forall b. Data b => b -> b) -> NOpPrecedence -> NOpPrecedence
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NOpPrecedence)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NOpPrecedence)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOpPrecedence)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NOpPrecedence)
dataTypeOf :: NOpPrecedence -> DataType
$cdataTypeOf :: NOpPrecedence -> DataType
toConstr :: NOpPrecedence -> Constr
$ctoConstr :: NOpPrecedence -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOpPrecedence
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NOpPrecedence
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOpPrecedence -> c NOpPrecedence
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NOpPrecedence -> c NOpPrecedence
Data, Int -> NOpPrecedence -> ShowS
[NOpPrecedence] -> ShowS
NOpPrecedence -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NOpPrecedence] -> ShowS
$cshowList :: [NOpPrecedence] -> ShowS
show :: NOpPrecedence -> String
$cshow :: NOpPrecedence -> String
showsPrec :: Int -> NOpPrecedence -> ShowS
$cshowsPrec :: Int -> NOpPrecedence -> ShowS
Show, NOpPrecedence -> ()
forall a. (a -> ()) -> NFData a
rnf :: NOpPrecedence -> ()
$crnf :: NOpPrecedence -> ()
NFData)

instance Enum NOpPrecedence where
  toEnum :: Int -> NOpPrecedence
toEnum = coerce :: forall a b. Coercible a b => a -> b
coerce
  fromEnum :: NOpPrecedence -> Int
fromEnum = coerce :: forall a b. Coercible a b => a -> b
coerce

instance Num NOpPrecedence where
  + :: NOpPrecedence -> NOpPrecedence -> NOpPrecedence
(+) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a -> a
(+) @Int)
  * :: NOpPrecedence -> NOpPrecedence -> NOpPrecedence
(*) = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a -> a
(*) @Int)
  abs :: NOpPrecedence -> NOpPrecedence
abs = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a
abs @Int)
  signum :: NOpPrecedence -> NOpPrecedence
signum = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a
signum @Int)
  fromInteger :: Integer -> NOpPrecedence
fromInteger = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => Integer -> a
fromInteger @Int)
  negate :: NOpPrecedence -> NOpPrecedence
negate = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Num a => a -> a
negate @Int)

--  2022-01-26: NOTE: This type belongs into 'Type.Expr' & be used in NExprF.
data NAppOp = NAppOp
  deriving (NAppOp -> NAppOp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NAppOp -> NAppOp -> Bool
$c/= :: NAppOp -> NAppOp -> Bool
== :: NAppOp -> NAppOp -> Bool
$c== :: NAppOp -> NAppOp -> Bool
Eq, Eq NAppOp
NAppOp -> NAppOp -> Bool
NAppOp -> NAppOp -> Ordering
NAppOp -> NAppOp -> NAppOp
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 :: NAppOp -> NAppOp -> NAppOp
$cmin :: NAppOp -> NAppOp -> NAppOp
max :: NAppOp -> NAppOp -> NAppOp
$cmax :: NAppOp -> NAppOp -> NAppOp
>= :: NAppOp -> NAppOp -> Bool
$c>= :: NAppOp -> NAppOp -> Bool
> :: NAppOp -> NAppOp -> Bool
$c> :: NAppOp -> NAppOp -> Bool
<= :: NAppOp -> NAppOp -> Bool
$c<= :: NAppOp -> NAppOp -> Bool
< :: NAppOp -> NAppOp -> Bool
$c< :: NAppOp -> NAppOp -> Bool
compare :: NAppOp -> NAppOp -> Ordering
$ccompare :: NAppOp -> NAppOp -> Ordering
Ord, forall x. Rep NAppOp x -> NAppOp
forall x. NAppOp -> Rep NAppOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NAppOp x -> NAppOp
$cfrom :: forall x. NAppOp -> Rep NAppOp x
Generic, Typeable, Typeable NAppOp
NAppOp -> DataType
NAppOp -> Constr
(forall b. Data b => b -> b) -> NAppOp -> NAppOp
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) -> NAppOp -> u
forall u. (forall d. Data d => d -> u) -> NAppOp -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAppOp -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAppOp -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAppOp
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAppOp -> c NAppOp
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NAppOp)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAppOp)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NAppOp -> m NAppOp
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NAppOp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NAppOp -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NAppOp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NAppOp -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAppOp -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAppOp -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAppOp -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAppOp -> r
gmapT :: (forall b. Data b => b -> b) -> NAppOp -> NAppOp
$cgmapT :: (forall b. Data b => b -> b) -> NAppOp -> NAppOp
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAppOp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAppOp)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NAppOp)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NAppOp)
dataTypeOf :: NAppOp -> DataType
$cdataTypeOf :: NAppOp -> DataType
toConstr :: NAppOp -> Constr
$ctoConstr :: NAppOp -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAppOp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NAppOp
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAppOp -> c NAppOp
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NAppOp -> c NAppOp
Data, Int -> NAppOp -> ShowS
[NAppOp] -> ShowS
NAppOp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NAppOp] -> ShowS
$cshowList :: [NAppOp] -> ShowS
show :: NAppOp -> String
$cshow :: NAppOp -> String
showsPrec :: Int -> NAppOp -> ShowS
$cshowsPrec :: Int -> NAppOp -> ShowS
Show, NAppOp -> ()
forall a. (a -> ()) -> NFData a
rnf :: NAppOp -> ()
$crnf :: NAppOp -> ()
NFData)

--  2022-01-26: NOTE: This type belongs into 'Type.Expr' & be used in NExprF.
data NSpecialOp
  = NHasAttrOp
  | NSelectOp
  | NTerm -- ^ For special handling of internal special cases.
  deriving (NSpecialOp -> NSpecialOp -> Bool
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
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
Ord, 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
NSpecialOp -> DataType
NSpecialOp -> Constr
(forall b. Data b => b -> b) -> NSpecialOp -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> NSpecialOp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NSpecialOp -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NSpecialOp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NSpecialOp -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Int -> NSpecialOp -> ShowS
[NSpecialOp] -> ShowS
NSpecialOp -> String
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 -> ()
forall a. (a -> ()) -> NFData a
rnf :: NSpecialOp -> ()
$crnf :: NSpecialOp -> ()
NFData)

data NAssoc
  = NAssocLeft
  -- Nota bene: @parser-combinators@ named "associative property" as 'InfixN' stating it as "non-associative property".
  -- Binary operators having some associativity is a basis property in mathematical algebras in use (for example, in Category theory). Having no associativity in operators makes theory mostly impossible in use and so non-associativity is not encountered in notations, therefore under 'InfixN' @parser-combinators@ meant "associative".
  -- | Bidirectional associativity, or simply: associative property.
  | NAssoc
  | NAssocRight
  deriving (NAssoc -> NAssoc -> Bool
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
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
Ord, 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
NAssoc -> DataType
NAssoc -> Constr
(forall b. Data b => b -> b) -> NAssoc -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> NAssoc -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NAssoc -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NAssoc -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NAssoc -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Int -> NAssoc -> ShowS
[NAssoc] -> ShowS
NAssoc -> String
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 -> ()
forall a. (a -> ()) -> NFData a
rnf :: NAssoc -> ()
$crnf :: NAssoc -> ()
NFData)

--  2022-01-31: NOTE: This type and related typeclasses & their design, probably need a refinement.
--
-- In the "Nix.Pretty", the code probably should be well-typed to the type of operations its processes.
-- Therefor splitting operation types into separate types there is probably needed.
--
-- After that:
--
-- > { NAssoc, NOpPrecedence, NOpName }
--
-- Can be formed into a type.
--
-- Also 'NAppDef' really has only 1 implementation, @{ NAssoc, NOpPrecedence, NOpName }@
-- were added there only to make type uniformal.
-- All impossible cases ideally should be unrepresentable.
-- | Single operator grammar entries.
data NOperatorDef
  = NAppDef     NAppOp     NAssoc NOpPrecedence NOpName
  | NUnaryDef   NUnaryOp   NAssoc NOpPrecedence NOpName
  | NBinaryDef  NBinaryOp  NAssoc NOpPrecedence NOpName
  | NSpecialDef NSpecialOp NAssoc NOpPrecedence NOpName
  --  2022-01-26: NOTE: Ord can be the order of evaluation of precedence (which 'Pretty' printing also accounts for).
  deriving (NOperatorDef -> NOperatorDef -> Bool
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
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
Ord, 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
NOperatorDef -> DataType
NOperatorDef -> Constr
(forall b. Data b => b -> b) -> NOperatorDef -> 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> NOperatorDef -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NOperatorDef -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NOperatorDef -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NOperatorDef -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data, Int -> NOperatorDef -> ShowS
[NOperatorDef] -> ShowS
NOperatorDef -> String
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 -> ()
forall a. (a -> ()) -> NFData a
rnf :: NOperatorDef -> ()
$crnf :: NOperatorDef -> ()
NFData)

-- Supplied since its definition gets called/used frequently.
-- | Functional application operator definition, left associative, high precedence.
appOpDef :: NOperatorDef
appOpDef :: NOperatorDef
appOpDef = NAppOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NAppDef NAppOp
NAppOp NAssoc
NAssocLeft NOpPrecedence
1 NOpName
" " -- This defined as "2" in Nix lang spec.

--  2022-01-26: NOTE: When total - make sure to hide & inline all these instances to get free solution.
-- | Class to get a private free construction to abstract away the gap between the Nix operation types
-- 'NUnaryOp', 'NBinaryOp', 'NSpecialOp'.
-- And in doing remove 'OperatorInfo' from existance.
class NOp a where
  {-# minimal getOpDef, getOpAssoc, getOpPrecedence, getOpName #-}

  getOpDef :: a -> NOperatorDef
  getOpAssoc :: a -> NAssoc
  getOpPrecedence :: a -> NOpPrecedence
  getOpName :: a -> NOpName

instance NOp NAppOp where
  getOpDef :: NAppOp -> NOperatorDef
getOpDef NAppOp
NAppOp = NOperatorDef
appOpDef
  getOpAssoc :: NAppOp -> NAssoc
getOpAssoc NAppOp
_op = NOperatorDef -> NAssoc
fun NOperatorDef
appOpDef
   where
    fun :: NOperatorDef -> NAssoc
fun (NAppDef NAppOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) = NAssoc
assoc
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, funapp operation should been matched."
  getOpPrecedence :: NAppOp -> NOpPrecedence
getOpPrecedence NAppOp
_op = NOperatorDef -> NOpPrecedence
fun NOperatorDef
appOpDef
   where
    fun :: NOperatorDef -> NOpPrecedence
fun (NAppDef NAppOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, funapp operation should been matched."
  getOpName :: NAppOp -> NOpName
getOpName NAppOp
_ = NOperatorDef -> NOpName
fun NOperatorDef
appOpDef
   where
    fun :: NOperatorDef -> NOpName
fun (NAppDef NAppOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, funapp operation should been matched."

instance NOp NUnaryOp where
  getOpDef :: NUnaryOp -> NOperatorDef
getOpDef =
    \case
      NUnaryOp
NNeg -> NUnaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NUnaryDef NUnaryOp
NNeg NAssoc
NAssocRight NOpPrecedence
3 NOpName
"-"
      NUnaryOp
NNot -> NUnaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NUnaryDef NUnaryOp
NNot NAssoc
NAssocRight NOpPrecedence
8 NOpName
"!"
  getOpAssoc :: NUnaryOp -> NAssoc
getOpAssoc = NOperatorDef -> NAssoc
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NAssoc
fun (NUnaryDef NUnaryOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) = NAssoc
assoc
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, unary operation should been matched."
  getOpPrecedence :: NUnaryOp -> NOpPrecedence
getOpPrecedence = NOperatorDef -> NOpPrecedence
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpPrecedence
fun (NUnaryDef NUnaryOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, unary operation should been matched."
  getOpName :: NUnaryOp -> NOpName
getOpName = NOperatorDef -> NOpName
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpName
fun (NUnaryDef NUnaryOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, unary operation should been matched."

instance NOp NBinaryOp where
  getOpDef :: NBinaryOp -> NOperatorDef
getOpDef =
    \case
      NBinaryOp
NConcat -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NConcat NAssoc
NAssocRight  NOpPrecedence
5 NOpName
"++"
      NBinaryOp
NMult   -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NMult   NAssoc
NAssocLeft   NOpPrecedence
6 NOpName
"*"
      NBinaryOp
NDiv    -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NDiv    NAssoc
NAssocLeft   NOpPrecedence
6 NOpName
"/"
      NBinaryOp
NPlus   -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NPlus   NAssoc
NAssocLeft   NOpPrecedence
7 NOpName
"+"
      NBinaryOp
NMinus  -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NMinus  NAssoc
NAssocLeft   NOpPrecedence
7 NOpName
"-"
      NBinaryOp
NUpdate -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NUpdate NAssoc
NAssocRight  NOpPrecedence
9 NOpName
"//"
      NBinaryOp
NLt     -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NLt     NAssoc
NAssocLeft  NOpPrecedence
10 NOpName
"<"
      NBinaryOp
NLte    -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NLte    NAssoc
NAssocLeft  NOpPrecedence
10 NOpName
"<="
      NBinaryOp
NGt     -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NGt     NAssoc
NAssocLeft  NOpPrecedence
10 NOpName
">"
      NBinaryOp
NGte    -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NGte    NAssoc
NAssocLeft  NOpPrecedence
10 NOpName
">="
      NBinaryOp
NEq     -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NEq     NAssoc
NAssoc      NOpPrecedence
11 NOpName
"=="
      NBinaryOp
NNEq    -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NNEq    NAssoc
NAssoc      NOpPrecedence
11 NOpName
"!="
      NBinaryOp
NAnd    -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NAnd    NAssoc
NAssocLeft  NOpPrecedence
12 NOpName
"&&"
      NBinaryOp
NOr     -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NOr     NAssoc
NAssocLeft  NOpPrecedence
13 NOpName
"||"
      NBinaryOp
NImpl   -> NBinaryOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NBinaryDef NBinaryOp
NImpl   NAssoc
NAssocRight NOpPrecedence
14 NOpName
"->"
  getOpAssoc :: NBinaryOp -> NAssoc
getOpAssoc = NOperatorDef -> NAssoc
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NAssoc
fun (NBinaryDef NBinaryOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) = NAssoc
assoc
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, binary operation should been matched."
  getOpPrecedence :: NBinaryOp -> NOpPrecedence
getOpPrecedence = NOperatorDef -> NOpPrecedence
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpPrecedence
fun (NBinaryDef NBinaryOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, binary operation should been matched."
  getOpName :: NBinaryOp -> NOpName
getOpName = NOperatorDef -> NOpName
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpName
fun (NBinaryDef NBinaryOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, binary operation should been matched."

instance NOp NSpecialOp where
  getOpDef :: NSpecialOp -> NOperatorDef
getOpDef =
    \case
      NSpecialOp
NSelectOp  -> NSpecialOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NSpecialDef NSpecialOp
NSelectOp  NAssoc
NAssocLeft NOpPrecedence
1 NOpName
"."
      NSpecialOp
NHasAttrOp -> NSpecialOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NSpecialDef NSpecialOp
NHasAttrOp NAssoc
NAssocLeft NOpPrecedence
4 NOpName
"?"
      NSpecialOp
NTerm      -> NSpecialOp -> NAssoc -> NOpPrecedence -> NOpName -> NOperatorDef
NSpecialDef NSpecialOp
NTerm      NAssoc
NAssocLeft NOpPrecedence
1 NOpName
"???"
  getOpAssoc :: NSpecialOp -> NAssoc
getOpAssoc = NOperatorDef -> NAssoc
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NAssoc
fun (NSpecialDef NSpecialOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) = NAssoc
assoc
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, special operation should been matched."
  getOpPrecedence :: NSpecialOp -> NOpPrecedence
getOpPrecedence = NOperatorDef -> NOpPrecedence
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpPrecedence
fun (NSpecialDef NSpecialOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, special operation should been matched."
  getOpName :: NSpecialOp -> NOpName
getOpName = NOperatorDef -> NOpName
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpName
fun (NSpecialDef NSpecialOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun NOperatorDef
_ = forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Impossible happened, special operation should been matched."

instance NOp NOperatorDef where
  getOpDef :: NOperatorDef -> NOperatorDef
getOpDef NOperatorDef
op = NOperatorDef
op
  getOpAssoc :: NOperatorDef -> NAssoc
getOpAssoc = \case
    (NAppDef     NAppOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) -> NAssoc
assoc
    (NUnaryDef   NUnaryOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) -> NAssoc
assoc
    (NBinaryDef  NBinaryOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) -> NAssoc
assoc
    (NSpecialDef NSpecialOp
_op NAssoc
assoc NOpPrecedence
_prec NOpName
_name) -> NAssoc
assoc
  getOpPrecedence :: NOperatorDef -> NOpPrecedence
getOpPrecedence = NOperatorDef -> NOpPrecedence
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpPrecedence
fun (NAppDef     NAppOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun (NUnaryDef   NUnaryOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun (NBinaryDef  NBinaryOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
    fun (NSpecialDef NSpecialOp
_op NAssoc
_assoc NOpPrecedence
prec NOpName
_name) = NOpPrecedence
prec
  getOpName :: NOperatorDef -> NOpName
getOpName = NOperatorDef -> NOpName
fun forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NOp a => a -> NOperatorDef
getOpDef
   where
    fun :: NOperatorDef -> NOpName
fun (NAppDef     NAppOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun (NUnaryDef   NUnaryOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun (NBinaryDef  NBinaryOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name
    fun (NSpecialDef NSpecialOp
_op NAssoc
_assoc NOpPrecedence
_prec NOpName
name) = NOpName
name

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

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

binary
  :: NBinaryOp
  -> Operator Parser NExprLoc
binary :: NBinaryOp
-> Operator (ParsecT Void Text (State SourcePos)) NExprLoc
binary NBinaryOp
op =
  forall (m :: * -> *) a. NAssoc -> m (a -> a -> a) -> Operator m a
mapAssocToInfix (forall a. NOp a => a -> NAssoc
getOpAssoc NBinaryOp
op) forall a b. (a -> b) -> a -> b
$ forall o a. (AnnUnit SrcSpan o -> a) -> o -> NOpName -> Parser a
opWithLoc AnnUnit SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
annNBinary NBinaryOp
op (forall a. NOp a => a -> NOpName
getOpName NBinaryOp
op)

mapAssocToInfix :: NAssoc -> m (a -> a -> a) -> Operator m a
mapAssocToInfix :: forall (m :: * -> *) a. NAssoc -> m (a -> a -> a) -> Operator m a
mapAssocToInfix NAssoc
NAssocLeft  = forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixL
mapAssocToInfix NAssoc
NAssoc      = forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixN
mapAssocToInfix NAssoc
NAssocRight = forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixR

-- ** x: y lambda function

-- | Gets all of the arguments for a function.
argExpr :: Parser (Params NExprLoc)
argExpr :: Parser (Params NExprLoc)
argExpr =
  forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
    [ Parser (Params NExprLoc)
atLeft
    , forall {r}. ParsecT Void Text (State SourcePos) (Params r)
onlyname
    , Parser (Params NExprLoc)
atRight
    ]
  forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser 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 =
    forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
      [ ParsecT Void Text (State SourcePos) NExprLoc
nixUri forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e s (m :: * -> *) a.
MonadParsec e s m =>
ErrorItem (Token s) -> m a
unexpected (forall t. NonEmpty Char -> ErrorItem t
Label forall a b. (a -> b) -> a -> b
$ forall l. IsList l => [Item l] -> l
fromList String
"valid uri" )
      , forall r. VarName -> Params r
Param 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 =
    forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$
      do
        VarName
name             <- Parser VarName
identifier forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Char
symbol Char
'@'
        (Variadic
variadic, [(VarName, Maybe NExprLoc)]
pset) <- Parser (Variadic, [(VarName, Maybe NExprLoc)])
params
        pure $ forall r. Maybe VarName -> Variadic -> ParamSet r -> Params r
ParamSet (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
      (Variadic
variadic, [(VarName, Maybe NExprLoc)]
pset) <- Parser (Variadic, [(VarName, Maybe NExprLoc)])
params
      Maybe VarName
name             <- forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall a b. (a -> b) -> a -> b
$ Char -> Parser Char
symbol Char
'@' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser VarName
identifier
      pure $ 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 (Variadic, [(VarName, Maybe NExprLoc)])
params = forall a. Parser a -> Parser a
braces Parser (Variadic, [(VarName, Maybe NExprLoc)])
getParams

  -- Collects the parameters within curly braces. Returns the parameters and
  -- an flag indication if the parameters are variadic.
  getParams :: Parser (Variadic, [(VarName, Maybe NExprLoc)])
  getParams :: Parser (Variadic, [(VarName, Maybe NExprLoc)])
getParams = [(VarName, Maybe NExprLoc)]
-> Parser (Variadic, [(VarName, Maybe NExprLoc)])
go 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 (Variadic, [(VarName, Maybe NExprLoc)])
    go :: [(VarName, Maybe NExprLoc)]
-> Parser (Variadic, [(VarName, Maybe NExprLoc)])
go [(VarName, Maybe NExprLoc)]
acc = ((Variadic
Variadic, [(VarName, Maybe NExprLoc)]
acc) forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Void Text (State SourcePos) Text
symbols Text
"...") forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<|> Parser (Variadic, [(VarName, Maybe NExprLoc)])
getMore
     where
      getMore :: Parser (Variadic, [(VarName, Maybe NExprLoc)])
      getMore :: Parser (Variadic, [(VarName, Maybe NExprLoc)])
getMore =
        -- Could be nothing, in which just return what we have so far.
        forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option (forall a. Monoid a => a
mempty, [(VarName, Maybe NExprLoc)]
acc) forall a b. (a -> b) -> a -> b
$
          do
            -- Get an argument name and an optional default.
            (VarName, Maybe NExprLoc)
pair <-
              forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,)
                Parser VarName
identifier
                (forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Void Text (State SourcePos) NExprLoc
exprAfterSymbol Char
'?')

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

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

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


-- ** let expression

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

-- ** if then else

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

-- ** with

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


-- ** assert

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

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

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

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

nixSelector :: Parser (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector :: Parser (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector =
  forall a. Parser a -> Parser (AnnUnit SrcSpan a)
annotateLocation1 forall a b. (a -> b) -> a -> b
$ forall l. IsList l => [Item l] -> l
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (NKeyName NExprLoc)
keyName forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy1` Parser ()
selectorDot

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

    forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      forall a. a -> a
id
      (forall a b. a -> b -> a
const ParsecT Void Text (State SourcePos) NExprLoc
-> ParsecT Void Text (State SourcePos) NExprLoc
nixSelect)
      Maybe ()
continues
      (forall (f :: * -> *) a. Applicative f => a -> f a
pure NExprLoc
res)
 where
  builder
    :: NExprLoc
    -> Maybe
      ( Maybe NExprLoc
      , AnnUnit SrcSpan (NAttrPath NExprLoc)
      )
    -> NExprLoc
  builder :: NExprLoc
-> Maybe (Maybe NExprLoc, AnnUnit SrcSpan (NAttrPath NExprLoc))
-> NExprLoc
builder NExprLoc
t =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      NExprLoc
t
      (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (Maybe NExprLoc
-> NExprLoc -> AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc
`annNSelect` NExprLoc
t))


-- ** _ - syntax hole

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

-- List of Nix operation parsers with their precedence.
opParsers :: [(NOpPrecedence, Operator Parser NExprLoc)]
opParsers :: [(NOpPrecedence,
  Operator (ParsecT Void Text (State SourcePos)) NExprLoc)]
opParsers =
  -- 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)
  -- ]

  -- NApp is left associative
  -- 2018-05-07: jwiegley: Thanks to Brent Yorgey for showing me this trick!
  forall t b. NOp t => t -> b -> [(NOpPrecedence, b)]
specialBuilder NAppOp
NAppOp (forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixL forall a b. (a -> b) -> a -> b
$ NExprLoc -> NExprLoc -> NExprLoc
annNApp forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Void Text (State SourcePos) Text
symbols forall a. Monoid a => a
mempty) forall a. Semigroup a => a -> a -> a
<>
  forall t b. NOp t => t -> b -> [(NOpPrecedence, b)]
specialBuilder NSpecialOp
NHasAttrOp (forall (m :: * -> *) a. m (a -> a) -> Operator m a
Postfix forall a b. (a -> b) -> a -> b
$ Char -> Parser Char
symbol Char
'?' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (forall a b c. (a -> b -> c) -> b -> a -> c
flip NExprLoc -> AnnUnit SrcSpan (NAttrPath NExprLoc) -> NExprLoc
annNHasAttr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (AnnUnit SrcSpan (NAttrPath NExprLoc))
nixSelector)) forall a. Semigroup a => a -> a -> a
<>
  forall t b.
(Enum t, Bounded t, NOp t) =>
(t -> b) -> [(NOpPrecedence, b)]
builder NUnaryOp -> Operator (ParsecT Void Text (State SourcePos)) NExprLoc
prefix forall a. Semigroup a => a -> a -> a
<>
  forall t b.
(Enum t, Bounded t, NOp t) =>
(t -> b) -> [(NOpPrecedence, b)]
builder NBinaryOp
-> Operator (ParsecT Void Text (State SourcePos)) NExprLoc
binary
 where
  specialBuilder :: NOp t => t -> b -> [(NOpPrecedence, b)]
  specialBuilder :: forall t b. NOp t => t -> b -> [(NOpPrecedence, b)]
specialBuilder t
op b
parser = forall x. One x => OneItem x -> x
one (forall t b. NOp t => t -> (t -> b) -> (NOpPrecedence, b)
entry t
op (forall a b. a -> b -> a
const b
parser))

  builder :: (Enum t, Bounded t, NOp t) => (t -> b) -> [(NOpPrecedence, b)]
  builder :: forall t b.
(Enum t, Bounded t, NOp t) =>
(t -> b) -> [(NOpPrecedence, b)]
builder t -> b
tp = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall t b. NOp t => t -> (t -> b) -> (NOpPrecedence, b)
`entry` t -> b
tp) forall a. (Bounded a, Enum a) => [a]
universe

  entry :: NOp t => t -> (t -> b) -> (NOpPrecedence, b)
  entry :: forall t b. NOp t => t -> (t -> b) -> (NOpPrecedence, b)
entry t
op t -> b
parser = (forall a. NOp a => a -> NOpPrecedence
getOpPrecedence t
op, t -> b
parser t
op)


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

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

-- | Bundles parsers into @[[]]@ based on precedence (form is required for `megaparsec`).
nixOperators :: [[ Operator Parser NExprLoc ]]
nixOperators :: [[Operator (ParsecT Void Text (State SourcePos)) NExprLoc]]
nixOperators =
  forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
    forall k v. Ord k => [(k, v)] -> [(k, [v])]
groupSort [(NOpPrecedence,
  Operator (ParsecT Void Text (State SourcePos)) NExprLoc)]
opParsers

-- | 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 :: ParsecT Void Text (State SourcePos) NExprLoc
nixExprAlgebra =
  forall (m :: * -> *) a.
MonadPlus m =>
m a -> [[Operator m a]] -> m a
makeExprParser
    ParsecT Void Text (State SourcePos) NExprLoc
nixTerm
    [[Operator (ParsecT Void Text (State SourcePos)) NExprLoc]]
nixOperators

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


-- * Parse

type Result a = Either (Doc Void) a


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


parseFromFileEx :: MonadFile m => Parser a -> Path -> m (Result a)
parseFromFileEx :: forall (m :: * -> *) a.
MonadFile m =>
Parser a -> Path -> m (Result a)
parseFromFileEx Parser a
parser Path
file = forall a. Parser a -> Path -> Text -> Either (Doc Void) a
parseWith Parser a
parser Path
file forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadIO m => Path -> m Text
readFile Path
file

parseFromText :: Parser a -> Text -> Result a
parseFromText :: forall a. Parser a -> Text -> Result a
parseFromText = (forall a. Parser a -> Path -> Text -> Either (Doc Void) a
`parseWith` Path
"<string>")

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

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

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

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

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

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

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

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