{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor      #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}

module Nix.Parser
  ( parseNixFile
  , parseNixFileLoc
  , parseNixText
  , parseNixTextLoc
  , parseFromFileEx
  , Parser
  , parseFromText
  , Result(..)
  , reservedNames
  , OperatorInfo(..)
  , NSpecialOp(..)
  , NAssoc(..)
  , NOperatorDef
  , getUnaryOperator
  , getBinaryOperator
  , getSpecialOperator
  , nixToplevelForm
  , nixExpr
  , nixSet
  , nixBinders
  , nixSelector
  , nixSym
  , nixPath
  , nixString
  , nixUri
  , nixSearchPath
  , nixFloat
  , nixInt
  , nixBool
  , nixNull
  , symbol
  , whiteSpace
  )
where

import           Prelude                 hiding ( readFile )

import           Control.Applicative     hiding ( many
                                                , some
                                                )
import           Control.DeepSeq
import           Control.Monad
import           Control.Monad.Combinators.Expr
import           Data.Char                      ( isAlpha
                                                , isDigit
                                                , isSpace
                                                )
import           Data.Data                      ( Data(..) )
import           Data.Functor
import           Data.Functor.Identity
import           Data.HashSet                   ( HashSet )
import qualified Data.HashSet                  as HashSet
import           Data.List.NonEmpty             ( NonEmpty(..) )
import qualified Data.List.NonEmpty            as NE
import qualified Data.Map                      as Map
import           Data.Text               hiding ( map
                                                , foldr1
                                                , concat
                                                , concatMap
                                                , zipWith
                                                )
import           Data.Text.Prettyprint.Doc      ( Doc
                                                , pretty
                                                )
import           Data.Text.Encoding
import           Data.Typeable                  ( Typeable )
import           Data.Void
import           GHC.Generics            hiding ( Prefix )
import           Nix.Expr                hiding ( ($>) )
import           Nix.Expr.Strings
import           Nix.Render
import           Text.Megaparsec
import           Text.Megaparsec.Char
import qualified Text.Megaparsec.Char.Lexer    as L

infixl 3 <+>
(<+>) :: MonadPlus m => m a -> m a -> m a
<+> :: m a -> m a -> m a
(<+>) = m a -> m a -> m a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus

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

nixExpr :: Parser NExprLoc
nixExpr :: Parser NExprLoc
nixExpr = Parser NExprLoc
-> [[Operator (ParsecT Void Text Identity) NExprLoc]]
-> Parser NExprLoc
forall (m :: * -> *) a.
MonadPlus m =>
m a -> [[Operator m a]] -> m a
makeExprParser Parser NExprLoc
nixTerm ([[Operator (ParsecT Void Text Identity) NExprLoc]]
 -> Parser NExprLoc)
-> [[Operator (ParsecT Void Text Identity) NExprLoc]]
-> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ ([(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
 -> [Operator (ParsecT Void Text Identity) NExprLoc])
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
-> [[Operator (ParsecT Void Text Identity) NExprLoc]]
forall a b. (a -> b) -> [a] -> [b]
map (((NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)
 -> Operator (ParsecT Void Text Identity) NExprLoc)
-> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
-> [Operator (ParsecT Void Text Identity) NExprLoc]
forall a b. (a -> b) -> [a] -> [b]
map (NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)
-> Operator (ParsecT Void Text Identity) NExprLoc
forall a b. (a, b) -> b
snd) (Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
nixOperators Parser (Ann SrcSpan (NAttrPath NExprLoc))
nixSelector)

antiStart :: Parser Text
antiStart :: Parser Text
antiStart = Text -> Parser Text
symbol "${" Parser Text -> String -> Parser Text
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String -> String
forall a. Show a => a -> String
show ("${" :: String)

nixAntiquoted :: Parser a -> Parser (Antiquoted a NExprLoc)
nixAntiquoted :: Parser a -> Parser (Antiquoted a NExprLoc)
nixAntiquoted p :: Parser a
p =
  NExprLoc -> Antiquoted a NExprLoc
forall v r. r -> Antiquoted v r
Antiquoted
    (NExprLoc -> Antiquoted a NExprLoc)
-> Parser NExprLoc -> Parser (Antiquoted a NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser Text
antiStart Parser Text -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm Parser NExprLoc -> Parser Text -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Parser Text
symbol "}")
    Parser (Antiquoted a NExprLoc)
-> Parser (Antiquoted a NExprLoc) -> Parser (Antiquoted a NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> a -> Antiquoted a NExprLoc
forall v r. v -> Antiquoted v r
Plain
    (a -> Antiquoted a NExprLoc)
-> Parser a -> Parser (Antiquoted a NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser a
p
    Parser (Antiquoted a NExprLoc)
-> String -> Parser (Antiquoted a NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "anti-quotation"

selDot :: Parser ()
selDot :: Parser ()
selDot = Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Text -> Parser Text
symbol "." Parser Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy Parser NExprLoc
nixPath) Parser () -> String -> Parser ()
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "."

nixSelect :: Parser NExprLoc -> Parser NExprLoc
nixSelect :: Parser NExprLoc -> Parser NExprLoc
nixSelect term :: Parser NExprLoc
term = do
  NExprLoc
res <- NExprLoc
-> Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> NExprLoc
build (NExprLoc
 -> Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
 -> NExprLoc)
-> Parser NExprLoc
-> ParsecT
     Void
     Text
     Identity
     (Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
      -> NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NExprLoc
term ParsecT
  Void
  Text
  Identity
  (Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
   -> NExprLoc)
-> ParsecT
     Void
     Text
     Identity
     (Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
-> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT
  Void
  Text
  Identity
  (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> ParsecT
     Void
     Text
     Identity
     (Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional
    ((,) (Ann SrcSpan (NAttrPath NExprLoc)
 -> Maybe NExprLoc
 -> (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
-> Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> ParsecT
     Void
     Text
     Identity
     (Maybe NExprLoc
      -> (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser ()
selDot Parser ()
-> Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> Parser (Ann SrcSpan (NAttrPath NExprLoc))
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser (Ann SrcSpan (NAttrPath NExprLoc))
nixSelector) ParsecT
  Void
  Text
  Identity
  (Maybe NExprLoc
   -> (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc))
-> ParsecT Void Text Identity (Maybe NExprLoc)
-> ParsecT
     Void
     Text
     Identity
     (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser NExprLoc -> ParsecT Void Text Identity (Maybe NExprLoc)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Text -> Parser ()
reserved "or" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixTerm))
  Maybe ()
continues <- Parser () -> ParsecT Void Text Identity (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser () -> ParsecT Void Text Identity (Maybe ()))
-> Parser () -> ParsecT Void Text Identity (Maybe ())
forall a b. (a -> b) -> a -> b
$ Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead Parser ()
selDot
  case Maybe ()
continues of
    Nothing -> NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a. Applicative f => a -> f a
pure NExprLoc
res
    Just _  -> Parser NExprLoc -> Parser NExprLoc
nixSelect (NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a. Applicative f => a -> f a
pure NExprLoc
res)
 where
  build
    :: NExprLoc
    -> Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
    -> NExprLoc
  build :: NExprLoc
-> Maybe (Ann SrcSpan (NAttrPath NExprLoc), Maybe NExprLoc)
-> NExprLoc
build t :: NExprLoc
t Nothing       = NExprLoc
t
  build t :: NExprLoc
t (Just (s :: Ann SrcSpan (NAttrPath NExprLoc)
s, o :: Maybe NExprLoc
o)) = NExprLoc
-> Ann SrcSpan (NAttrPath NExprLoc) -> Maybe NExprLoc -> NExprLoc
nSelectLoc NExprLoc
t Ann SrcSpan (NAttrPath NExprLoc)
s Maybe NExprLoc
o

nixSelector :: Parser (Ann SrcSpan (NAttrPath NExprLoc))
nixSelector :: Parser (Ann SrcSpan (NAttrPath NExprLoc))
nixSelector = Parser (NAttrPath NExprLoc)
-> Parser (Ann SrcSpan (NAttrPath NExprLoc))
forall a. Parser a -> Parser (Ann SrcSpan a)
annotateLocation (Parser (NAttrPath NExprLoc)
 -> Parser (Ann SrcSpan (NAttrPath NExprLoc)))
-> Parser (NAttrPath NExprLoc)
-> Parser (Ann SrcSpan (NAttrPath NExprLoc))
forall a b. (a -> b) -> a -> b
$ do
  (x :: NKeyName NExprLoc
x : xs :: [NKeyName NExprLoc]
xs) <- Parser (NKeyName NExprLoc)
keyName Parser (NKeyName NExprLoc)
-> Parser () -> ParsecT Void Text Identity [NKeyName NExprLoc]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy1` Parser ()
selDot
  NAttrPath NExprLoc -> Parser (NAttrPath NExprLoc)
forall (m :: * -> *) a. Monad m => a -> m a
return (NAttrPath NExprLoc -> Parser (NAttrPath NExprLoc))
-> NAttrPath NExprLoc -> Parser (NAttrPath NExprLoc)
forall a b. (a -> b) -> a -> b
$ NKeyName NExprLoc
x NKeyName NExprLoc -> [NKeyName NExprLoc] -> NAttrPath NExprLoc
forall a. a -> [a] -> NonEmpty a
:| [NKeyName NExprLoc]
xs

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

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

nixSym :: Parser NExprLoc
nixSym :: Parser NExprLoc
nixSym = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Text -> NExprF NExprLoc
forall a. Text -> NExprF a
mkSymF (Text -> NExprF NExprLoc)
-> Parser Text -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text
identifier

nixSynHole :: Parser NExprLoc
nixSynHole :: Parser NExprLoc
nixSynHole = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Text -> NExprF NExprLoc
forall a. Text -> NExprF a
mkSynHoleF (Text -> NExprF NExprLoc)
-> Parser Text -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'^' ParsecT Void Text Identity Char -> Parser Text -> Parser Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser Text
identifier)

nixInt :: Parser NExprLoc
nixInt :: Parser NExprLoc
nixInt = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Integer -> NExprF NExprLoc
forall a. Integer -> NExprF a
mkIntF (Integer -> NExprF NExprLoc)
-> ParsecT Void Text Identity Integer -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Integer
integer Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "integer")

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

nixBool :: Parser NExprLoc
nixBool :: Parser NExprLoc
nixBool =
  Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Text -> Bool -> Parser (NExprF NExprLoc)
forall a. Text -> Bool -> ParsecT Void Text Identity (NExprF a)
bool "true" Bool
True Parser (NExprF NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> Text -> Bool -> Parser (NExprF NExprLoc)
forall a. Text -> Bool -> ParsecT Void Text Identity (NExprF a)
bool "false" Bool
False) Parser NExprLoc -> String -> Parser NExprLoc
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "bool"
  where bool :: Text -> Bool -> ParsecT Void Text Identity (NExprF a)
bool str :: Text
str b :: Bool
b = Bool -> NExprF a
forall a. Bool -> NExprF a
mkBoolF Bool
b NExprF a -> Parser () -> ParsecT Void Text Identity (NExprF a)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser ()
reserved Text
str

nixNull :: Parser NExprLoc
nixNull :: Parser NExprLoc
nixNull = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (NExprF NExprLoc
forall a. NExprF a
mkNullF NExprF NExprLoc -> Parser () -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser ()
reserved "null" Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "null")

nixParens :: Parser NExprLoc
nixParens :: Parser NExprLoc
nixParens = Parser NExprLoc -> Parser NExprLoc
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
parens Parser NExprLoc
nixToplevelForm Parser NExprLoc -> String -> Parser NExprLoc
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "parens"

nixList :: Parser NExprLoc
nixList :: Parser NExprLoc
nixList = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
brackets ([NExprLoc] -> NExprF NExprLoc
forall r. [r] -> NExprF r
NList ([NExprLoc] -> NExprF NExprLoc)
-> ParsecT Void Text Identity [NExprLoc]
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NExprLoc -> ParsecT Void Text Identity [NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many Parser NExprLoc
nixTerm) Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "list")

pathChar :: Char -> Bool
pathChar :: Char -> Bool
pathChar x :: Char
x =
  Char -> Bool
isAlpha Char
x
    Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
x
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '.'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '_'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '-'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '+'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '~'

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

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

pathStr :: Parser FilePath
pathStr :: ParsecT Void Text Identity String
pathStr = ParsecT Void Text Identity String
-> ParsecT Void Text Identity String
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (ParsecT Void Text Identity String
 -> ParsecT Void Text Identity String)
-> ParsecT Void Text Identity String
-> ParsecT Void Text Identity String
forall a b. (a -> b) -> a -> b
$ (String -> String -> String)
-> ParsecT Void Text Identity String
-> ParsecT Void Text Identity String
-> ParsecT Void Text Identity String
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2
  String -> String -> String
forall a. [a] -> [a] -> [a]
(++)
  (ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ((Token Text -> Bool) -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
pathChar))
  ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Prelude.concat ([String] -> String)
-> ParsecT Void Text Identity [String]
-> ParsecT Void Text Identity String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity String
-> ParsecT Void Text Identity [String]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ((Char -> String -> String)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
-> ParsecT Void Text Identity String
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (:) ParsecT Void Text Identity Char
slash (ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ((Token Text -> Bool) -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
pathChar))))

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

nixLet :: Parser NExprLoc
nixLet :: Parser NExprLoc
nixLet = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1
  (Text -> Parser ()
reserved "let" Parser () -> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Parser (NExprF NExprLoc)
letBody Parser (NExprF NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> Parser (NExprF NExprLoc)
letBinders) Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "let block")
 where
  letBinders :: Parser (NExprF NExprLoc)
letBinders = [Binding NExprLoc] -> NExprLoc -> NExprF NExprLoc
forall r. [Binding r] -> r -> NExprF r
NLet ([Binding NExprLoc] -> NExprLoc -> NExprF NExprLoc)
-> ParsecT Void Text Identity [Binding NExprLoc]
-> ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity [Binding NExprLoc]
nixBinders ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser ()
reserved "in" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
  -- Let expressions `let {..., body = ...}' are just desugared
  -- into `(rec {..., body = ...}).body'.
  letBody :: Parser (NExprF NExprLoc)
letBody    = (\x :: NExprLoc
x -> NExprLoc -> NAttrPath NExprLoc -> Maybe NExprLoc -> NExprF NExprLoc
forall r. r -> NAttrPath r -> Maybe r -> NExprF r
NSelect NExprLoc
x (Text -> NKeyName NExprLoc
forall r. Text -> NKeyName r
StaticKey "body" NKeyName NExprLoc -> [NKeyName NExprLoc] -> NAttrPath NExprLoc
forall a. a -> [a] -> NonEmpty a
:| []) Maybe NExprLoc
forall a. Maybe a
Nothing) (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NExprLoc
aset
  aset :: Parser NExprLoc
aset       = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ NRecordType -> [Binding NExprLoc] -> NExprF NExprLoc
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NRecursive ([Binding NExprLoc] -> NExprF NExprLoc)
-> ParsecT Void Text Identity [Binding NExprLoc]
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity [Binding NExprLoc]
-> ParsecT Void Text Identity [Binding NExprLoc]
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
braces ParsecT Void Text Identity [Binding NExprLoc]
nixBinders

nixIf :: Parser NExprLoc
nixIf :: Parser NExprLoc
nixIf = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1
  (   NExprLoc -> NExprLoc -> NExprLoc -> NExprF NExprLoc
forall r. r -> r -> r -> NExprF r
NIf
  (NExprLoc -> NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc
-> ParsecT
     Void Text Identity (NExprLoc -> NExprLoc -> NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Parser ()
reserved "if" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixExpr)
  ParsecT
  Void Text Identity (NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc
-> ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser ()
reserved "then" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
  ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser ()
reserved "else" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
  Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "if"
  )

nixAssert :: Parser NExprLoc
nixAssert :: Parser NExprLoc
nixAssert = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1
  (   NExprLoc -> NExprLoc -> NExprF NExprLoc
forall r. r -> r -> NExprF r
NAssert
  (NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc
-> ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Parser ()
reserved "assert" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixExpr)
  ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser Text
semi Parser Text -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
  Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "assert"
  )

nixWith :: Parser NExprLoc
nixWith :: Parser NExprLoc
nixWith = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1
  (   NExprLoc -> NExprLoc -> NExprF NExprLoc
forall r. r -> r -> NExprF r
NWith
  (NExprLoc -> NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc
-> ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Parser ()
reserved "with" Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
  ParsecT Void Text Identity (NExprLoc -> NExprF NExprLoc)
-> Parser NExprLoc -> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser Text
semi Parser Text -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
  Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "with"
  )

nixLambda :: Parser NExprLoc
nixLambda :: Parser NExprLoc
nixLambda = Ann SrcSpan (Params NExprLoc) -> NExprLoc -> NExprLoc
nAbs (Ann SrcSpan (Params NExprLoc) -> NExprLoc -> NExprLoc)
-> ParsecT Void Text Identity (Ann SrcSpan (Params NExprLoc))
-> ParsecT Void Text Identity (NExprLoc -> NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Params NExprLoc)
-> ParsecT Void Text Identity (Ann SrcSpan (Params NExprLoc))
forall a. Parser a -> Parser (Ann SrcSpan a)
annotateLocation (Parser (Params NExprLoc) -> Parser (Params NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser (Params NExprLoc)
argExpr) ParsecT Void Text Identity (NExprLoc -> NExprLoc)
-> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser NExprLoc
nixToplevelForm

nixString :: Parser NExprLoc
nixString :: Parser NExprLoc
nixString = Ann SrcSpan (NString NExprLoc) -> NExprLoc
nStr (Ann SrcSpan (NString NExprLoc) -> NExprLoc)
-> ParsecT Void Text Identity (Ann SrcSpan (NString NExprLoc))
-> Parser NExprLoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (NString NExprLoc)
-> ParsecT Void Text Identity (Ann SrcSpan (NString NExprLoc))
forall a. Parser a -> Parser (Ann SrcSpan a)
annotateLocation Parser (NString NExprLoc)
nixString'

nixUri :: Parser NExprLoc
nixUri :: Parser NExprLoc
nixUri = Parser NExprLoc -> Parser NExprLoc
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser NExprLoc -> Parser NExprLoc)
-> Parser NExprLoc -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 (Parser (NExprF NExprLoc) -> Parser NExprLoc)
-> Parser (NExprF NExprLoc) -> Parser NExprLoc
forall a b. (a -> b) -> a -> b
$ Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc))
-> Parser (NExprF NExprLoc) -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$ do
  Char
start    <- ParsecT Void Text Identity Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
letterChar
  String
protocol <- ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT Void Text Identity Char
 -> ParsecT Void Text Identity String)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall a b. (a -> b) -> a -> b
$ (Token Text -> Bool) -> ParsecT Void Text Identity Char
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy ((Token Text -> Bool) -> ParsecT Void Text Identity Char)
-> (Token Text -> Bool) -> ParsecT Void Text Identity Char
forall a b. (a -> b) -> a -> b
$ \x :: Token Text
x ->
    Char -> Bool
isAlpha Char
Token Text
x Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
Token Text
x Bool -> Bool -> Bool
|| Char
Token Text
x Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ("+-." :: String)
  Text
_       <- Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string ":"
  String
address <- ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some (ParsecT Void Text Identity Char
 -> ParsecT Void Text Identity String)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall a b. (a -> b) -> a -> b
$ (Token Text -> Bool) -> ParsecT Void Text Identity Char
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy ((Token Text -> Bool) -> ParsecT Void Text Identity Char)
-> (Token Text -> Bool) -> ParsecT Void Text Identity Char
forall a b. (a -> b) -> a -> b
$ \x :: Token Text
x ->
    Char -> Bool
isAlpha Char
Token Text
x Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
Token Text
x Bool -> Bool -> Bool
|| Char
Token Text
x Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ("%/?:@&=+$,-_.!~*'" :: String)
  NExprF NExprLoc -> Parser (NExprF NExprLoc)
forall (m :: * -> *) a. Monad m => a -> m a
return (NExprF NExprLoc -> Parser (NExprF NExprLoc))
-> NExprF NExprLoc -> Parser (NExprF NExprLoc)
forall a b. (a -> b) -> a -> b
$ NString NExprLoc -> NExprF NExprLoc
forall r. NString r -> NExprF r
NStr (NString NExprLoc -> NExprF NExprLoc)
-> NString NExprLoc -> NExprF NExprLoc
forall a b. (a -> b) -> a -> b
$ [Antiquoted Text NExprLoc] -> NString NExprLoc
forall r. [Antiquoted Text r] -> NString r
DoubleQuoted
    [Text -> Antiquoted Text NExprLoc
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text NExprLoc)
-> Text -> Antiquoted Text NExprLoc
forall a b. (a -> b) -> a -> b
$ String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Char
start Char -> String -> String
forall a. a -> [a] -> [a]
: String
protocol String -> String -> String
forall a. [a] -> [a] -> [a]
++ ':' Char -> String -> String
forall a. a -> [a] -> [a]
: String
address]

nixString' :: Parser (NString NExprLoc)
nixString' :: Parser (NString NExprLoc)
nixString' = Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser (NString NExprLoc)
doubleQuoted Parser (NString NExprLoc)
-> Parser (NString NExprLoc) -> Parser (NString NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> Parser (NString NExprLoc)
indented Parser (NString NExprLoc) -> String -> Parser (NString NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "string")
 where
  doubleQuoted :: Parser (NString NExprLoc)
  doubleQuoted :: Parser (NString NExprLoc)
doubleQuoted =
    [Antiquoted Text NExprLoc] -> NString NExprLoc
forall r. [Antiquoted Text r] -> NString r
DoubleQuoted
      ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> ([Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc])
-> [Antiquoted Text NExprLoc]
-> NString NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.   [Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
removePlainEmpty
      ([Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc])
-> ([Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc])
-> [Antiquoted Text NExprLoc]
-> [Antiquoted Text NExprLoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.   [Antiquoted Text NExprLoc] -> [Antiquoted Text NExprLoc]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain
      ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
-> Parser (NString NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (  Parser ()
doubleQ
          Parser ()
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (Parser ()
-> Parser ()
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
stringChar Parser ()
doubleQ (ParsecT Void Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text Identity Char -> Parser ())
-> ParsecT Void Text Identity Char -> Parser ()
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'\\') ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall r. ParsecT Void Text Identity (Antiquoted Text r)
doubleEscape)
          ParsecT Void Text Identity [Antiquoted Text NExprLoc]
-> Parser ()
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
doubleQ
          )
      Parser (NString NExprLoc) -> String -> Parser (NString NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "double quoted string"

  doubleQ :: Parser ()
doubleQ      = ParsecT Void Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'"')
  doubleEscape :: ParsecT Void Text Identity (Antiquoted Text r)
doubleEscape = Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text r)
-> (Char -> Text) -> Char -> Antiquoted Text r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
singleton (Char -> Antiquoted Text r)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity (Antiquoted Text r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'\\' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Char
escapeCode)

  indented :: Parser (NString NExprLoc)
  indented :: Parser (NString NExprLoc)
indented =
    [Antiquoted Text NExprLoc] -> NString NExprLoc
forall r. [Antiquoted Text r] -> NString r
stripIndent
      ([Antiquoted Text NExprLoc] -> NString NExprLoc)
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
-> Parser (NString NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (  Parser ()
indentedQ
          Parser ()
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (Parser ()
-> Parser ()
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
stringChar Parser ()
indentedQ Parser ()
indentedQ ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall r. ParsecT Void Text Identity (Antiquoted Text r)
indentedEscape)
          ParsecT Void Text Identity [Antiquoted Text NExprLoc]
-> Parser ()
-> ParsecT Void Text Identity [Antiquoted Text NExprLoc]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
indentedQ
          )
      Parser (NString NExprLoc) -> String -> Parser (NString NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "indented string"

  indentedQ :: Parser ()
indentedQ      = ParsecT Void Text Identity (Tokens Text) -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string "''" ParsecT Void Text Identity (Tokens Text)
-> String -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "\"''\"")
  indentedEscape :: ParsecT Void Text Identity (Antiquoted Text r)
indentedEscape = ParsecT Void Text Identity (Antiquoted Text r)
-> ParsecT Void Text Identity (Antiquoted Text r)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity (Antiquoted Text r)
 -> ParsecT Void Text Identity (Antiquoted Text r))
-> ParsecT Void Text Identity (Antiquoted Text r)
-> ParsecT Void Text Identity (Antiquoted Text r)
forall a b. (a -> b) -> a -> b
$ do
    Parser ()
indentedQ
    (Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text r)
-> Parser Text -> ParsecT Void Text Identity (Antiquoted Text r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ("''" Text -> ParsecT Void Text Identity Char -> Parser Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'\'' Parser Text -> Parser Text -> Parser Text
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> "$" Text -> ParsecT Void Text Identity Char -> Parser Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'$')) ParsecT Void Text Identity (Antiquoted Text r)
-> ParsecT Void Text Identity (Antiquoted Text r)
-> ParsecT Void Text Identity (Antiquoted Text r)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> do
      Char
_ <- Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'\\'
      Char
c <- ParsecT Void Text Identity Char
escapeCode
      Antiquoted Text r -> ParsecT Void Text Identity (Antiquoted Text r)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Antiquoted Text r
 -> ParsecT Void Text Identity (Antiquoted Text r))
-> Antiquoted Text r
-> ParsecT Void Text Identity (Antiquoted Text r)
forall a b. (a -> b) -> a -> b
$ if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '\n' then Antiquoted Text r
forall v r. Antiquoted v r
EscapedNewline else Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text -> Antiquoted Text r) -> Text -> Antiquoted Text r
forall a b. (a -> b) -> a -> b
$ Char -> Text
singleton Char
c

  stringChar :: Parser ()
-> Parser ()
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
stringChar end :: Parser ()
end escStart :: Parser ()
escStart esc :: ParsecT Void Text Identity (Antiquoted Text NExprLoc)
esc =
    NExprLoc -> Antiquoted Text NExprLoc
forall v r. r -> Antiquoted v r
Antiquoted
      (NExprLoc -> Antiquoted Text NExprLoc)
-> Parser NExprLoc
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser Text
antiStart Parser Text -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm Parser NExprLoc
-> ParsecT Void Text Identity Char -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'}')
      ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> Text -> Antiquoted Text NExprLoc
forall v r. v -> Antiquoted v r
Plain
      (Text -> Antiquoted Text NExprLoc)
-> (Char -> Text) -> Char -> Antiquoted Text NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.   Char -> Text
singleton
      (Char -> Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'$'
      ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
esc
      ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> Text -> Antiquoted Text NExprLoc
forall v r. v -> Antiquoted v r
Plain
      (Text -> Antiquoted Text NExprLoc)
-> (String -> Text) -> String -> Antiquoted Text NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.   String -> Text
pack
      (String -> Antiquoted Text NExprLoc)
-> ParsecT Void Text Identity String
-> ParsecT Void Text Identity (Antiquoted Text NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ParsecT Void Text Identity Char
plainChar
   where
    plainChar :: ParsecT Void Text Identity Char
plainChar =
      Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Parser ()
end Parser () -> Parser () -> Parser ()
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> ParsecT Void Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'$') Parser () -> Parser () -> Parser ()
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> Parser ()
escStart) Parser ()
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Char
forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle

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

-- | Gets all of the arguments for a function.
argExpr :: Parser (Params NExprLoc)
argExpr :: Parser (Params NExprLoc)
argExpr = [Parser (Params NExprLoc)] -> Parser (Params NExprLoc)
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [Parser (Params NExprLoc)
atLeft, Parser (Params NExprLoc)
forall r. ParsecT Void Text Identity (Params r)
onlyname, Parser (Params NExprLoc)
atRight] Parser (Params NExprLoc) -> Parser Text -> Parser (Params NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Parser Text
symbol ":" 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 Identity (Params r)
onlyname =
    [ParsecT Void Text Identity (Params r)]
-> ParsecT Void Text Identity (Params r)
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
      [ Parser NExprLoc
nixUri Parser NExprLoc
-> ParsecT Void Text Identity (Params r)
-> ParsecT Void Text Identity (Params r)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ErrorItem (Token Text) -> ParsecT Void Text Identity (Params r)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
ErrorItem (Token s) -> m a
unexpected (NonEmpty Char -> ErrorItem Char
forall t. NonEmpty Char -> ErrorItem t
Label ('v' Char -> String -> NonEmpty Char
forall a. a -> [a] -> NonEmpty a
NE.:| "alid uri"))
      , Text -> Params r
forall r. Text -> Params r
Param (Text -> Params r)
-> Parser Text -> ParsecT Void Text Identity (Params r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text
identifier
      ]

  -- Parameters named by an identifier on the left (`args @ {x, y}`)
  atLeft :: Parser (Params NExprLoc)
atLeft = Parser (Params NExprLoc) -> Parser (Params NExprLoc)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser (Params NExprLoc) -> Parser (Params NExprLoc))
-> Parser (Params NExprLoc) -> Parser (Params NExprLoc)
forall a b. (a -> b) -> a -> b
$ do
    Text
name               <- Parser Text
identifier Parser Text -> Parser Text -> Parser Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Parser Text
symbol "@"
    (variadic :: Bool
variadic, params :: [(Text, Maybe NExprLoc)]
params) <- ParsecT Void Text Identity (Bool, [(Text, Maybe NExprLoc)])
params
    Params NExprLoc -> Parser (Params NExprLoc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Params NExprLoc -> Parser (Params NExprLoc))
-> Params NExprLoc -> Parser (Params NExprLoc)
forall a b. (a -> b) -> a -> b
$ [(Text, Maybe NExprLoc)] -> Bool -> Maybe Text -> Params NExprLoc
forall r. ParamSet r -> Bool -> Maybe Text -> Params r
ParamSet [(Text, Maybe NExprLoc)]
params Bool
variadic (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
name)

  -- Parameters named by an identifier on the right, or none (`{x, y} @ args`)
  atRight :: Parser (Params NExprLoc)
atRight = do
    (variadic :: Bool
variadic, params :: [(Text, Maybe NExprLoc)]
params) <- ParsecT Void Text Identity (Bool, [(Text, Maybe NExprLoc)])
params
    Maybe Text
name               <- Parser Text -> ParsecT Void Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Text -> ParsecT Void Text Identity (Maybe Text))
-> Parser Text -> ParsecT Void Text Identity (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Parser Text
symbol "@" Parser Text -> Parser Text -> Parser Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text
identifier
    Params NExprLoc -> Parser (Params NExprLoc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Params NExprLoc -> Parser (Params NExprLoc))
-> Params NExprLoc -> Parser (Params NExprLoc)
forall a b. (a -> b) -> a -> b
$ [(Text, Maybe NExprLoc)] -> Bool -> Maybe Text -> Params NExprLoc
forall r. ParamSet r -> Bool -> Maybe Text -> Params r
ParamSet [(Text, Maybe NExprLoc)]
params Bool
variadic Maybe Text
name

  -- Return the parameters set.
  params :: ParsecT Void Text Identity (Bool, [(Text, Maybe NExprLoc)])
params = do
    (args :: [(Text, Maybe NExprLoc)]
args, dotdots :: Bool
dotdots) <- ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
braces ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
getParams
    (Bool, [(Text, Maybe NExprLoc)])
-> ParsecT Void Text Identity (Bool, [(Text, Maybe NExprLoc)])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
dotdots, [(Text, Maybe NExprLoc)]
args)

  -- Collects the parameters within curly braces. Returns the parameters and
  -- a boolean indicating if the parameters are variadic.
  getParams :: Parser ([(Text, Maybe NExprLoc)], Bool)
  getParams :: ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
getParams = [(Text, Maybe NExprLoc)]
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
go []   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 :: [(Text, Maybe NExprLoc)]
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
go acc :: [(Text, Maybe NExprLoc)]
acc = (([(Text, Maybe NExprLoc)]
acc, Bool
True) ([(Text, Maybe NExprLoc)], Bool)
-> Parser Text
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser Text
symbol "...") ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> [(Text, Maybe NExprLoc)]
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
getMore [(Text, Maybe NExprLoc)]
acc
    getMore :: [(Text, Maybe NExprLoc)]
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
getMore acc :: [(Text, Maybe NExprLoc)]
acc =
      -- Could be nothing, in which just return what we have so far.
                  ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option ([(Text, Maybe NExprLoc)]
acc, Bool
False) (ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
 -> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool))
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall a b. (a -> b) -> a -> b
$ do
        -- Get an argument name and an optional default.
      (Text, Maybe NExprLoc)
pair <- (Text -> Maybe NExprLoc -> (Text, Maybe NExprLoc))
-> Parser Text
-> ParsecT Void Text Identity (Maybe NExprLoc)
-> ParsecT Void Text Identity (Text, Maybe NExprLoc)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) Parser Text
identifier (Parser NExprLoc -> ParsecT Void Text Identity (Maybe NExprLoc)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser NExprLoc -> ParsecT Void Text Identity (Maybe NExprLoc))
-> Parser NExprLoc -> ParsecT Void Text Identity (Maybe NExprLoc)
forall a b. (a -> b) -> a -> b
$ Parser Text
question Parser Text -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
      -- Either return this, or attempt to get a comma and restart.
      ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option ([(Text, Maybe NExprLoc)]
acc [(Text, Maybe NExprLoc)]
-> [(Text, Maybe NExprLoc)] -> [(Text, Maybe NExprLoc)]
forall a. [a] -> [a] -> [a]
++ [(Text, Maybe NExprLoc)
pair], Bool
False) (ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
 -> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool))
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall a b. (a -> b) -> a -> b
$ Parser Text
comma Parser Text
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [(Text, Maybe NExprLoc)]
-> ParsecT Void Text Identity ([(Text, Maybe NExprLoc)], Bool)
go ([(Text, Maybe NExprLoc)]
acc [(Text, Maybe NExprLoc)]
-> [(Text, Maybe NExprLoc)] -> [(Text, Maybe NExprLoc)]
forall a. [a] -> [a] -> [a]
++ [(Text, Maybe NExprLoc)
pair])

nixBinders :: Parser [Binding NExprLoc]
nixBinders :: ParsecT Void Text Identity [Binding NExprLoc]
nixBinders = (ParsecT Void Text Identity (Binding NExprLoc)
inherit ParsecT Void Text Identity (Binding NExprLoc)
-> ParsecT Void Text Identity (Binding NExprLoc)
-> ParsecT Void Text Identity (Binding NExprLoc)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> ParsecT Void Text Identity (Binding NExprLoc)
namedVar) ParsecT Void Text Identity (Binding NExprLoc)
-> Parser Text -> ParsecT Void Text Identity [Binding NExprLoc]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`endBy` Parser Text
semi where
  inherit :: ParsecT Void Text Identity (Binding NExprLoc)
inherit = do
      -- We can't use 'reserved' here because it would consume the whitespace
      -- after the keyword, which is not exactly the semantics of C++ Nix.
    Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string "inherit" Parser Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (ParsecT Void Text Identity Char -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ((Token Text -> Bool) -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
reservedEnd))
    SourcePos
p <- ParsecT Void Text Identity SourcePos
forall e s (m :: * -> *). MonadParsec e s m => m SourcePos
getSourcePos
    Maybe NExprLoc
x <- Parser ()
whiteSpace Parser ()
-> ParsecT Void Text Identity (Maybe NExprLoc)
-> ParsecT Void Text Identity (Maybe NExprLoc)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc -> ParsecT Void Text Identity (Maybe NExprLoc)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser NExprLoc
scope
    Maybe NExprLoc
-> [NKeyName NExprLoc] -> SourcePos -> Binding NExprLoc
forall r. Maybe r -> [NKeyName r] -> SourcePos -> Binding r
Inherit Maybe NExprLoc
x ([NKeyName NExprLoc] -> SourcePos -> Binding NExprLoc)
-> ParsecT Void Text Identity [NKeyName NExprLoc]
-> ParsecT Void Text Identity (SourcePos -> Binding NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (NKeyName NExprLoc)
-> ParsecT Void Text Identity [NKeyName NExprLoc]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many Parser (NKeyName NExprLoc)
keyName ParsecT Void Text Identity (SourcePos -> Binding NExprLoc)
-> ParsecT Void Text Identity SourcePos
-> ParsecT Void Text Identity (Binding NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourcePos -> ParsecT Void Text Identity SourcePos
forall (f :: * -> *) a. Applicative f => a -> f a
pure SourcePos
p ParsecT Void Text Identity (Binding NExprLoc)
-> String -> ParsecT Void Text Identity (Binding NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "inherited binding"
  namedVar :: ParsecT Void Text Identity (Binding NExprLoc)
namedVar = do
    SourcePos
p <- ParsecT Void Text Identity SourcePos
forall e s (m :: * -> *). MonadParsec e s m => m SourcePos
getSourcePos
    NAttrPath NExprLoc -> NExprLoc -> SourcePos -> Binding NExprLoc
forall r. NAttrPath r -> r -> SourcePos -> Binding r
NamedVar
      (NAttrPath NExprLoc -> NExprLoc -> SourcePos -> Binding NExprLoc)
-> Parser (NAttrPath NExprLoc)
-> ParsecT
     Void Text Identity (NExprLoc -> SourcePos -> Binding NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ann SrcSpan (NAttrPath NExprLoc) -> NAttrPath NExprLoc
forall ann a. Ann ann a -> a
annotated (Ann SrcSpan (NAttrPath NExprLoc) -> NAttrPath NExprLoc)
-> Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> Parser (NAttrPath NExprLoc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Ann SrcSpan (NAttrPath NExprLoc))
nixSelector)
      ParsecT
  Void Text Identity (NExprLoc -> SourcePos -> Binding NExprLoc)
-> Parser NExprLoc
-> ParsecT Void Text Identity (SourcePos -> Binding NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser Text
equals Parser Text -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm)
      ParsecT Void Text Identity (SourcePos -> Binding NExprLoc)
-> ParsecT Void Text Identity SourcePos
-> ParsecT Void Text Identity (Binding NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourcePos -> ParsecT Void Text Identity SourcePos
forall (f :: * -> *) a. Applicative f => a -> f a
pure SourcePos
p
      ParsecT Void Text Identity (Binding NExprLoc)
-> String -> ParsecT Void Text Identity (Binding NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "variable binding"
  scope :: Parser NExprLoc
scope = Parser NExprLoc -> Parser NExprLoc
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
parens Parser NExprLoc
nixToplevelForm Parser NExprLoc -> String -> Parser NExprLoc
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "inherit scope"

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

nixSet :: Parser NExprLoc
nixSet :: Parser NExprLoc
nixSet = Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 ((ParsecT Void Text Identity ([Binding NExprLoc] -> NExprF NExprLoc)
forall r. ParsecT Void Text Identity ([Binding r] -> NExprF r)
isRec ParsecT Void Text Identity ([Binding NExprLoc] -> NExprF NExprLoc)
-> ParsecT Void Text Identity [Binding NExprLoc]
-> Parser (NExprF NExprLoc)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Void Text Identity [Binding NExprLoc]
-> ParsecT Void Text Identity [Binding NExprLoc]
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
braces ParsecT Void Text Identity [Binding NExprLoc]
nixBinders) Parser (NExprF NExprLoc) -> String -> Parser (NExprF NExprLoc)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "set")
  where isRec :: ParsecT Void Text Identity ([Binding r] -> NExprF r)
isRec = (Text -> Parser ()
reserved "rec" Parser ()
-> ([Binding r] -> NExprF r)
-> ParsecT Void Text Identity ([Binding r] -> NExprF r)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> NRecordType -> [Binding r] -> NExprF r
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NRecursive ParsecT Void Text Identity ([Binding r] -> NExprF r)
-> String -> ParsecT Void Text Identity ([Binding r] -> NExprF r)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> "recursive set") ParsecT Void Text Identity ([Binding r] -> NExprF r)
-> ParsecT Void Text Identity ([Binding r] -> NExprF r)
-> ParsecT Void Text Identity ([Binding r] -> NExprF r)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
<+> ([Binding r] -> NExprF r)
-> ParsecT Void Text Identity ([Binding r] -> NExprF r)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NRecordType -> [Binding r] -> NExprF r
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NNonRecursive)

parseNixFile :: MonadFile m => FilePath -> m (Result NExpr)
parseNixFile :: String -> m (Result NExpr)
parseNixFile =
  Parser NExpr -> String -> m (Result NExpr)
forall (m :: * -> *) a.
MonadFile m =>
Parser a -> String -> m (Result a)
parseFromFileEx (Parser NExpr -> String -> m (Result NExpr))
-> Parser NExpr -> String -> m (Result NExpr)
forall a b. (a -> b) -> a -> b
$ NExprLoc -> NExpr
forall (f :: * -> *) ann. Functor f => Fix (AnnF ann f) -> Fix f
stripAnnotation (NExprLoc -> NExpr) -> Parser NExprLoc -> Parser NExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser ()
whiteSpace Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm Parser NExprLoc -> Parser () -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)

parseNixFileLoc :: MonadFile m => FilePath -> m (Result NExprLoc)
parseNixFileLoc :: String -> m (Result NExprLoc)
parseNixFileLoc = Parser NExprLoc -> String -> m (Result NExprLoc)
forall (m :: * -> *) a.
MonadFile m =>
Parser a -> String -> m (Result a)
parseFromFileEx (Parser ()
whiteSpace Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm Parser NExprLoc -> Parser () -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)

parseNixText :: Text -> Result NExpr
parseNixText :: Text -> Result NExpr
parseNixText =
  Parser NExpr -> Text -> Result NExpr
forall a. Parser a -> Text -> Result a
parseFromText (Parser NExpr -> Text -> Result NExpr)
-> Parser NExpr -> Text -> Result NExpr
forall a b. (a -> b) -> a -> b
$ NExprLoc -> NExpr
forall (f :: * -> *) ann. Functor f => Fix (AnnF ann f) -> Fix f
stripAnnotation (NExprLoc -> NExpr) -> Parser NExprLoc -> Parser NExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser ()
whiteSpace Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm Parser NExprLoc -> Parser () -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)

parseNixTextLoc :: Text -> Result NExprLoc
parseNixTextLoc :: Text -> Result NExprLoc
parseNixTextLoc = Parser NExprLoc -> Text -> Result NExprLoc
forall a. Parser a -> Text -> Result a
parseFromText (Parser ()
whiteSpace Parser () -> Parser NExprLoc -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser NExprLoc
nixToplevelForm Parser NExprLoc -> Parser () -> Parser NExprLoc
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)

{- Parser.Library -}

skipLineComment' :: Tokens Text -> Parser ()
skipLineComment' :: Tokens Text -> Parser ()
skipLineComment' prefix :: Tokens Text
prefix = Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens Text
prefix
  Parser Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (String -> Maybe String
forall a. a -> Maybe a
Just "character") (\x :: Token Text
x -> Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= '\n' Bool -> Bool -> Bool
&& Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= '\r'))

whiteSpace :: Parser ()
whiteSpace :: Parser ()
whiteSpace = Parser () -> Parser () -> Parser () -> Parser ()
forall e s (m :: * -> *).
MonadParsec e s m =>
m () -> m () -> m () -> m ()
L.space Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
space1 Parser ()
lineCmnt Parser ()
blockCmnt
 where
  lineCmnt :: Parser ()
lineCmnt  = Tokens Text -> Parser ()
skipLineComment' "#"
  blockCmnt :: Parser ()
blockCmnt = Tokens Text -> Tokens Text -> Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Tokens s -> Tokens s -> m ()
L.skipBlockComment "/*" "*/"

lexeme :: Parser a -> Parser a
lexeme :: Parser a -> Parser a
lexeme p :: Parser a
p = Parser a
p Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
whiteSpace

symbol :: Text -> Parser Text
symbol :: Text -> Parser Text
symbol = Parser Text -> Parser Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser Text -> Parser Text)
-> (Text -> Parser Text) -> Text -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Parser Text
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string

reservedEnd :: Char -> Bool
reservedEnd :: Char -> Bool
reservedEnd x :: Char
x =
  Char -> Bool
isSpace Char
x
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '{'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '('
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '['
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '}'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ')'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ']'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ';'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ':'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '.'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '"'
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '\''
    Bool -> Bool -> Bool
|| Char
x
    Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ','

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

identifier :: Parser Text
identifier = Parser Text -> Parser Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ Parser Text -> Parser Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ do
  Text
ident <-
    Char -> Text -> Text
cons
    (Char -> Text -> Text)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token Text -> Bool) -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy (\x :: Token Text
x -> Char -> Bool
isAlpha Char
Token Text
x Bool -> Bool -> Bool
|| Char
Token Text
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '_')
    ParsecT Void Text Identity (Text -> Text)
-> Parser Text -> Parser Text
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe String
forall a. Maybe a
Nothing Char -> Bool
Token Text -> Bool
identLetter
  Bool -> Parser ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (Text
ident Text -> HashSet Text -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HashSet.member` HashSet Text
reservedNames))
  Text -> Parser Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
ident
 where
  identLetter :: Char -> Bool
identLetter x :: Char
x = Char -> Bool
isAlpha Char
x Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
x Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '_' Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '\'' Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '-'

parens :: ParsecT Void Text Identity a -> ParsecT Void Text Identity a
parens = Parser Text
-> Parser Text
-> ParsecT Void Text Identity a
-> ParsecT Void Text Identity a
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Text -> Parser Text
symbol "(") (Text -> Parser Text
symbol ")")
braces :: ParsecT Void Text Identity a -> ParsecT Void Text Identity a
braces = Parser Text
-> Parser Text
-> ParsecT Void Text Identity a
-> ParsecT Void Text Identity a
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Text -> Parser Text
symbol "{") (Text -> Parser Text
symbol "}")
-- angles    = between (symbol "<") (symbol ">")
brackets :: ParsecT Void Text Identity a -> ParsecT Void Text Identity a
brackets = Parser Text
-> Parser Text
-> ParsecT Void Text Identity a
-> ParsecT Void Text Identity a
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Text -> Parser Text
symbol "[") (Text -> Parser Text
symbol "]")
semi :: Parser Text
semi = Text -> Parser Text
symbol ";"
comma :: Parser Text
comma = Text -> Parser Text
symbol ","
-- colon     = symbol ":"
-- dot       = symbol "."
equals :: Parser Text
equals = Text -> Parser Text
symbol "="
question :: Parser Text
question = Text -> Parser Text
symbol "?"

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

float :: Parser Double
float :: ParsecT Void Text Identity Double
float = ParsecT Void Text Identity Double
-> ParsecT Void Text Identity Double
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme ParsecT Void Text Identity Double
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, RealFloat a) =>
m a
L.float

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

type Parser = ParsecT Void Text Identity

data Result a = Success a | Failure (Doc Void) deriving (Int -> Result a -> String -> String
[Result a] -> String -> String
Result a -> String
(Int -> Result a -> String -> String)
-> (Result a -> String)
-> ([Result a] -> String -> String)
-> Show (Result a)
forall a. Show a => Int -> Result a -> String -> String
forall a. Show a => [Result a] -> String -> String
forall a. Show a => Result a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Result a] -> String -> String
$cshowList :: forall a. Show a => [Result a] -> String -> String
show :: Result a -> String
$cshow :: forall a. Show a => Result a -> String
showsPrec :: Int -> Result a -> String -> String
$cshowsPrec :: forall a. Show a => Int -> Result a -> String -> String
Show, a -> Result b -> Result a
(a -> b) -> Result a -> Result b
(forall a b. (a -> b) -> Result a -> Result b)
-> (forall a b. a -> Result b -> Result a) -> Functor Result
forall a b. a -> Result b -> Result a
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Result b -> Result a
$c<$ :: forall a b. a -> Result b -> Result a
fmap :: (a -> b) -> Result a -> Result b
$cfmap :: forall a b. (a -> b) -> Result a -> Result b
Functor)

parseFromFileEx :: MonadFile m => Parser a -> FilePath -> m (Result a)
parseFromFileEx :: Parser a -> String -> m (Result a)
parseFromFileEx p :: Parser a
p path :: String
path = do
  Text
txt <- ByteString -> Text
decodeUtf8 (ByteString -> Text) -> m ByteString -> m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> m ByteString
forall (m :: * -> *). MonadFile m => String -> m ByteString
readFile String
path
  Result a -> m (Result a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Result a -> m (Result a)) -> Result a -> m (Result a)
forall a b. (a -> b) -> a -> b
$ (ParseErrorBundle Text Void -> Result a)
-> (a -> Result a)
-> Either (ParseErrorBundle Text Void) a
-> Result a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Doc Void -> Result a
forall a. Doc Void -> Result a
Failure (Doc Void -> Result a)
-> (ParseErrorBundle Text Void -> Doc Void)
-> ParseErrorBundle Text Void
-> Result a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc Void
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc Void)
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> Doc Void
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(Stream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty) a -> Result a
forall a. a -> Result a
Success (Either (ParseErrorBundle Text Void) a -> Result a)
-> Either (ParseErrorBundle Text Void) a -> Result a
forall a b. (a -> b) -> a -> b
$ Parser a -> String -> Text -> Either (ParseErrorBundle Text Void) a
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
parse Parser a
p
                                                                         String
path
                                                                         Text
txt

parseFromText :: Parser a -> Text -> Result a
parseFromText :: Parser a -> Text -> Result a
parseFromText p :: Parser a
p txt :: Text
txt =
  (ParseErrorBundle Text Void -> Result a)
-> (a -> Result a)
-> Either (ParseErrorBundle Text Void) a
-> Result a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Doc Void -> Result a
forall a. Doc Void -> Result a
Failure (Doc Void -> Result a)
-> (ParseErrorBundle Text Void -> Doc Void)
-> ParseErrorBundle Text Void
-> Result a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc Void
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc Void)
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> Doc Void
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(Stream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty) a -> Result a
forall a. a -> Result a
Success (Either (ParseErrorBundle Text Void) a -> Result a)
-> Either (ParseErrorBundle Text Void) a -> Result a
forall a b. (a -> b) -> a -> b
$ Parser a -> String -> Text -> Either (ParseErrorBundle Text Void) a
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
parse Parser a
p "<string>" Text
txt

{- Parser.Operators -}

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

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

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

annotateLocation :: Parser a -> Parser (Ann SrcSpan a)
annotateLocation :: Parser a -> Parser (Ann SrcSpan a)
annotateLocation p :: Parser a
p = do
  SourcePos
begin <- ParsecT Void Text Identity SourcePos
forall e s (m :: * -> *). MonadParsec e s m => m SourcePos
getSourcePos
  a
res   <- Parser a
p
  SourcePos
end   <- ParsecT Void Text Identity SourcePos
forall e s (m :: * -> *). MonadParsec e s m => m SourcePos
getSourcePos
  Ann SrcSpan a -> Parser (Ann SrcSpan a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ann SrcSpan a -> Parser (Ann SrcSpan a))
-> Ann SrcSpan a -> Parser (Ann SrcSpan a)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> a -> Ann SrcSpan a
forall ann a. ann -> a -> Ann ann a
Ann (SourcePos -> SourcePos -> SrcSpan
SrcSpan SourcePos
begin SourcePos
end) a
res

annotateLocation1 :: Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 :: Parser (NExprF NExprLoc) -> Parser NExprLoc
annotateLocation1 = (Ann SrcSpan (NExprF NExprLoc) -> NExprLoc)
-> ParsecT Void Text Identity (Ann SrcSpan (NExprF NExprLoc))
-> Parser NExprLoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ann SrcSpan (NExprF NExprLoc) -> NExprLoc
forall ann (f :: * -> *).
Ann ann (f (Fix (AnnF ann f))) -> Fix (AnnF ann f)
annToAnnF (ParsecT Void Text Identity (Ann SrcSpan (NExprF NExprLoc))
 -> Parser NExprLoc)
-> (Parser (NExprF NExprLoc)
    -> ParsecT Void Text Identity (Ann SrcSpan (NExprF NExprLoc)))
-> Parser (NExprF NExprLoc)
-> Parser NExprLoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser (NExprF NExprLoc)
-> ParsecT Void Text Identity (Ann SrcSpan (NExprF NExprLoc))
forall a. Parser a -> Parser (Ann SrcSpan a)
annotateLocation

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

operator :: Text -> Parser Text
operator "-" = Parser Text -> Parser Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser Text -> Parser Text)
-> (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser Text -> Parser Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string "-" Parser Text -> Parser () -> Parser Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Char -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'>')
operator "/" = Parser Text -> Parser Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser Text -> Parser Text)
-> (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser Text -> Parser Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string "/" Parser Text -> Parser () -> Parser Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Char -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'/')
operator "<" = Parser Text -> Parser Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser Text -> Parser Text)
-> (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser Text -> Parser Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string "<" Parser Text -> Parser () -> Parser Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Char -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'=')
operator ">" = Parser Text -> Parser Text
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
lexeme (Parser Text -> Parser Text)
-> (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser Text -> Parser Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser Text -> Parser Text) -> Parser Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string ">" Parser Text -> Parser () -> Parser Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Char -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Token Text
'=')
operator n :: Text
n   = Text -> Parser Text
symbol Text
n

opWithLoc :: Text -> o -> (Ann SrcSpan o -> a) -> Parser a
opWithLoc :: Text -> o -> (Ann SrcSpan o -> a) -> Parser a
opWithLoc name :: Text
name op :: o
op f :: Ann SrcSpan o -> a
f = do
  Ann ann :: SrcSpan
ann _ <- Parser Text -> Parser (Ann SrcSpan Text)
forall a. Parser a -> Parser (Ann SrcSpan a)
annotateLocation (Parser Text -> Parser (Ann SrcSpan Text))
-> Parser Text -> Parser (Ann SrcSpan Text)
forall a b. (a -> b) -> a -> b
$ {- dbg (unpack name) $ -}
                                  Text -> Parser Text
operator Text
name
  a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Parser a) -> a -> Parser a
forall a b. (a -> b) -> a -> b
$ Ann SrcSpan o -> a
f (SrcSpan -> o -> Ann SrcSpan o
forall ann a. ann -> a -> Ann ann a
Ann SrcSpan
ann o
op)

binaryN :: Text
-> NBinaryOp
-> (NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)
binaryN name :: Text
name op :: NBinaryOp
op =
  (Text -> NBinaryOp -> NAssoc -> NOperatorDef
NBinaryDef Text
name NBinaryOp
op NAssoc
NAssocNone, ParsecT Void Text Identity (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator (ParsecT Void Text Identity) NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixN (Text
-> NBinaryOp
-> (Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc)
-> ParsecT Void Text Identity (NExprLoc -> NExprLoc -> NExprLoc)
forall o a. Text -> o -> (Ann SrcSpan o -> a) -> Parser a
opWithLoc Text
name NBinaryOp
op Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
nBinary))
binaryL :: Text
-> NBinaryOp
-> (NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)
binaryL name :: Text
name op :: NBinaryOp
op =
  (Text -> NBinaryOp -> NAssoc -> NOperatorDef
NBinaryDef Text
name NBinaryOp
op NAssoc
NAssocLeft, ParsecT Void Text Identity (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator (ParsecT Void Text Identity) NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixL (Text
-> NBinaryOp
-> (Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc)
-> ParsecT Void Text Identity (NExprLoc -> NExprLoc -> NExprLoc)
forall o a. Text -> o -> (Ann SrcSpan o -> a) -> Parser a
opWithLoc Text
name NBinaryOp
op Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
nBinary))
binaryR :: Text
-> NBinaryOp
-> (NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)
binaryR name :: Text
name op :: NBinaryOp
op =
  (Text -> NBinaryOp -> NAssoc -> NOperatorDef
NBinaryDef Text
name NBinaryOp
op NAssoc
NAssocRight, ParsecT Void Text Identity (NExprLoc -> NExprLoc -> NExprLoc)
-> Operator (ParsecT Void Text Identity) NExprLoc
forall (m :: * -> *) a. m (a -> a -> a) -> Operator m a
InfixR (Text
-> NBinaryOp
-> (Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc)
-> ParsecT Void Text Identity (NExprLoc -> NExprLoc -> NExprLoc)
forall o a. Text -> o -> (Ann SrcSpan o -> a) -> Parser a
opWithLoc Text
name NBinaryOp
op Ann SrcSpan NBinaryOp -> NExprLoc -> NExprLoc -> NExprLoc
nBinary))
prefix :: Text
-> NUnaryOp
-> (NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)
prefix name :: Text
name op :: NUnaryOp
op =
  (Text -> NUnaryOp -> NOperatorDef
NUnaryDef Text
name NUnaryOp
op, ParsecT Void Text Identity (NExprLoc -> NExprLoc)
-> Operator (ParsecT Void Text Identity) NExprLoc
forall (m :: * -> *) a. m (a -> a) -> Operator m a
Prefix (ParsecT Void Text Identity (NExprLoc -> NExprLoc)
-> ParsecT Void Text Identity (NExprLoc -> NExprLoc)
forall (f :: * -> *) a. MonadPlus f => f (a -> a) -> f (a -> a)
manyUnaryOp (Text
-> NUnaryOp
-> (Ann SrcSpan NUnaryOp -> NExprLoc -> NExprLoc)
-> ParsecT Void Text Identity (NExprLoc -> NExprLoc)
forall o a. Text -> o -> (Ann SrcSpan o -> a) -> Parser a
opWithLoc Text
name NUnaryOp
op Ann SrcSpan NUnaryOp -> NExprLoc -> NExprLoc
nUnary)))
-- postfix name op = (NUnaryDef name op,
--                    Postfix (opWithLoc name op nUnary))

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

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

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

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

getUnaryOperator :: NUnaryOp -> OperatorInfo
getUnaryOperator :: NUnaryOp -> OperatorInfo
getUnaryOperator = (Map NUnaryOp OperatorInfo
m Map NUnaryOp OperatorInfo -> NUnaryOp -> OperatorInfo
forall k a. Ord k => Map k a -> k -> a
Map.!) where
  m :: Map NUnaryOp OperatorInfo
m = [(NUnaryOp, OperatorInfo)] -> Map NUnaryOp OperatorInfo
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(NUnaryOp, OperatorInfo)] -> Map NUnaryOp OperatorInfo)
-> [(NUnaryOp, OperatorInfo)] -> Map NUnaryOp OperatorInfo
forall a b. (a -> b) -> a -> b
$ [[(NUnaryOp, OperatorInfo)]] -> [(NUnaryOp, OperatorInfo)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(NUnaryOp, OperatorInfo)]] -> [(NUnaryOp, OperatorInfo)])
-> [[(NUnaryOp, OperatorInfo)]] -> [(NUnaryOp, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$ (Int
 -> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
 -> [(NUnaryOp, OperatorInfo)])
-> [Int]
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
-> [[(NUnaryOp, OperatorInfo)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int
-> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
-> [(NUnaryOp, OperatorInfo)]
forall (t :: * -> *) b.
Foldable t =>
Int -> t (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)]
buildEntry
                                      [1 ..]
                                      (Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
nixOperators (String -> Parser (Ann SrcSpan (NAttrPath NExprLoc))
forall a. HasCallStack => String -> a
error "unused"))
  buildEntry :: Int -> t (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)]
buildEntry i :: Int
i = ((NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)])
-> t (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)])
 -> t (NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)])
-> ((NOperatorDef, b) -> [(NUnaryOp, OperatorInfo)])
-> t (NOperatorDef, b)
-> [(NUnaryOp, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$ \case
    (NUnaryDef name :: Text
name op :: NUnaryOp
op, _) -> [(NUnaryOp
op, Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
i NAssoc
NAssocNone Text
name)]
    _                      -> []

getBinaryOperator :: NBinaryOp -> OperatorInfo
getBinaryOperator :: NBinaryOp -> OperatorInfo
getBinaryOperator = (Map NBinaryOp OperatorInfo
m Map NBinaryOp OperatorInfo -> NBinaryOp -> OperatorInfo
forall k a. Ord k => Map k a -> k -> a
Map.!) where
  m :: Map NBinaryOp OperatorInfo
m = [(NBinaryOp, OperatorInfo)] -> Map NBinaryOp OperatorInfo
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(NBinaryOp, OperatorInfo)] -> Map NBinaryOp OperatorInfo)
-> [(NBinaryOp, OperatorInfo)] -> Map NBinaryOp OperatorInfo
forall a b. (a -> b) -> a -> b
$ [[(NBinaryOp, OperatorInfo)]] -> [(NBinaryOp, OperatorInfo)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(NBinaryOp, OperatorInfo)]] -> [(NBinaryOp, OperatorInfo)])
-> [[(NBinaryOp, OperatorInfo)]] -> [(NBinaryOp, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$ (Int
 -> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
 -> [(NBinaryOp, OperatorInfo)])
-> [Int]
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
-> [[(NBinaryOp, OperatorInfo)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int
-> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
-> [(NBinaryOp, OperatorInfo)]
forall (t :: * -> *) b.
Foldable t =>
Int -> t (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)]
buildEntry
                                      [1 ..]
                                      (Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
nixOperators (String -> Parser (Ann SrcSpan (NAttrPath NExprLoc))
forall a. HasCallStack => String -> a
error "unused"))
  buildEntry :: Int -> t (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)]
buildEntry i :: Int
i = ((NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)])
-> t (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)])
 -> t (NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)])
-> ((NOperatorDef, b) -> [(NBinaryOp, OperatorInfo)])
-> t (NOperatorDef, b)
-> [(NBinaryOp, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$ \case
    (NBinaryDef name :: Text
name op :: NBinaryOp
op assoc :: NAssoc
assoc, _) -> [(NBinaryOp
op, Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
i NAssoc
assoc Text
name)]
    _                             -> []

getSpecialOperator :: NSpecialOp -> OperatorInfo
getSpecialOperator :: NSpecialOp -> OperatorInfo
getSpecialOperator NSelectOp = Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo 1 NAssoc
NAssocLeft "."
getSpecialOperator o :: NSpecialOp
o         = Map NSpecialOp OperatorInfo
m Map NSpecialOp OperatorInfo -> NSpecialOp -> OperatorInfo
forall k a. Ord k => Map k a -> k -> a
Map.! NSpecialOp
o where
  m :: Map NSpecialOp OperatorInfo
m = [(NSpecialOp, OperatorInfo)] -> Map NSpecialOp OperatorInfo
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(NSpecialOp, OperatorInfo)] -> Map NSpecialOp OperatorInfo)
-> [(NSpecialOp, OperatorInfo)] -> Map NSpecialOp OperatorInfo
forall a b. (a -> b) -> a -> b
$ [[(NSpecialOp, OperatorInfo)]] -> [(NSpecialOp, OperatorInfo)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(NSpecialOp, OperatorInfo)]] -> [(NSpecialOp, OperatorInfo)])
-> [[(NSpecialOp, OperatorInfo)]] -> [(NSpecialOp, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$ (Int
 -> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
 -> [(NSpecialOp, OperatorInfo)])
-> [Int]
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
-> [[(NSpecialOp, OperatorInfo)]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int
-> [(NOperatorDef, Operator (ParsecT Void Text Identity) NExprLoc)]
-> [(NSpecialOp, OperatorInfo)]
forall (t :: * -> *) b.
Foldable t =>
Int -> t (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)]
buildEntry
                                      [1 ..]
                                      (Parser (Ann SrcSpan (NAttrPath NExprLoc))
-> [[(NOperatorDef,
      Operator (ParsecT Void Text Identity) NExprLoc)]]
nixOperators (String -> Parser (Ann SrcSpan (NAttrPath NExprLoc))
forall a. HasCallStack => String -> a
error "unused"))
  buildEntry :: Int -> t (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)]
buildEntry i :: Int
i = ((NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)])
-> t (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)])
 -> t (NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)])
-> ((NOperatorDef, b) -> [(NSpecialOp, OperatorInfo)])
-> t (NOperatorDef, b)
-> [(NSpecialOp, OperatorInfo)]
forall a b. (a -> b) -> a -> b
$ \case
    (NSpecialDef name :: Text
name op :: NSpecialOp
op assoc :: NAssoc
assoc, _) -> [(NSpecialOp
op, Int -> NAssoc -> Text -> OperatorInfo
OperatorInfo Int
i NAssoc
assoc Text
name)]
    _                              -> []