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

Safe HaskellNone
LanguageHaskell2010

Clr.Method.Static

Documentation

class MethodS n t m args where Source #

Minimal complete definition

rawInvokeS

Associated Types

type ResultTypeS n t m args :: Type Source #

Methods

rawInvokeS :: CurryT' n (BridgeTypes args) (IO (BridgeType (ResultTypeS n t m args))) Source #

Instances

MethodInvokeS1 t m () => MethodS 1 t m ([] Type) Source # 

Associated Types

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

MethodInvokeS1 t m a => MethodS 1 t m ((:) Type a ([] Type)) Source # 

Associated Types

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

Methods

rawInvokeS :: CurryT' 1 (BridgeTypes ((Type ': a) [Type])) (IO (BridgeType (ResultTypeS 1 t m ((Type ': a) [Type])))) Source #

MethodInvokeS2 t m a0 a1 => MethodS 2 t m ((:) Type a0 ((:) Type a1 ([] Type))) Source # 

Associated Types

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

Methods

rawInvokeS :: CurryT' 2 (BridgeTypes ((Type ': a0) ((Type ': a1) [Type]))) (IO (BridgeType (ResultTypeS 2 t m ((Type ': a0) ((Type ': a1) [Type]))))) Source #

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

Associated Types

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

Methods

rawInvokeS :: CurryT' 3 (BridgeTypes ((Type ': a0) ((Type ': a1) ((Type ': a2) [Type])))) (IO (BridgeType (ResultTypeS 3 t m ((Type ': a0) ((Type ': a1) ((Type ': a2) [Type])))))) Source #

class MethodResultS1 t m arg0 Source #

Associated Types

type ResultTypeS1 t m arg0 :: Type Source #

class MethodResultS2 t m arg0 arg1 Source #

Associated Types

type ResultTypeS2 t m arg0 arg1 :: Type Source #

class MethodResultS3 t m arg0 arg1 arg2 Source #

Associated Types

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

class MethodResultS1 (t :: Type) (m :: Type) (arg0 :: Type) => MethodInvokeS1 t m arg0 where Source #

Minimal complete definition

rawInvokeS1

Methods

rawInvokeS1 :: BridgeType arg0 -> IO (BridgeType (ResultTypeS1 t m arg0)) Source #

class MethodResultS2 (t :: Type) (m :: Type) (arg0 :: Type) (arg1 :: Type) => MethodInvokeS2 t m arg0 arg1 where Source #

Minimal complete definition

rawInvokeS2

Methods

rawInvokeS2 :: BridgeType arg0 -> BridgeType arg1 -> IO (BridgeType (ResultTypeS2 t m arg0 arg1)) Source #

class MethodResultS3 (t :: Type) (m :: Type) (arg0 :: Type) (arg1 :: Type) (arg2 :: Type) => MethodInvokeS3 t m arg0 arg1 arg2 where Source #

Minimal complete definition

rawInvokeS3

Methods

rawInvokeS3 :: BridgeType arg0 -> BridgeType arg1 -> BridgeType arg2 -> IO (BridgeType (ResultTypeS3 t m arg0 arg1 arg2)) Source #

invokeS :: forall ms ts resultBridge resultHask m t argsClrUnResolved argsClr argsHask argCount argsBridge. (MakeT ms ~ m, MakeT ts ~ t, ArgCount argsHask ~ argCount, HaskToClrL (TupleToList argsHask) ~ argsClrUnResolved, ResolveMember argsClrUnResolved (Candidates t m) ~ argsClr, MethodS argCount t m argsClr, ListToTuple (BridgeTypeL argsClr) ~ argsBridge, BridgeType (ResultTypeS argCount t m argsClr) ~ resultBridge, Marshal argsHask argsBridge, Unmarshal resultBridge resultHask, Curry argCount (argsBridge -> IO resultBridge) (CurryT' argCount argsBridge (IO resultBridge))) => argsHask -> IO resultHask Source #