-- GENERATED by C->Haskell Compiler, version 0.28.3 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/TensorFlow/Internal/Raw.chs" #-}
-- Copyright 2016 TensorFlow authors.
--
-- Licensed under the Apache License, Version 2.0 (the "License");
-- you may not use this file except in compliance with the License.
-- You may obtain a copy of the License at
--
--     http://www.apache.org/licenses/LICENSE-2.0
--
-- Unless required by applicable law or agreed to in writing, software
-- distributed under the License is distributed on an "AS IS" BASIS,
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-- See the License for the specific language governing permissions and
-- limitations under the License.

{-# LANGUAGE ForeignFunctionInterface #-}

module TensorFlow.Internal.Raw where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp





import Foreign
import Foreign.C

data DataType = TF_FLOAT
              | TF_DOUBLE
              | TF_INT32
              | TF_UINT8
              | TF_INT16
              | TF_INT8
              | TF_STRING
              | TF_COMPLEX64
              | TF_COMPLEX
              | TF_INT64
              | TF_BOOL
              | TF_QINT8
              | TF_QUINT8
              | TF_QINT32
              | TF_BFLOAT16
              | TF_QINT16
              | TF_QUINT16
              | TF_UINT16
              | TF_COMPLEX128
              | TF_HALF
              | TF_RESOURCE
              | TF_VARIANT
              | TF_UINT32
              | TF_UINT64
  deriving (Show,Eq)
instance Enum DataType where
  succ TF_FLOAT = TF_DOUBLE
  succ TF_DOUBLE = TF_INT32
  succ TF_INT32 = TF_UINT8
  succ TF_UINT8 = TF_INT16
  succ TF_INT16 = TF_INT8
  succ TF_INT8 = TF_STRING
  succ TF_STRING = TF_COMPLEX64
  succ TF_COMPLEX64 = TF_INT64
  succ TF_COMPLEX = TF_INT64
  succ TF_INT64 = TF_BOOL
  succ TF_BOOL = TF_QINT8
  succ TF_QINT8 = TF_QUINT8
  succ TF_QUINT8 = TF_QINT32
  succ TF_QINT32 = TF_BFLOAT16
  succ TF_BFLOAT16 = TF_QINT16
  succ TF_QINT16 = TF_QUINT16
  succ TF_QUINT16 = TF_UINT16
  succ TF_UINT16 = TF_COMPLEX128
  succ TF_COMPLEX128 = TF_HALF
  succ TF_HALF = TF_RESOURCE
  succ TF_RESOURCE = TF_VARIANT
  succ TF_VARIANT = TF_UINT32
  succ TF_UINT32 = TF_UINT64
  succ TF_UINT64 = error "DataType.succ: TF_UINT64 has no successor"

  pred TF_DOUBLE = TF_FLOAT
  pred TF_INT32 = TF_DOUBLE
  pred TF_UINT8 = TF_INT32
  pred TF_INT16 = TF_UINT8
  pred TF_INT8 = TF_INT16
  pred TF_STRING = TF_INT8
  pred TF_COMPLEX64 = TF_STRING
  pred TF_COMPLEX = TF_STRING
  pred TF_INT64 = TF_COMPLEX64
  pred TF_BOOL = TF_INT64
  pred TF_QINT8 = TF_BOOL
  pred TF_QUINT8 = TF_QINT8
  pred TF_QINT32 = TF_QUINT8
  pred TF_BFLOAT16 = TF_QINT32
  pred TF_QINT16 = TF_BFLOAT16
  pred TF_QUINT16 = TF_QINT16
  pred TF_UINT16 = TF_QUINT16
  pred TF_COMPLEX128 = TF_UINT16
  pred TF_HALF = TF_COMPLEX128
  pred TF_RESOURCE = TF_HALF
  pred TF_VARIANT = TF_RESOURCE
  pred TF_UINT32 = TF_VARIANT
  pred TF_UINT64 = TF_UINT32
  pred TF_FLOAT = error "DataType.pred: TF_FLOAT has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from TF_UINT64

  fromEnum TF_FLOAT = 1
  fromEnum TF_DOUBLE = 2
  fromEnum TF_INT32 = 3
  fromEnum TF_UINT8 = 4
  fromEnum TF_INT16 = 5
  fromEnum TF_INT8 = 6
  fromEnum TF_STRING = 7
  fromEnum TF_COMPLEX64 = 8
  fromEnum TF_COMPLEX = 8
  fromEnum TF_INT64 = 9
  fromEnum TF_BOOL = 10
  fromEnum TF_QINT8 = 11
  fromEnum TF_QUINT8 = 12
  fromEnum TF_QINT32 = 13
  fromEnum TF_BFLOAT16 = 14
  fromEnum TF_QINT16 = 15
  fromEnum TF_QUINT16 = 16
  fromEnum TF_UINT16 = 17
  fromEnum TF_COMPLEX128 = 18
  fromEnum TF_HALF = 19
  fromEnum TF_RESOURCE = 20
  fromEnum TF_VARIANT = 21
  fromEnum TF_UINT32 = 22
  fromEnum TF_UINT64 = 23

  toEnum 1 = TF_FLOAT
  toEnum 2 = TF_DOUBLE
  toEnum 3 = TF_INT32
  toEnum 4 = TF_UINT8
  toEnum 5 = TF_INT16
  toEnum 6 = TF_INT8
  toEnum 7 = TF_STRING
  toEnum 8 = TF_COMPLEX64
  toEnum 9 = TF_INT64
  toEnum 10 = TF_BOOL
  toEnum 11 = TF_QINT8
  toEnum 12 = TF_QUINT8
  toEnum 13 = TF_QINT32
  toEnum 14 = TF_BFLOAT16
  toEnum 15 = TF_QINT16
  toEnum 16 = TF_QUINT16
  toEnum 17 = TF_UINT16
  toEnum 18 = TF_COMPLEX128
  toEnum 19 = TF_HALF
  toEnum 20 = TF_RESOURCE
  toEnum 21 = TF_VARIANT
  toEnum 22 = TF_UINT32
  toEnum 23 = TF_UINT64
  toEnum unmatched = error ("DataType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 24 "src/TensorFlow/Internal/Raw.chs" #-}

data Code = TF_OK
          | TF_CANCELLED
          | TF_UNKNOWN
          | TF_INVALID_ARGUMENT
          | TF_DEADLINE_EXCEEDED
          | TF_NOT_FOUND
          | TF_ALREADY_EXISTS
          | TF_PERMISSION_DENIED
          | TF_RESOURCE_EXHAUSTED
          | TF_FAILED_PRECONDITION
          | TF_ABORTED
          | TF_OUT_OF_RANGE
          | TF_UNIMPLEMENTED
          | TF_INTERNAL
          | TF_UNAVAILABLE
          | TF_DATA_LOSS
          | TF_UNAUTHENTICATED
  deriving (Show,Eq)
instance Enum Code where
  succ TF_OK = TF_CANCELLED
  succ TF_CANCELLED = TF_UNKNOWN
  succ TF_UNKNOWN = TF_INVALID_ARGUMENT
  succ TF_INVALID_ARGUMENT = TF_DEADLINE_EXCEEDED
  succ TF_DEADLINE_EXCEEDED = TF_NOT_FOUND
  succ TF_NOT_FOUND = TF_ALREADY_EXISTS
  succ TF_ALREADY_EXISTS = TF_PERMISSION_DENIED
  succ TF_PERMISSION_DENIED = TF_RESOURCE_EXHAUSTED
  succ TF_RESOURCE_EXHAUSTED = TF_FAILED_PRECONDITION
  succ TF_FAILED_PRECONDITION = TF_ABORTED
  succ TF_ABORTED = TF_OUT_OF_RANGE
  succ TF_OUT_OF_RANGE = TF_UNIMPLEMENTED
  succ TF_UNIMPLEMENTED = TF_INTERNAL
  succ TF_INTERNAL = TF_UNAVAILABLE
  succ TF_UNAVAILABLE = TF_DATA_LOSS
  succ TF_DATA_LOSS = TF_UNAUTHENTICATED
  succ TF_UNAUTHENTICATED = error "Code.succ: TF_UNAUTHENTICATED has no successor"

  pred TF_CANCELLED = TF_OK
  pred TF_UNKNOWN = TF_CANCELLED
  pred TF_INVALID_ARGUMENT = TF_UNKNOWN
  pred TF_DEADLINE_EXCEEDED = TF_INVALID_ARGUMENT
  pred TF_NOT_FOUND = TF_DEADLINE_EXCEEDED
  pred TF_ALREADY_EXISTS = TF_NOT_FOUND
  pred TF_PERMISSION_DENIED = TF_ALREADY_EXISTS
  pred TF_RESOURCE_EXHAUSTED = TF_PERMISSION_DENIED
  pred TF_FAILED_PRECONDITION = TF_RESOURCE_EXHAUSTED
  pred TF_ABORTED = TF_FAILED_PRECONDITION
  pred TF_OUT_OF_RANGE = TF_ABORTED
  pred TF_UNIMPLEMENTED = TF_OUT_OF_RANGE
  pred TF_INTERNAL = TF_UNIMPLEMENTED
  pred TF_UNAVAILABLE = TF_INTERNAL
  pred TF_DATA_LOSS = TF_UNAVAILABLE
  pred TF_UNAUTHENTICATED = TF_DATA_LOSS
  pred TF_OK = error "Code.pred: TF_OK has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from TF_UNAUTHENTICATED

  fromEnum TF_OK = 0
  fromEnum TF_CANCELLED = 1
  fromEnum TF_UNKNOWN = 2
  fromEnum TF_INVALID_ARGUMENT = 3
  fromEnum TF_DEADLINE_EXCEEDED = 4
  fromEnum TF_NOT_FOUND = 5
  fromEnum TF_ALREADY_EXISTS = 6
  fromEnum TF_PERMISSION_DENIED = 7
  fromEnum TF_RESOURCE_EXHAUSTED = 8
  fromEnum TF_FAILED_PRECONDITION = 9
  fromEnum TF_ABORTED = 10
  fromEnum TF_OUT_OF_RANGE = 11
  fromEnum TF_UNIMPLEMENTED = 12
  fromEnum TF_INTERNAL = 13
  fromEnum TF_UNAVAILABLE = 14
  fromEnum TF_DATA_LOSS = 15
  fromEnum TF_UNAUTHENTICATED = 16

  toEnum 0 = TF_OK
  toEnum 1 = TF_CANCELLED
  toEnum 2 = TF_UNKNOWN
  toEnum 3 = TF_INVALID_ARGUMENT
  toEnum 4 = TF_DEADLINE_EXCEEDED
  toEnum 5 = TF_NOT_FOUND
  toEnum 6 = TF_ALREADY_EXISTS
  toEnum 7 = TF_PERMISSION_DENIED
  toEnum 8 = TF_RESOURCE_EXHAUSTED
  toEnum 9 = TF_FAILED_PRECONDITION
  toEnum 10 = TF_ABORTED
  toEnum 11 = TF_OUT_OF_RANGE
  toEnum 12 = TF_UNIMPLEMENTED
  toEnum 13 = TF_INTERNAL
  toEnum 14 = TF_UNAVAILABLE
  toEnum 15 = TF_DATA_LOSS
  toEnum 16 = TF_UNAUTHENTICATED
  toEnum unmatched = error ("Code.toEnum: Cannot match " ++ show unmatched)

{-# LINE 25 "src/TensorFlow/Internal/Raw.chs" #-}



-- Status.
newtype Status = Status (C2HSImp.Ptr (Status))
{-# LINE 29 "src/TensorFlow/Internal/Raw.chs" #-}


newStatus :: IO Status
newStatus = tFNewStatus
{-# LINE 32 "src/TensorFlow/Internal/Raw.chs" #-}


deleteStatus :: Status -> IO ()
deleteStatus = tFDeleteStatus
{-# LINE 35 "src/TensorFlow/Internal/Raw.chs" #-}


setStatus :: Status -> Code -> CString -> IO ()
setStatus s c = tFSetStatus s (fromIntegral $ fromEnum c)

getCode :: Status -> IO Code
getCode s = toEnum . fromIntegral <$> tFGetCode s

message :: Status -> IO CString
message = tFMessage
{-# LINE 44 "src/TensorFlow/Internal/Raw.chs" #-}



-- Buffer.
data Buffer
type BufferPtr = C2HSImp.Ptr (Buffer)
{-# LINE 49 "src/TensorFlow/Internal/Raw.chs" #-}


getBufferData :: BufferPtr -> IO (Ptr ())
getBufferData = (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr ())})
{-# LINE 52 "src/TensorFlow/Internal/Raw.chs" #-}


getBufferLength :: BufferPtr -> IO CULong
getBufferLength =(\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CULong})
{-# LINE 55 "src/TensorFlow/Internal/Raw.chs" #-}


-- Tensor.
newtype Tensor = Tensor (C2HSImp.Ptr (Tensor))
{-# LINE 58 "src/TensorFlow/Internal/Raw.chs" #-}


instance Storable Tensor where
    sizeOf (Tensor t) = sizeOf t
    alignment (Tensor t) = alignment t
    peek p = fmap Tensor (peek (castPtr p))
    poke p (Tensor t) = poke (castPtr p) t

-- A synonym for the int64_t type, which is used in the TensorFlow API.
-- On some platforms it's `long`; on others (e.g., Mac OS X) it's `long long`;
-- and as far as Haskell is concerned, those are distinct types (`CLong` vs
-- `CLLong`).
type CInt64 = (C2HSImp.CLong)
{-# LINE 70 "src/TensorFlow/Internal/Raw.chs" #-}


newTensor :: DataType
          -> Ptr CInt64   -- dimensions array
          -> CInt         -- num dimensions
          -> Ptr ()       -- data
          -> CULong       -- data len
          -> FunPtr (Ptr () -> CULong -> Ptr () -> IO ())  -- deallocator
          -> Ptr ()       -- deallocator arg
          -> IO Tensor
newTensor dt = tFNewTensor (fromIntegral $ fromEnum dt)

deleteTensor :: Tensor -> IO ()
deleteTensor = tFDeleteTensor
{-# LINE 83 "src/TensorFlow/Internal/Raw.chs" #-}


tensorType :: Tensor -> IO DataType
tensorType t = toEnum . fromIntegral <$> tFTensorType t

numDims :: Tensor -> IO CInt
numDims = tFNumDims
{-# LINE 89 "src/TensorFlow/Internal/Raw.chs" #-}


dim :: Tensor -> CInt -> IO CInt64
dim = tFDim
{-# LINE 92 "src/TensorFlow/Internal/Raw.chs" #-}


tensorByteSize :: Tensor -> IO CULong
tensorByteSize = tFTensorByteSize
{-# LINE 95 "src/TensorFlow/Internal/Raw.chs" #-}


tensorData :: Tensor -> IO (Ptr ())
tensorData = tFTensorData
{-# LINE 98 "src/TensorFlow/Internal/Raw.chs" #-}



-- Session Options.
newtype SessionOptions = SessionOptions (C2HSImp.Ptr (SessionOptions))
{-# LINE 102 "src/TensorFlow/Internal/Raw.chs" #-}


newSessionOptions :: IO SessionOptions
newSessionOptions = tFNewSessionOptions
{-# LINE 105 "src/TensorFlow/Internal/Raw.chs" #-}


setTarget :: SessionOptions -> CString -> IO ()
setTarget = tFSetTarget
{-# LINE 108 "src/TensorFlow/Internal/Raw.chs" #-}


setConfig :: SessionOptions -> Ptr () -> CULong -> Status -> IO ()
setConfig = tFSetConfig
{-# LINE 111 "src/TensorFlow/Internal/Raw.chs" #-}


deleteSessionOptions :: SessionOptions -> IO ()
deleteSessionOptions = tFDeleteSessionOptions
{-# LINE 114 "src/TensorFlow/Internal/Raw.chs" #-}



-- Session.
newtype Session = Session (C2HSImp.Ptr (Session))
{-# LINE 118 "src/TensorFlow/Internal/Raw.chs" #-}


newSession :: SessionOptions -> Status -> IO Session
newSession = tFNewDeprecatedSession
{-# LINE 121 "src/TensorFlow/Internal/Raw.chs" #-}


closeSession :: Session -> Status -> IO ()
closeSession = tFCloseDeprecatedSession
{-# LINE 124 "src/TensorFlow/Internal/Raw.chs" #-}


deleteSession :: Session -> Status -> IO ()
deleteSession = tFDeleteDeprecatedSession
{-# LINE 127 "src/TensorFlow/Internal/Raw.chs" #-}


extendGraph :: Session -> Ptr () -> CULong -> Status -> IO ()
extendGraph = tFExtendGraph
{-# LINE 130 "src/TensorFlow/Internal/Raw.chs" #-}


run :: Session
    -> BufferPtr                          -- RunOptions proto.
    -> Ptr CString -> Ptr Tensor -> CInt  -- Input (names, tensors, count).
    -> Ptr CString -> Ptr Tensor -> CInt  -- Output (names, tensors, count).
    -> Ptr CString -> CInt                -- Target nodes (names, count).
    -> BufferPtr                          -- RunMetadata proto.
    -> Status
    -> IO ()
run = tFRun
{-# LINE 140 "src/TensorFlow/Internal/Raw.chs" #-}


-- FFI helpers.
type TensorDeallocFn = Ptr () -> CULong -> Ptr () -> IO ()
foreign import ccall "wrapper"
    wrapTensorDealloc :: TensorDeallocFn -> IO (FunPtr TensorDeallocFn)


-- | Get the OpList of all OpDefs defined in this address space.
-- Returns a BufferPtr, ownership of which is transferred to the caller
-- (and can be freed using deleteBuffer).
--
-- The data in the buffer will be the serialized OpList proto for ops registered
-- in this address space.
getAllOpList :: IO BufferPtr
getAllOpList = tFGetAllOpList
{-# LINE 155 "src/TensorFlow/Internal/Raw.chs" #-}


foreign import ccall "&TF_DeleteBuffer"
  deleteBuffer :: FunPtr (BufferPtr -> IO ())

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_NewStatus"
  tFNewStatus :: (IO (Status))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_DeleteStatus"
  tFDeleteStatus :: ((Status) -> (IO ()))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_SetStatus"
  tFSetStatus :: ((Status) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_GetCode"
  tFGetCode :: ((Status) -> (IO C2HSImp.CInt))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_Message"
  tFMessage :: ((Status) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_NewTensor"
  tFNewTensor :: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CLong) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> (IO ()))))) -> ((C2HSImp.Ptr ()) -> (IO (Tensor)))))))))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_DeleteTensor"
  tFDeleteTensor :: ((Tensor) -> (IO ()))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_TensorType"
  tFTensorType :: ((Tensor) -> (IO C2HSImp.CInt))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_NumDims"
  tFNumDims :: ((Tensor) -> (IO C2HSImp.CInt))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_Dim"
  tFDim :: ((Tensor) -> (C2HSImp.CInt -> (IO C2HSImp.CLong)))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_TensorByteSize"
  tFTensorByteSize :: ((Tensor) -> (IO C2HSImp.CULong))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_TensorData"
  tFTensorData :: ((Tensor) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_NewSessionOptions"
  tFNewSessionOptions :: (IO (SessionOptions))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_SetTarget"
  tFSetTarget :: ((SessionOptions) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_SetConfig"
  tFSetConfig :: ((SessionOptions) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((Status) -> (IO ())))))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_DeleteSessionOptions"
  tFDeleteSessionOptions :: ((SessionOptions) -> (IO ()))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_NewDeprecatedSession"
  tFNewDeprecatedSession :: ((SessionOptions) -> ((Status) -> (IO (Session))))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_CloseDeprecatedSession"
  tFCloseDeprecatedSession :: ((Session) -> ((Status) -> (IO ())))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_DeleteDeprecatedSession"
  tFDeleteDeprecatedSession :: ((Session) -> ((Status) -> (IO ())))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_ExtendGraph"
  tFExtendGraph :: ((Session) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((Status) -> (IO ())))))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_Run"
  tFRun :: ((Session) -> ((BufferPtr) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr (Tensor)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr (Tensor)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> (C2HSImp.CInt -> ((BufferPtr) -> ((Status) -> (IO ())))))))))))))

foreign import ccall safe "TensorFlow/Internal/Raw.chs.h TF_GetAllOpList"
  tFGetAllOpList :: (IO (BufferPtr))