Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Ginger.Interpret.Builtins
Synopsis
- type BuiltinAttribs a (m :: Type -> Type) = Map Identifier (a -> m (Either RuntimeError (Value m)))
- builtinGlobals :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Map Identifier (Value m)
- builtinGlobalsNonJinja :: forall (m :: Type -> Type). Monad m => (Expr -> GingerT m (Value m)) -> Map Identifier (Value m)
- builtinIntAttribs :: Monad m => BuiltinAttribs Integer m
- builtinFloatAttribs :: Monad m => BuiltinAttribs Double m
- builtinBoolAttribs :: Monad m => BuiltinAttribs Bool m
- builtinStringAttribs :: Monad m => BuiltinAttribs Text m
- builtinListAttribs :: Monad m => BuiltinAttribs (Vector (Value m)) m
- builtinDictAttribs :: Monad m => BuiltinAttribs (Map Scalar (Value m)) m
- regexModule :: forall (m :: Type -> Type). Monad m => Value m
- runReWith :: forall a (m :: Type -> Type). Monad m => (Regex -> Text -> a) -> Text -> Text -> Text -> ExceptT RuntimeError m a
- fnReMatch :: forall (m :: Type -> Type). Monad m => Procedure m
- fnReMatches :: forall (m :: Type -> Type). Monad m => Procedure m
- fnReTest :: forall (m :: Type -> Type). Monad m => Procedure m
- parseCompOpts :: Text -> CompOption
- convertMatchOnceText :: Maybe (Text, MatchText Text, Text) -> Maybe [Text]
- convertMatchText :: MatchText Text -> [Text]
- fnLength :: forall (m :: Type -> Type). Monad m => Procedure m
- fnEscape :: forall (m :: Type -> Type). Monad m => Procedure m
- fnToList :: forall (m :: Type -> Type). Monad m => Procedure m
- fnToFloat :: forall (m :: Type -> Type). Monad m => Procedure m
- fnToInt :: forall (m :: Type -> Type). Monad m => Procedure m
- fnToString :: forall (m :: Type -> Type). Monad m => Procedure m
- fnMin :: forall (m :: Type -> Type). Monad m => Procedure m
- fnMax :: forall (m :: Type -> Type). Monad m => Procedure m
- fnSum :: forall (m :: Type -> Type). Monad m => Procedure m
- valueSum :: forall (m :: Type -> Type). [Value m] -> Value m
- valueAdd :: forall (m :: Type -> Type). Value m -> Value m -> Value m
- caseFoldValue :: forall (m :: Type -> Type). Value m -> Value m
- fnRandom :: forall (m :: Type -> Type). MonadRandom m => Procedure m
- fnReverse :: forall (m :: Type -> Type). Monad m => Procedure m
- fnItems :: forall (m :: Type -> Type). Monad m => Procedure m
- data DictSortBy
- fnSlice :: forall (m :: Type -> Type). Monad m => Procedure m
- fnSort :: forall (m :: Type -> Type). Monad m => Procedure m
- fnDict :: forall (m :: Type -> Type). Monad m => Procedure m
- fnDictsort :: forall (m :: Type -> Type). Monad m => Procedure m
- fnSelectAttr :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m
- fnRejectAttr :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m
- fnSelectRejectAttr :: forall (m :: Type -> Type). MonadRandom m => Bool -> Text -> Text -> (Expr -> GingerT m (Value m)) -> Filter m
- scalarToIdentifier :: Scalar -> Maybe Identifier
- fnSelect :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m
- fnReject :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m
- fnSelectReject :: forall (m :: Type -> Type). MonadRandom m => Bool -> Text -> Text -> (Expr -> GingerT m (Value m)) -> Filter m
- fnMap :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m
- fnRound :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrReplace :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrStrip :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrLStrip :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrRStrip :: forall (m :: Type -> Type). Monad m => Procedure m
- fnToJSON :: forall (m :: Type -> Type). Monad m => Procedure m
- fnJoin :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrJoin :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrSplit :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrStartswith :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrEndswith :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrEncode :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrCount :: forall (m :: Type -> Type). Monad m => Procedure m
- fnCenter :: forall (m :: Type -> Type). Monad m => Procedure m
- fnLipsum :: forall (m :: Type -> Type). MonadRandom m => Procedure m
- newtype FileSize = FileSize Integer
- fnFormat :: forall (m :: Type -> Type). Monad m => Procedure m
- fnStrFormat :: forall (m :: Type -> Type). Monad m => Procedure m
- valueToFormatArg :: forall (m :: Type -> Type) t. (Monad m, MonadTrans t, MonadError RuntimeError (t m)) => Value m -> t m FormatArg
- valueDictToFormatDict :: forall (m :: Type -> Type) t. (Monad m, MonadTrans t, MonadError RuntimeError (t m)) => Map Scalar (Value m) -> t m (Map Text FormatArg)
- byteStringToInteger :: ByteString -> Integer
- fnFilesizeFormat :: forall (m :: Type -> Type). Monad m => Procedure m
- fnGroupBy :: forall (m :: Type -> Type). Monad m => Procedure m
- fnBatch :: forall (m :: Type -> Type). Monad m => Procedure m
- fnFirst :: forall (m :: Type -> Type). Monad m => Procedure m
- fnLast :: forall (m :: Type -> Type). Monad m => Procedure m
- autoParseDate :: TimeZone -> Text -> Maybe ZonedTime
- dateFromParts :: forall (m :: Type -> Type). Monad m => TimeZone -> [Value m] -> Maybe ZonedTime
- parseTZ :: forall (m :: Type -> Type). Value m -> Maybe TimeZone
- convertTZ :: Maybe TimeZone -> ZonedTime -> ZonedTime
- fnDateFormat :: forall (m :: Type -> Type). Monad m => Procedure m
- fnHelp :: forall (m :: Type -> Type). Monad m => Procedure m
- fnDictGet :: forall (m :: Type -> Type). Monad m => Procedure m
- isUpperVal :: forall (m :: Type -> Type). Value m -> Value m
- isLowerVal :: forall (m :: Type -> Type). Value m -> Value m
- isBoolean :: forall (m :: Type -> Type). Bool -> Value m -> Value m
- isNone :: forall (m :: Type -> Type). Value m -> Value m
- isDecimal :: Text -> Bool
- allEitherBool :: [Either a Bool] -> Either a Bool
- getAttrRaw :: Monad m => Value m -> Identifier -> m (Either RuntimeError (Maybe (Value m)))
- getItemRaw :: Monad m => Value m -> Value m -> m (Maybe (Value m))
- getAttrOrItemRaw :: Monad m => Value m -> Identifier -> m (Either RuntimeError (Maybe (Value m)))
- getItemOrAttrRaw :: Monad m => Value m -> Value m -> m (Either RuntimeError (Maybe (Value m)))
- nativeMethod :: forall (m :: Type -> Type). Procedure m -> Value m -> Value m
- nativePureMethod :: forall (m :: Type -> Type). Monad m => ObjectID -> Maybe ProcedureDoc -> (Value m -> Either RuntimeError (Value m)) -> Value m -> Value m
- toNativeMethod :: forall (m :: Type -> Type) a. ToNativeProcedure m a => ObjectID -> Maybe ProcedureDoc -> a -> Value m -> Value m
- pureAttrib :: Applicative m => (s -> a) -> s -> m (Either RuntimeError a)
- textBuiltin :: forall (m :: Type -> Type) a. (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Text -> a) -> Value m
- intBuiltin :: forall (m :: Type -> Type) a. (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Integer -> a) -> Value m
- numericBuiltin :: forall (m :: Type -> Type). Monad m => ObjectID -> Maybe ProcedureDoc -> (Integer -> Integer) -> (Double -> Double) -> Value m
- anyBuiltin :: forall (m :: Type -> Type) a b. (Monad m, FromValue a m, ToValue b m) => ObjectID -> Maybe ProcedureDoc -> (a -> b) -> Value m
- boolProp :: (Monad m, ToValue a m) => (Bool -> a) -> Bool -> m (Either RuntimeError (Value m))
- boolAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Bool -> a) -> Bool -> m (Either RuntimeError (Value m))
- boolNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Bool -> m (Either RuntimeError (Value m))
- boolProcAttrib :: Monad m => Procedure m -> Bool -> m (Either RuntimeError (Value m))
- intProp :: (Monad m, ToValue a m) => (Integer -> a) -> Integer -> m (Either RuntimeError (Value m))
- intAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Integer -> a) -> Integer -> m (Either RuntimeError (Value m))
- intNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Integer -> m (Either RuntimeError (Value m))
- intProcAttrib :: Monad m => Procedure m -> Integer -> m (Either RuntimeError (Value m))
- floatProp :: (Monad m, ToValue a m) => (Double -> a) -> Double -> m (Either RuntimeError (Value m))
- floatAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Double -> a) -> Double -> m (Either RuntimeError (Value m))
- floatNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Double -> m (Either RuntimeError (Value m))
- floatProcAttrib :: Monad m => Procedure m -> Double -> m (Either RuntimeError (Value m))
- textProp :: (Monad m, ToValue a m) => (Text -> a) -> Text -> m (Either RuntimeError (Value m))
- textAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Text -> a) -> Text -> m (Either RuntimeError (Value m))
- textNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Text -> m (Either RuntimeError (Value m))
- textProcAttrib :: Monad m => Procedure m -> Text -> m (Either RuntimeError (Value m))
- dictProp :: (Monad m, ToValue a m) => (Map Scalar (Value m) -> a) -> Map Scalar (Value m) -> m (Either RuntimeError (Value m))
- dictAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Map Scalar (Value m) -> a) -> Map Scalar (Value m) -> m (Either RuntimeError (Value m))
- dictNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Map Scalar (Value m) -> m (Either RuntimeError (Value m))
- dictProcAttrib :: Monad m => Procedure m -> Map Scalar (Value m) -> m (Either RuntimeError (Value m))
- builtinNotImplemented :: forall (m :: Type -> Type). Monad m => Text -> Value m
- fnMaybeArg :: forall (m :: Type -> Type) b. Monad m => Text -> Text -> Maybe b -> ExceptT RuntimeError m b
- fnArg :: forall (m :: Type -> Type) a. (Monad m, FromValue a m) => Text -> Identifier -> Map Identifier (Value m) -> ExceptT RuntimeError m a
- describeArg :: forall (m :: Type -> Type). Identifier -> Maybe (Value m) -> Maybe TypeDoc -> Text -> ArgumentDoc
- mkFn0' :: forall (m :: Type -> Type) r. (Monad m, ToValue r m) => Text -> Text -> Maybe TypeDoc -> (Context m -> ExceptT RuntimeError m r) -> Procedure m
- mkFn0 :: forall (m :: Type -> Type) r. (Monad m, ToValue r m) => Text -> Text -> Maybe TypeDoc -> ExceptT RuntimeError m r -> Procedure m
- mkFn1' :: forall (m :: Type -> Type) a r. (Monad m, ToValue a m, FromValue a m, ToValue r m) => Text -> Text -> (Identifier, Maybe a, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a -> ExceptT RuntimeError m r) -> Procedure m
- mkFn1 :: forall (m :: Type -> Type) a r. (Monad m, ToValue a m, FromValue a m, ToValue r m) => Text -> Text -> (Identifier, Maybe a, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a -> ExceptT RuntimeError m r) -> Procedure m
- mkFn2' :: forall (m :: Type -> Type) a1 a2 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a1 -> a2 -> ExceptT RuntimeError m r) -> Procedure m
- mkFn2 :: forall (m :: Type -> Type) a1 a2 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a1 -> a2 -> ExceptT RuntimeError m r) -> Procedure m
- mkFn3' :: forall (m :: Type -> Type) a1 a2 a3 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a1 -> a2 -> a3 -> ExceptT RuntimeError m r) -> Procedure m
- mkFn3 :: forall (m :: Type -> Type) a1 a2 a3 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a1 -> a2 -> a3 -> ExceptT RuntimeError m r) -> Procedure m
- mkFn4' :: forall (m :: Type -> Type) a1 a2 a3 a4 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue a4 m, FromValue a4 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> (Identifier, Maybe a4, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a1 -> a2 -> a3 -> a4 -> ExceptT RuntimeError m r) -> Procedure m
- mkFn4 :: forall (m :: Type -> Type) a1 a2 a3 a4 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue a4 m, FromValue a4 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> (Identifier, Maybe a4, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a1 -> a2 -> a3 -> a4 -> ExceptT RuntimeError m r) -> Procedure m
Documentation
type BuiltinAttribs a (m :: Type -> Type) = Map Identifier (a -> m (Either RuntimeError (Value m))) Source #
builtinGlobals :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Map Identifier (Value m) Source #
builtinGlobalsNonJinja :: forall (m :: Type -> Type). Monad m => (Expr -> GingerT m (Value m)) -> Map Identifier (Value m) Source #
builtinIntAttribs :: Monad m => BuiltinAttribs Integer m Source #
builtinFloatAttribs :: Monad m => BuiltinAttribs Double m Source #
builtinBoolAttribs :: Monad m => BuiltinAttribs Bool m Source #
builtinStringAttribs :: Monad m => BuiltinAttribs Text m Source #
builtinListAttribs :: Monad m => BuiltinAttribs (Vector (Value m)) m Source #
builtinDictAttribs :: Monad m => BuiltinAttribs (Map Scalar (Value m)) m Source #
runReWith :: forall a (m :: Type -> Type). Monad m => (Regex -> Text -> a) -> Text -> Text -> Text -> ExceptT RuntimeError m a Source #
parseCompOpts :: Text -> CompOption Source #
data DictSortBy Source #
Instances
fnSelectAttr :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m Source #
fnRejectAttr :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m Source #
fnSelectRejectAttr :: forall (m :: Type -> Type). MonadRandom m => Bool -> Text -> Text -> (Expr -> GingerT m (Value m)) -> Filter m Source #
fnSelect :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m Source #
fnReject :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m Source #
fnSelectReject :: forall (m :: Type -> Type). MonadRandom m => Bool -> Text -> Text -> (Expr -> GingerT m (Value m)) -> Filter m Source #
fnMap :: forall (m :: Type -> Type). MonadRandom m => (Expr -> GingerT m (Value m)) -> Filter m Source #
valueToFormatArg :: forall (m :: Type -> Type) t. (Monad m, MonadTrans t, MonadError RuntimeError (t m)) => Value m -> t m FormatArg Source #
valueDictToFormatDict :: forall (m :: Type -> Type) t. (Monad m, MonadTrans t, MonadError RuntimeError (t m)) => Map Scalar (Value m) -> t m (Map Text FormatArg) Source #
byteStringToInteger :: ByteString -> Integer Source #
Interpret bytestring as big-endian integer number
dateFromParts :: forall (m :: Type -> Type). Monad m => TimeZone -> [Value m] -> Maybe ZonedTime Source #
getAttrRaw :: Monad m => Value m -> Identifier -> m (Either RuntimeError (Maybe (Value m))) Source #
getAttrOrItemRaw :: Monad m => Value m -> Identifier -> m (Either RuntimeError (Maybe (Value m))) Source #
getItemOrAttrRaw :: Monad m => Value m -> Value m -> m (Either RuntimeError (Maybe (Value m))) Source #
nativePureMethod :: forall (m :: Type -> Type). Monad m => ObjectID -> Maybe ProcedureDoc -> (Value m -> Either RuntimeError (Value m)) -> Value m -> Value m Source #
toNativeMethod :: forall (m :: Type -> Type) a. ToNativeProcedure m a => ObjectID -> Maybe ProcedureDoc -> a -> Value m -> Value m Source #
pureAttrib :: Applicative m => (s -> a) -> s -> m (Either RuntimeError a) Source #
textBuiltin :: forall (m :: Type -> Type) a. (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Text -> a) -> Value m Source #
intBuiltin :: forall (m :: Type -> Type) a. (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Integer -> a) -> Value m Source #
numericBuiltin :: forall (m :: Type -> Type). Monad m => ObjectID -> Maybe ProcedureDoc -> (Integer -> Integer) -> (Double -> Double) -> Value m Source #
anyBuiltin :: forall (m :: Type -> Type) a b. (Monad m, FromValue a m, ToValue b m) => ObjectID -> Maybe ProcedureDoc -> (a -> b) -> Value m Source #
boolProp :: (Monad m, ToValue a m) => (Bool -> a) -> Bool -> m (Either RuntimeError (Value m)) Source #
boolAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Bool -> a) -> Bool -> m (Either RuntimeError (Value m)) Source #
boolNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Bool -> m (Either RuntimeError (Value m)) Source #
boolProcAttrib :: Monad m => Procedure m -> Bool -> m (Either RuntimeError (Value m)) Source #
intProp :: (Monad m, ToValue a m) => (Integer -> a) -> Integer -> m (Either RuntimeError (Value m)) Source #
intAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Integer -> a) -> Integer -> m (Either RuntimeError (Value m)) Source #
intNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Integer -> m (Either RuntimeError (Value m)) Source #
intProcAttrib :: Monad m => Procedure m -> Integer -> m (Either RuntimeError (Value m)) Source #
floatProp :: (Monad m, ToValue a m) => (Double -> a) -> Double -> m (Either RuntimeError (Value m)) Source #
floatAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Double -> a) -> Double -> m (Either RuntimeError (Value m)) Source #
floatNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Double -> m (Either RuntimeError (Value m)) Source #
floatProcAttrib :: Monad m => Procedure m -> Double -> m (Either RuntimeError (Value m)) Source #
textProp :: (Monad m, ToValue a m) => (Text -> a) -> Text -> m (Either RuntimeError (Value m)) Source #
textAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Text -> a) -> Text -> m (Either RuntimeError (Value m)) Source #
textNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Text -> m (Either RuntimeError (Value m)) Source #
textProcAttrib :: Monad m => Procedure m -> Text -> m (Either RuntimeError (Value m)) Source #
dictProp :: (Monad m, ToValue a m) => (Map Scalar (Value m) -> a) -> Map Scalar (Value m) -> m (Either RuntimeError (Value m)) Source #
dictAttrib :: (Monad m, ToValue a m) => ObjectID -> Maybe ProcedureDoc -> (Map Scalar (Value m) -> a) -> Map Scalar (Value m) -> m (Either RuntimeError (Value m)) Source #
dictNProcAttrib :: (Monad m, ToNativeProcedure m a) => ObjectID -> Maybe ProcedureDoc -> (Value m -> a) -> Map Scalar (Value m) -> m (Either RuntimeError (Value m)) Source #
dictProcAttrib :: Monad m => Procedure m -> Map Scalar (Value m) -> m (Either RuntimeError (Value m)) Source #
fnMaybeArg :: forall (m :: Type -> Type) b. Monad m => Text -> Text -> Maybe b -> ExceptT RuntimeError m b Source #
fnArg :: forall (m :: Type -> Type) a. (Monad m, FromValue a m) => Text -> Identifier -> Map Identifier (Value m) -> ExceptT RuntimeError m a Source #
describeArg :: forall (m :: Type -> Type). Identifier -> Maybe (Value m) -> Maybe TypeDoc -> Text -> ArgumentDoc Source #
mkFn0' :: forall (m :: Type -> Type) r. (Monad m, ToValue r m) => Text -> Text -> Maybe TypeDoc -> (Context m -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn0 :: forall (m :: Type -> Type) r. (Monad m, ToValue r m) => Text -> Text -> Maybe TypeDoc -> ExceptT RuntimeError m r -> Procedure m Source #
mkFn1' :: forall (m :: Type -> Type) a r. (Monad m, ToValue a m, FromValue a m, ToValue r m) => Text -> Text -> (Identifier, Maybe a, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn1 :: forall (m :: Type -> Type) a r. (Monad m, ToValue a m, FromValue a m, ToValue r m) => Text -> Text -> (Identifier, Maybe a, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn2' :: forall (m :: Type -> Type) a1 a2 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a1 -> a2 -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn2 :: forall (m :: Type -> Type) a1 a2 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a1 -> a2 -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn3' :: forall (m :: Type -> Type) a1 a2 a3 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a1 -> a2 -> a3 -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn3 :: forall (m :: Type -> Type) a1 a2 a3 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a1 -> a2 -> a3 -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn4' :: forall (m :: Type -> Type) a1 a2 a3 a4 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue a4 m, FromValue a4 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> (Identifier, Maybe a4, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (Context m -> a1 -> a2 -> a3 -> a4 -> ExceptT RuntimeError m r) -> Procedure m Source #
mkFn4 :: forall (m :: Type -> Type) a1 a2 a3 a4 r. (Monad m, ToValue a1 m, FromValue a1 m, ToValue a2 m, FromValue a2 m, ToValue a3 m, FromValue a3 m, ToValue a4 m, FromValue a4 m, ToValue r m) => Text -> Text -> (Identifier, Maybe a1, Maybe TypeDoc, Text) -> (Identifier, Maybe a2, Maybe TypeDoc, Text) -> (Identifier, Maybe a3, Maybe TypeDoc, Text) -> (Identifier, Maybe a4, Maybe TypeDoc, Text) -> Maybe TypeDoc -> (a1 -> a2 -> a3 -> a4 -> ExceptT RuntimeError m r) -> Procedure m Source #