-- generated by using spec/Declarations.yaml {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} module Torch.Internal.Const where import qualified Language.C.Inline.Cpp as C import qualified Language.C.Inline.Cpp.Unsafe as C import qualified Language.C.Inline.Context as C import qualified Language.C.Types as C import qualified Data.Map as Map import Foreign.C.String import Foreign.C.Types import Foreign import Torch.Internal.Type C.context $ C.cppCtx <> mempty { C.ctxTypesTable = typeTable } C.include "" C.include "" C.include "" C.include "" torchVersionMajor :: CInt torchVersionMajor = [C.pure| int { TORCH_VERSION_MAJOR } |] torchVersionMinor :: CInt torchVersionMinor = [C.pure| int { TORCH_VERSION_MINOR } |] torchVersionPatch :: CInt torchVersionPatch = [C.pure| int { TORCH_VERSION_PATCH } |] torchVersion :: String torchVersion = show torchVersionMajor ++ "." ++ show torchVersionMinor ++ "." ++ show torchVersionPatch kByte :: ScalarType kByte = [C.pure| int8_t { (int8_t) at::ScalarType::Byte } |] kChar :: ScalarType kChar = [C.pure| int8_t { (int8_t) at::ScalarType::Char } |] kDouble :: ScalarType kDouble = [C.pure| int8_t { (int8_t) at::ScalarType::Double } |] kFloat :: ScalarType kFloat = [C.pure| int8_t { (int8_t) at::ScalarType::Float } |] kInt :: ScalarType kInt = [C.pure| int8_t { (int8_t) at::ScalarType::Int } |] kLong :: ScalarType kLong = [C.pure| int8_t { (int8_t) at::ScalarType::Long } |] kShort :: ScalarType kShort = [C.pure| int8_t { (int8_t) at::ScalarType::Short } |] kHalf :: ScalarType kHalf = [C.pure| int8_t { (int8_t) at::ScalarType::Half } |] kBool :: ScalarType kBool = [C.pure| int8_t { (int8_t) at::ScalarType::Bool } |] kComplexHalf :: ScalarType kComplexHalf = [C.pure| int8_t { (int8_t) at::ScalarType::ComplexHalf } |] kComplexFloat :: ScalarType kComplexFloat = [C.pure| int8_t { (int8_t) at::ScalarType::ComplexFloat } |] kComplexDouble :: ScalarType kComplexDouble = [C.pure| int8_t { (int8_t) at::ScalarType::ComplexDouble } |] kQInt8 :: ScalarType kQInt8 = [C.pure| int8_t { (int8_t) at::ScalarType::QInt8 } |] kQUInt8 :: ScalarType kQUInt8 = [C.pure| int8_t { (int8_t) at::ScalarType::QUInt8 } |] kQInt32 :: ScalarType kQInt32 = [C.pure| int8_t { (int8_t) at::ScalarType::QInt32 } |] kBFloat16 :: ScalarType kBFloat16 = [C.pure| int8_t { (int8_t) at::ScalarType::BFloat16 } |] kUndefined :: ScalarType kUndefined = [C.pure| int8_t { (int8_t) at::ScalarType::Undefined } |] kCPU :: DeviceType kCPU = [C.pure| int16_t { (int16_t) at::DeviceType::CPU } |] kCUDA :: DeviceType kCUDA = [C.pure| int16_t { (int16_t) at::DeviceType::CUDA } |] kMPS :: DeviceType kMPS = [C.pure| int16_t { (int16_t) at::DeviceType::MPS } |] kMKLDNN :: DeviceType kMKLDNN = [C.pure| int16_t { (int16_t) at::DeviceType::MKLDNN } |] kOPENGL :: DeviceType kOPENGL = [C.pure| int16_t { (int16_t) at::DeviceType::OPENGL } |] kOPENCL :: DeviceType kOPENCL = [C.pure| int16_t { (int16_t) at::DeviceType::OPENCL } |] kIDEEP :: DeviceType kIDEEP = [C.pure| int16_t { (int16_t) at::DeviceType::IDEEP } |] kHIP :: DeviceType kHIP = [C.pure| int16_t { (int16_t) at::DeviceType::HIP } |] kFPGA :: DeviceType kFPGA = [C.pure| int16_t { (int16_t) at::DeviceType::FPGA } |] kXLA :: DeviceType kXLA = [C.pure| int16_t { (int16_t) at::DeviceType::XLA } |] kVulkan :: DeviceType kVulkan = [C.pure| int16_t { (int16_t) at::DeviceType::Vulkan } |] kMetal :: DeviceType kMetal = [C.pure| int16_t { (int16_t) at::DeviceType::Metal } |] kXPU :: DeviceType kXPU = [C.pure| int16_t { (int16_t) at::DeviceType::XPU } |] kCOMPILE_TIME_MAX_DEVICE_TYPES :: DeviceType kCOMPILE_TIME_MAX_DEVICE_TYPES = [C.pure| int16_t { (int16_t) at::DeviceType::COMPILE_TIME_MAX_DEVICE_TYPES } |] -- TODO: add all values for at::Reduction kMean :: Int64 kMean = [C.pure| int64_t { (int64_t) at::Reduction::Mean } |] bCPU :: Backend bCPU = [C.pure| int { (int) at::Backend::CPU } |] bCUDA :: Backend bCUDA = [C.pure| int { (int) at::Backend::CUDA } |] bMPS :: Backend bMPS = [C.pure| int { (int) at::Backend::MPS } |] bHIP :: Backend bHIP = [C.pure| int { (int) at::Backend::HIP } |] bSparseCPU :: Backend bSparseCPU = [C.pure| int { (int) at::Backend::SparseCPU } |] bSparseCUDA :: Backend bSparseCUDA = [C.pure| int { (int) at::Backend::SparseCUDA } |] bSparseHIP :: Backend bSparseHIP = [C.pure| int { (int) at::Backend::SparseHIP } |] bXLA :: Backend bXLA = [C.pure| int { (int) at::Backend::XLA } |] bUndefined :: Backend bUndefined = [C.pure| int { (int) at::Backend::Undefined } |] bNumOptions :: Backend bNumOptions = [C.pure| int { (int) at::Backend::NumOptions } |] kStrided :: Layout kStrided = [C.pure| int8_t { (int8_t) at::kStrided } |] kSparse :: Layout kSparse = [C.pure| int8_t { (int8_t) at::kSparse } |] kMkldnn :: Layout kMkldnn = [C.pure| int8_t { (int8_t) at::kMkldnn } |]