clr-typed-0.2.0: A strongly typed Haskell interface to the CLR type system

Safe HaskellNone
LanguageHaskell2010

Clr.Method.Instance

Documentation

class MethodI n t m args where Source #

Minimal complete definition

rawInvokeI

Associated Types

type ResultTypeI n t m args :: Type Source #

Methods

rawInvokeI :: BridgeType t -> CurryT' n (BridgeTypes args) (IO (BridgeType (ResultTypeI n t m args))) Source #

Instances

MethodInvokeI1 t m () => MethodI 1 t m ([] Type) Source # 

Associated Types

type ResultTypeI (1 :: Nat) t m ([] Type :: [Type]) :: Type Source #

MethodInvokeI1 t m a => MethodI 1 t m ((:) Type a ([] Type)) Source # 

Associated Types

type ResultTypeI (1 :: Nat) t m ((:) Type a ([] Type) :: [Type]) :: Type Source #

Methods

rawInvokeI :: BridgeType t -> CurryT' 1 (BridgeTypes ((Type ': a) [Type])) (IO (BridgeType (ResultTypeI 1 t m ((Type ': a) [Type])))) Source #

MethodInvokeI2 t m a0 a1 => MethodI 2 t m ((:) Type a0 ((:) Type a1 ([] Type))) Source # 

Associated Types

type ResultTypeI (2 :: Nat) t m ((:) Type a0 ((:) Type a1 ([] Type)) :: [Type]) :: Type Source #

Methods

rawInvokeI :: BridgeType t -> CurryT' 2 (BridgeTypes ((Type ': a0) ((Type ': a1) [Type]))) (IO (BridgeType (ResultTypeI 2 t m ((Type ': a0) ((Type ': a1) [Type]))))) Source #

MethodInvokeI3 t m a0 a1 a2 => MethodI 3 t m ((:) Type a0 ((:) Type a1 ((:) Type a2 ([] Type)))) Source # 

Associated Types

type ResultTypeI (3 :: Nat) t m ((:) Type a0 ((:) Type a1 ((:) Type a2 ([] Type))) :: [Type]) :: Type Source #

Methods

rawInvokeI :: BridgeType t -> CurryT' 3 (BridgeTypes ((Type ': a0) ((Type ': a1) ((Type ': a2) [Type])))) (IO (BridgeType (ResultTypeI 3 t m ((Type ': a0) ((Type ': a1) ((Type ': a2) [Type])))))) Source #

class MethodResultI1 t m arg0 Source #

Associated Types

type ResultTypeI1 t m arg0 :: Type Source #

class MethodResultI2 t m arg0 arg1 Source #

Associated Types

type ResultTypeI2 t m arg0 arg1 :: Type Source #

class MethodResultI3 t m arg0 arg1 arg2 Source #

Associated Types

type ResultTypeI3 t m arg0 arg1 arg2 :: Type Source #

class MethodResultI1 (t :: Type) (m :: Type) (arg0 :: Type) => MethodInvokeI1 t m arg0 where Source #

Minimal complete definition

rawInvokeI1

Methods

rawInvokeI1 :: BridgeType t -> BridgeType arg0 -> IO (BridgeType (ResultTypeI1 t m arg0)) Source #

class MethodResultI2 (t :: Type) (m :: Type) (arg0 :: Type) (arg1 :: Type) => MethodInvokeI2 t m arg0 arg1 where Source #

Minimal complete definition

rawInvokeI2

Methods

rawInvokeI2 :: BridgeType t -> BridgeType arg0 -> BridgeType arg1 -> IO (BridgeType (ResultTypeI2 t m arg0 arg1)) Source #

class MethodResultI3 (t :: Type) (m :: Type) (arg0 :: Type) (arg1 :: Type) (arg2 :: Type) => MethodInvokeI3 t m arg0 arg1 arg2 where Source #

Minimal complete definition

rawInvokeI3

Methods

rawInvokeI3 :: BridgeType t -> BridgeType arg0 -> BridgeType arg1 -> BridgeType arg2 -> IO (BridgeType (ResultTypeI3 t m arg0 arg1 arg2)) Source #

invokeI :: forall ms resultBridge resultHask m tBase tDerived argsClrUnResolved argsClr argsHask argCount argsBridge. (MakeT ms ~ m, ArgCount argsHask ~ argCount, ResolveBaseType tDerived m ~ tBase, (tDerived `Implements` tBase) ~ True, HaskToClrL (TupleToList argsHask) ~ argsClrUnResolved, ResolveMember argsClrUnResolved (Candidates tBase m) ~ argsClr, MethodI argCount tBase m argsClr, ListToTuple (BridgeTypeL argsClr) ~ argsBridge, BridgeType (ResultTypeI argCount tBase m argsClr) ~ resultBridge, Marshal argsHask argsBridge, Marshal (Object tBase) (BridgeType tBase), Unmarshal resultBridge resultHask, Curry argCount (argsBridge -> IO resultBridge) (CurryT' argCount argsBridge (IO resultBridge))) => Object tDerived -> argsHask -> IO resultHask Source #