hasktorch-codegen-0.0.1.1: Code generation tools for Hasktorch

Safe HaskellNone
LanguageHaskell2010

CodeGen.Types.CLI

Synopsis

Documentation

data LibType Source #

All possible libraries that we intend to support (these are all src libraries in ATen). Note that this ordering is used in codegen and must not be changed.

Constructors

ATen 
THCUNN 
THCS 
THC 
THNN 
THS 
TH 
Instances
Bounded LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Enum LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Eq LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Methods

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

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

Data LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LibType -> c LibType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LibType #

toConstr :: LibType -> Constr #

dataTypeOf :: LibType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LibType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LibType) #

gmapT :: (forall b. Data b => b -> b) -> LibType -> LibType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LibType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LibType -> r #

gmapQ :: (forall d. Data d => d -> u) -> LibType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LibType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LibType -> m LibType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LibType -> m LibType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LibType -> m LibType #

Ord LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Read LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Show LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Generic LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Associated Types

type Rep LibType :: Type -> Type #

Methods

from :: LibType -> Rep LibType x #

to :: Rep LibType x -> LibType #

Hashable LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

Methods

hashWithSalt :: Int -> LibType -> Int

hash :: LibType -> Int

type Rep LibType Source # 
Instance details

Defined in CodeGen.Types.CLI

type Rep LibType = D1 (MetaData "LibType" "CodeGen.Types.CLI" "hasktorch-codegen-0.0.1.1-inplace" False) ((C1 (MetaCons "ATen" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "THCUNN" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "THCS" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "THC" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "THNN" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "THS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TH" PrefixI False) (U1 :: Type -> Type))))

describe' :: LibType -> String Source #

Short descriptions of each library we intend to support.

supported :: LibType -> Bool Source #

Whether or not we currently support code generation for the library

outDir :: LibType -> FilePath Source #

Where generated code will be placed.

outModule :: LibType -> Text Source #

The prefix of the output module name

srcDir :: LibType -> CodeGenType -> FilePath Source #

Where the source files are located, relative to the root of the hasktorch project.

data CodeGenType Source #

Type of code to generate

Constructors

GenericFiles

generic/ files which are used in C for type-generic code

ConcreteFiles

concrete supporting files. These include utility functions and random generators.

Instances
Bounded CodeGenType Source # 
Instance details

Defined in CodeGen.Types.CLI

Enum CodeGenType Source # 
Instance details

Defined in CodeGen.Types.CLI

Eq CodeGenType Source # 
Instance details

Defined in CodeGen.Types.CLI

Ord CodeGenType Source # 
Instance details

Defined in CodeGen.Types.CLI

Read CodeGenType Source # 
Instance details

Defined in CodeGen.Types.CLI

Show CodeGenType Source # 
Instance details

Defined in CodeGen.Types.CLI

generatable :: CodeGenType -> Bool Source #

Whether or not we currently support generating this type of code (ie: I (@stites) am not sure about the managed files).

data TemplateType Source #

Instances
Bounded TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

Eq TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

Ord TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

Show TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

Generic TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

Associated Types

type Rep TemplateType :: Type -> Type #

Hashable TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

type Rep TemplateType Source # 
Instance details

Defined in CodeGen.Types.CLI

type Rep TemplateType = D1 (MetaData "TemplateType" "CodeGen.Types.CLI" "hasktorch-codegen-0.0.1.1-inplace" False) (((C1 (MetaCons "GenByte" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GenChar" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GenDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GenFloat" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "GenHalf" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GenInt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GenLong" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GenShort" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GenNothing" PrefixI False) (U1 :: Type -> Type)))))