hasktorch-codegen-0.0.1.1: Code generation tools for Hasktorch

Safe HaskellNone
LanguageHaskell2010

CodeGen.Types.Parsed

Documentation

data Parsable Source #

Constructors

Ptr Parsable 
TenType TenType 
CType CType

NNType NNType

Instances
Eq Parsable Source # 
Instance details

Defined in CodeGen.Types.Parsed

Show Parsable Source # 
Instance details

Defined in CodeGen.Types.Parsed

Generic Parsable Source # 
Instance details

Defined in CodeGen.Types.Parsed

Associated Types

type Rep Parsable :: Type -> Type #

Methods

from :: Parsable -> Rep Parsable x #

to :: Rep Parsable x -> Parsable #

Hashable Parsable Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep Parsable Source # 
Instance details

Defined in CodeGen.Types.Parsed

data CType Source #

Instances
Bounded CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Enum CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Eq CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

(==) :: CType -> CType -> Bool #

(/=) :: CType -> CType -> Bool #

Show CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

showsPrec :: Int -> CType -> ShowS #

show :: CType -> String #

showList :: [CType] -> ShowS #

Generic CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Associated Types

type Rep CType :: Type -> Type #

Methods

from :: CType -> Rep CType x #

to :: Rep CType x -> CType #

Hashable CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

hashWithSalt :: Int -> CType -> Int

hash :: CType -> Int

type Rep CType Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep CType = D1 (MetaData "CType" "CodeGen.Types.Parsed" "hasktorch-codegen-0.0.1.1-inplace" False) ((((C1 (MetaCons "CBool" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CVoid" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CPtrdiff" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CFloat" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CLong" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CUInt64" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CUInt32" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CUInt16" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "CUInt8" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt64" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CInt32" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt16" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CInt8" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSize" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CChar" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CShort" PrefixI False) (U1 :: Type -> Type))))))

newtype TenType Source #

Constructors

Pair 
Instances
Eq TenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

(==) :: TenType -> TenType -> Bool #

(/=) :: TenType -> TenType -> Bool #

Show TenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Generic TenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Associated Types

type Rep TenType :: Type -> Type #

Methods

from :: TenType -> Rep TenType x #

to :: Rep TenType x -> TenType #

Hashable TenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

hashWithSalt :: Int -> TenType -> Int

hash :: TenType -> Int

type Rep TenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep TenType = D1 (MetaData "TenType" "CodeGen.Types.Parsed" "hasktorch-codegen-0.0.1.1-inplace" True) (C1 (MetaCons "Pair" PrefixI True) (S1 (MetaSel (Just "unTenType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RawTenType, LibType))))

data RawTenType Source #

Instances
Bounded RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Enum RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Eq RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Show RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Generic RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

Associated Types

type Rep RawTenType :: Type -> Type #

Hashable RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep RawTenType Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep RawTenType = D1 (MetaData "RawTenType" "CodeGen.Types.Parsed" "hasktorch-codegen-0.0.1.1-inplace" False) ((((C1 (MetaCons "Tensor" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ByteTensor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CharTensor" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ShortTensor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IntTensor" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LongTensor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FloatTensor" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "DoubleTensor" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HalfTensor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Storage" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ByteStorage" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CharStorage" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ShortStorage" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IntStorage" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "LongStorage" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FloatStorage" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DoubleStorage" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "HalfStorage" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DescBuff" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Generator" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Allocator" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "File" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Half" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "State" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IndexTensor" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "IntegerTensor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Real" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AccReal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Stream" PrefixI False) (U1 :: Type -> Type))))))

data Arg Source #

Constructors

Arg 

Fields

Instances
Eq Arg Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

(==) :: Arg -> Arg -> Bool #

(/=) :: Arg -> Arg -> Bool #

Show Arg Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

showsPrec :: Int -> Arg -> ShowS #

show :: Arg -> String #

showList :: [Arg] -> ShowS #

Generic Arg Source # 
Instance details

Defined in CodeGen.Types.Parsed

Associated Types

type Rep Arg :: Type -> Type #

Methods

from :: Arg -> Rep Arg x #

to :: Rep Arg x -> Arg #

Hashable Arg Source # 
Instance details

Defined in CodeGen.Types.Parsed

Methods

hashWithSalt :: Int -> Arg -> Int

hash :: Arg -> Int

type Rep Arg Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep Arg = D1 (MetaData "Arg" "CodeGen.Types.Parsed" "hasktorch-codegen-0.0.1.1-inplace" False) (C1 (MetaCons "Arg" PrefixI True) (S1 (MetaSel (Just "argType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parsable) :*: S1 (MetaSel (Just "argName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Function Source #

Constructors

Function 
Instances
Eq Function Source # 
Instance details

Defined in CodeGen.Types.Parsed

Show Function Source # 
Instance details

Defined in CodeGen.Types.Parsed

Generic Function Source # 
Instance details

Defined in CodeGen.Types.Parsed

Associated Types

type Rep Function :: Type -> Type #

Methods

from :: Function -> Rep Function x #

to :: Rep Function x -> Function #

Hashable Function Source # 
Instance details

Defined in CodeGen.Types.Parsed

type Rep Function Source # 
Instance details

Defined in CodeGen.Types.Parsed