{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Nix.Expr.Shorthands where
import Data.Fix
import Data.List.NonEmpty ( NonEmpty(..) )
import Data.Text ( Text )
import Nix.Atoms
import Nix.Expr.Types
import Text.Megaparsec.Pos ( SourcePos )
mkInt :: Integer -> NExpr
mkInt :: Integer -> NExpr
mkInt = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (Integer -> NExprF NExpr) -> Integer -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> NExprF NExpr
forall a. Integer -> NExprF a
mkIntF
mkIntF :: Integer -> NExprF a
mkIntF :: Integer -> NExprF a
mkIntF = NAtom -> NExprF a
forall r. NAtom -> NExprF r
NConstant (NAtom -> NExprF a) -> (Integer -> NAtom) -> Integer -> NExprF a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> NAtom
NInt
mkFloat :: Float -> NExpr
mkFloat :: Float -> NExpr
mkFloat = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (Float -> NExprF NExpr) -> Float -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> NExprF NExpr
forall a. Float -> NExprF a
mkFloatF
mkFloatF :: Float -> NExprF a
mkFloatF :: Float -> NExprF a
mkFloatF = NAtom -> NExprF a
forall r. NAtom -> NExprF r
NConstant (NAtom -> NExprF a) -> (Float -> NAtom) -> Float -> NExprF a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> NAtom
NFloat
mkStr :: Text -> NExpr
mkStr :: Text -> NExpr
mkStr = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> (Text -> NExprF NExpr) -> Text -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NString NExpr -> NExprF NExpr
forall r. NString r -> NExprF r
NStr (NString NExpr -> NExprF NExpr)
-> (Text -> NString NExpr) -> Text -> NExprF NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text NExpr] -> NString NExpr
forall r. [Antiquoted Text r] -> NString r
DoubleQuoted ([Antiquoted Text NExpr] -> NString NExpr)
-> (Text -> [Antiquoted Text NExpr]) -> Text -> NString NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
"" -> []
x :: Text
x -> [Text -> Antiquoted Text NExpr
forall v r. v -> Antiquoted v r
Plain Text
x]
mkIndentedStr :: Int -> Text -> NExpr
mkIndentedStr :: Int -> Text -> NExpr
mkIndentedStr w :: Int
w = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> (Text -> NExprF NExpr) -> Text -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NString NExpr -> NExprF NExpr
forall r. NString r -> NExprF r
NStr (NString NExpr -> NExprF NExpr)
-> (Text -> NString NExpr) -> Text -> NExprF NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Antiquoted Text NExpr] -> NString NExpr
forall r. Int -> [Antiquoted Text r] -> NString r
Indented Int
w ([Antiquoted Text NExpr] -> NString NExpr)
-> (Text -> [Antiquoted Text NExpr]) -> Text -> NString NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
"" -> []
x :: Text
x -> [Text -> Antiquoted Text NExpr
forall v r. v -> Antiquoted v r
Plain Text
x]
mkPath :: Bool -> FilePath -> NExpr
mkPath :: Bool -> FilePath -> NExpr
mkPath b :: Bool
b = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (FilePath -> NExprF NExpr) -> FilePath -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> FilePath -> NExprF NExpr
forall a. Bool -> FilePath -> NExprF a
mkPathF Bool
b
mkPathF :: Bool -> FilePath -> NExprF a
mkPathF :: Bool -> FilePath -> NExprF a
mkPathF False = FilePath -> NExprF a
forall r. FilePath -> NExprF r
NLiteralPath
mkPathF True = FilePath -> NExprF a
forall r. FilePath -> NExprF r
NEnvPath
mkEnvPath :: FilePath -> NExpr
mkEnvPath :: FilePath -> NExpr
mkEnvPath = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (FilePath -> NExprF NExpr) -> FilePath -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> NExprF NExpr
forall r. FilePath -> NExprF r
mkEnvPathF
mkEnvPathF :: FilePath -> NExprF a
mkEnvPathF :: FilePath -> NExprF a
mkEnvPathF = Bool -> FilePath -> NExprF a
forall a. Bool -> FilePath -> NExprF a
mkPathF Bool
True
mkRelPath :: FilePath -> NExpr
mkRelPath :: FilePath -> NExpr
mkRelPath = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (FilePath -> NExprF NExpr) -> FilePath -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> NExprF NExpr
forall r. FilePath -> NExprF r
mkRelPathF
mkRelPathF :: FilePath -> NExprF a
mkRelPathF :: FilePath -> NExprF a
mkRelPathF = Bool -> FilePath -> NExprF a
forall a. Bool -> FilePath -> NExprF a
mkPathF Bool
False
mkSym :: Text -> NExpr
mkSym :: Text -> NExpr
mkSym = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> (Text -> NExprF NExpr) -> Text -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> NExprF NExpr
forall a. Text -> NExprF a
mkSymF
mkSymF :: Text -> NExprF a
mkSymF :: Text -> NExprF a
mkSymF = Text -> NExprF a
forall a. Text -> NExprF a
NSym
mkSynHole :: Text -> NExpr
mkSynHole :: Text -> NExpr
mkSynHole = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> (Text -> NExprF NExpr) -> Text -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> NExprF NExpr
forall a. Text -> NExprF a
mkSynHoleF
mkSynHoleF :: Text -> NExprF a
mkSynHoleF :: Text -> NExprF a
mkSynHoleF = Text -> NExprF a
forall a. Text -> NExprF a
NSynHole
mkSelector :: Text -> NAttrPath NExpr
mkSelector :: Text -> NAttrPath NExpr
mkSelector = (NKeyName NExpr -> [NKeyName NExpr] -> NAttrPath NExpr
forall a. a -> [a] -> NonEmpty a
:| []) (NKeyName NExpr -> NAttrPath NExpr)
-> (Text -> NKeyName NExpr) -> Text -> NAttrPath NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> NKeyName NExpr
forall r. Text -> NKeyName r
StaticKey
mkBool :: Bool -> NExpr
mkBool :: Bool -> NExpr
mkBool = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> (Bool -> NExprF NExpr) -> Bool -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> NExprF NExpr
forall a. Bool -> NExprF a
mkBoolF
mkBoolF :: Bool -> NExprF a
mkBoolF :: Bool -> NExprF a
mkBoolF = NAtom -> NExprF a
forall r. NAtom -> NExprF r
NConstant (NAtom -> NExprF a) -> (Bool -> NAtom) -> Bool -> NExprF a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> NAtom
NBool
mkNull :: NExpr
mkNull :: NExpr
mkNull = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix NExprF NExpr
forall a. NExprF a
mkNullF
mkNullF :: NExprF a
mkNullF :: NExprF a
mkNullF = NAtom -> NExprF a
forall r. NAtom -> NExprF r
NConstant NAtom
NNull
mkOper :: NUnaryOp -> NExpr -> NExpr
mkOper :: NUnaryOp -> NExpr -> NExpr
mkOper op :: NUnaryOp
op = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NUnaryOp -> NExpr -> NExprF NExpr
forall r. NUnaryOp -> r -> NExprF r
NUnary NUnaryOp
op
mkOper2 :: NBinaryOp -> NExpr -> NExpr -> NExpr
mkOper2 :: NBinaryOp -> NExpr -> NExpr -> NExpr
mkOper2 op :: NBinaryOp
op a :: NExpr
a = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NBinaryOp -> NExpr -> NExpr -> NExprF NExpr
forall r. NBinaryOp -> r -> r -> NExprF r
NBinary NBinaryOp
op NExpr
a
mkParamset :: [(Text, Maybe NExpr)] -> Bool -> Params NExpr
mkParamset :: [(Text, Maybe NExpr)] -> Bool -> Params NExpr
mkParamset params :: [(Text, Maybe NExpr)]
params variadic :: Bool
variadic = [(Text, Maybe NExpr)] -> Bool -> Maybe Text -> Params NExpr
forall r. ParamSet r -> Bool -> Maybe Text -> Params r
ParamSet [(Text, Maybe NExpr)]
params Bool
variadic Maybe Text
forall a. Maybe a
Nothing
mkRecSet :: [Binding NExpr] -> NExpr
mkRecSet :: [Binding NExpr] -> NExpr
mkRecSet = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> ([Binding NExpr] -> NExprF NExpr) -> [Binding NExpr] -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NRecordType -> [Binding NExpr] -> NExprF NExpr
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NRecursive
mkNonRecSet :: [Binding NExpr] -> NExpr
mkNonRecSet :: [Binding NExpr] -> NExpr
mkNonRecSet = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> ([Binding NExpr] -> NExprF NExpr) -> [Binding NExpr] -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NRecordType -> [Binding NExpr] -> NExprF NExpr
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NNonRecursive
mkLets :: [Binding NExpr] -> NExpr -> NExpr
mkLets :: [Binding NExpr] -> NExpr -> NExpr
mkLets bindings :: [Binding NExpr]
bindings = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Binding NExpr] -> NExpr -> NExprF NExpr
forall r. [Binding r] -> r -> NExprF r
NLet [Binding NExpr]
bindings
mkList :: [NExpr] -> NExpr
mkList :: [NExpr] -> NExpr
mkList = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> ([NExpr] -> NExprF NExpr) -> [NExpr] -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NExpr] -> NExprF NExpr
forall r. [r] -> NExprF r
NList
mkWith :: NExpr -> NExpr -> NExpr
mkWith :: NExpr -> NExpr -> NExpr
mkWith e :: NExpr
e = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NExpr -> NExpr -> NExprF NExpr
forall r. r -> r -> NExprF r
NWith NExpr
e
mkAssert :: NExpr -> NExpr -> NExpr
mkAssert :: NExpr -> NExpr -> NExpr
mkAssert e :: NExpr
e = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NExpr -> NExpr -> NExprF NExpr
forall r. r -> r -> NExprF r
NWith NExpr
e
mkIf :: NExpr -> NExpr -> NExpr -> NExpr
mkIf :: NExpr -> NExpr -> NExpr -> NExpr
mkIf e1 :: NExpr
e1 e2 :: NExpr
e2 = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NExpr -> NExpr -> NExpr -> NExprF NExpr
forall r. r -> r -> r -> NExprF r
NIf NExpr
e1 NExpr
e2
mkFunction :: Params NExpr -> NExpr -> NExpr
mkFunction :: Params NExpr -> NExpr -> NExpr
mkFunction params :: Params NExpr
params = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Params NExpr -> NExpr -> NExprF NExpr
forall r. Params r -> r -> NExprF r
NAbs Params NExpr
params
inherit :: [NKeyName e] -> SourcePos -> Binding e
inherit :: [NKeyName e] -> SourcePos -> Binding e
inherit = Maybe e -> [NKeyName e] -> SourcePos -> Binding e
forall r. Maybe r -> [NKeyName r] -> SourcePos -> Binding r
Inherit Maybe e
forall a. Maybe a
Nothing
inheritFrom :: e -> [NKeyName e] -> SourcePos -> Binding e
inheritFrom :: e -> [NKeyName e] -> SourcePos -> Binding e
inheritFrom expr :: e
expr = Maybe e -> [NKeyName e] -> SourcePos -> Binding e
forall r. Maybe r -> [NKeyName r] -> SourcePos -> Binding r
Inherit (e -> Maybe e
forall a. a -> Maybe a
Just e
expr)
bindTo :: Text -> NExpr -> Binding NExpr
bindTo :: Text -> NExpr -> Binding NExpr
bindTo name :: Text
name x :: NExpr
x = NAttrPath NExpr -> NExpr -> SourcePos -> Binding NExpr
forall r. NAttrPath r -> r -> SourcePos -> Binding r
NamedVar (Text -> NAttrPath NExpr
mkSelector Text
name) NExpr
x SourcePos
nullPos
($=) :: Text -> NExpr -> Binding NExpr
$= :: Text -> NExpr -> Binding NExpr
($=) = Text -> NExpr -> Binding NExpr
bindTo
infixr 2 $=
appendBindings :: [Binding NExpr] -> NExpr -> NExpr
appendBindings :: [Binding NExpr] -> NExpr -> NExpr
appendBindings newBindings :: [Binding NExpr]
newBindings (Fix e :: NExprF NExpr
e) = case NExprF NExpr
e of
NLet bindings :: [Binding NExpr]
bindings e' :: NExpr
e' -> NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> NExprF NExpr -> NExpr
forall a b. (a -> b) -> a -> b
$ [Binding NExpr] -> NExpr -> NExprF NExpr
forall r. [Binding r] -> r -> NExprF r
NLet ([Binding NExpr]
bindings [Binding NExpr] -> [Binding NExpr] -> [Binding NExpr]
forall a. Semigroup a => a -> a -> a
<> [Binding NExpr]
newBindings) NExpr
e'
NSet recur :: NRecordType
recur bindings :: [Binding NExpr]
bindings -> NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> NExprF NExpr -> NExpr
forall a b. (a -> b) -> a -> b
$ NRecordType -> [Binding NExpr] -> NExprF NExpr
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
recur ([Binding NExpr]
bindings [Binding NExpr] -> [Binding NExpr] -> [Binding NExpr]
forall a. Semigroup a => a -> a -> a
<> [Binding NExpr]
newBindings)
_ -> FilePath -> NExpr
forall a. HasCallStack => FilePath -> a
error "Can only append bindings to a set or a let"
modifyFunctionBody :: (NExpr -> NExpr) -> NExpr -> NExpr
modifyFunctionBody :: (NExpr -> NExpr) -> NExpr -> NExpr
modifyFunctionBody f :: NExpr -> NExpr
f (Fix e :: NExprF NExpr
e) = case NExprF NExpr
e of
NAbs params :: Params NExpr
params body :: NExpr
body -> NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> NExprF NExpr -> NExpr
forall a b. (a -> b) -> a -> b
$ Params NExpr -> NExpr -> NExprF NExpr
forall r. Params r -> r -> NExprF r
NAbs Params NExpr
params (NExpr -> NExpr
f NExpr
body)
_ -> FilePath -> NExpr
forall a. HasCallStack => FilePath -> a
error "Not a function"
letsE :: [(Text, NExpr)] -> NExpr -> NExpr
letsE :: [(Text, NExpr)] -> NExpr -> NExpr
letsE pairs :: [(Text, NExpr)]
pairs = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Binding NExpr] -> NExpr -> NExprF NExpr
forall r. [Binding r] -> r -> NExprF r
NLet (((Text, NExpr) -> Binding NExpr)
-> [(Text, NExpr)] -> [Binding NExpr]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> NExpr -> Binding NExpr) -> (Text, NExpr) -> Binding NExpr
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> NExpr -> Binding NExpr
bindTo) [(Text, NExpr)]
pairs)
letE :: Text -> NExpr -> NExpr -> NExpr
letE :: Text -> NExpr -> NExpr -> NExpr
letE varName :: Text
varName varExpr :: NExpr
varExpr = [(Text, NExpr)] -> NExpr -> NExpr
letsE [(Text
varName, NExpr
varExpr)]
attrsE :: [(Text, NExpr)] -> NExpr
attrsE :: [(Text, NExpr)] -> NExpr
attrsE pairs :: [(Text, NExpr)]
pairs = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> NExprF NExpr -> NExpr
forall a b. (a -> b) -> a -> b
$ NRecordType -> [Binding NExpr] -> NExprF NExpr
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NNonRecursive (((Text, NExpr) -> Binding NExpr)
-> [(Text, NExpr)] -> [Binding NExpr]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> NExpr -> Binding NExpr) -> (Text, NExpr) -> Binding NExpr
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> NExpr -> Binding NExpr
bindTo) [(Text, NExpr)]
pairs)
recAttrsE :: [(Text, NExpr)] -> NExpr
recAttrsE :: [(Text, NExpr)] -> NExpr
recAttrsE pairs :: [(Text, NExpr)]
pairs = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr) -> NExprF NExpr -> NExpr
forall a b. (a -> b) -> a -> b
$ NRecordType -> [Binding NExpr] -> NExprF NExpr
forall r. NRecordType -> [Binding r] -> NExprF r
NSet NRecordType
NRecursive (((Text, NExpr) -> Binding NExpr)
-> [(Text, NExpr)] -> [Binding NExpr]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> NExpr -> Binding NExpr) -> (Text, NExpr) -> Binding NExpr
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> NExpr -> Binding NExpr
bindTo) [(Text, NExpr)]
pairs)
mkNot :: NExpr -> NExpr
mkNot :: NExpr -> NExpr
mkNot = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExprF NExpr -> NExpr)
-> (NExpr -> NExprF NExpr) -> NExpr -> NExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NUnaryOp -> NExpr -> NExprF NExpr
forall r. NUnaryOp -> r -> NExprF r
NUnary NUnaryOp
NNot
mkBinop :: NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop :: NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop op :: NBinaryOp
op e1 :: NExpr
e1 e2 :: NExpr
e2 = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NBinaryOp -> NExpr -> NExpr -> NExprF NExpr
forall r. NBinaryOp -> r -> r -> NExprF r
NBinary NBinaryOp
op NExpr
e1 NExpr
e2)
($==), ($!=), ($<), ($<=), ($>), ($>=), ($&&), ($||), ($->), ($//), ($+), ($-), ($*), ($/), ($++)
:: NExpr -> NExpr -> NExpr
e1 :: NExpr
e1 $== :: NExpr -> NExpr -> NExpr
$== e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NEq NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $!= :: NExpr -> NExpr -> NExpr
$!= e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NNEq NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $< :: NExpr -> NExpr -> NExpr
$< e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NLt NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $<= :: NExpr -> NExpr -> NExpr
$<= e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NLte NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $> :: NExpr -> NExpr -> NExpr
$> e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NGt NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $>= :: NExpr -> NExpr -> NExpr
$>= e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NGte NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $&& :: NExpr -> NExpr -> NExpr
$&& e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NAnd NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $|| :: NExpr -> NExpr -> NExpr
$|| e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NOr NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $-> :: NExpr -> NExpr -> NExpr
$-> e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NImpl NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $// :: NExpr -> NExpr -> NExpr
$// e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NUpdate NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $+ :: NExpr -> NExpr -> NExpr
$+ e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NPlus NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $- :: NExpr -> NExpr -> NExpr
$- e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NMinus NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $* :: NExpr -> NExpr -> NExpr
$* e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NMult NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $/ :: NExpr -> NExpr -> NExpr
$/ e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NDiv NExpr
e1 NExpr
e2
e1 :: NExpr
e1 $++ :: NExpr -> NExpr -> NExpr
$++ e2 :: NExpr
e2 = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NConcat NExpr
e1 NExpr
e2
(@@) :: NExpr -> NExpr -> NExpr
f :: NExpr
f @@ :: NExpr -> NExpr -> NExpr
@@ arg :: NExpr
arg = NBinaryOp -> NExpr -> NExpr -> NExpr
mkBinop NBinaryOp
NApp NExpr
f NExpr
arg
infixl 1 @@
(==>) :: Params NExpr -> NExpr -> NExpr
==> :: Params NExpr -> NExpr -> NExpr
(==>) = Params NExpr -> NExpr -> NExpr
mkFunction
infixr 1 ==>
(@.) :: NExpr -> Text -> NExpr
obj :: NExpr
obj @. :: NExpr -> Text -> NExpr
@. name :: Text
name = NExprF NExpr -> NExpr
forall (f :: * -> *). f (Fix f) -> Fix f
Fix (NExpr -> NAttrPath NExpr -> Maybe NExpr -> NExprF NExpr
forall r. r -> NAttrPath r -> Maybe r -> NExprF r
NSelect NExpr
obj (Text -> NKeyName NExpr
forall r. Text -> NKeyName r
StaticKey Text
name NKeyName NExpr -> [NKeyName NExpr] -> NAttrPath NExpr
forall a. a -> [a] -> NonEmpty a
:| []) Maybe NExpr
forall a. Maybe a
Nothing)
infixl 2 @.