{-# LANGUAGE DuplicateRecordFields #-}
module Temporal.Runtime (
Runtime,
TelemetryOptions (..),
Periodicity (..),
initializeRuntime,
withRuntime,
fetchLogs,
CoreLog (..),
LogLevel (..),
) where
import Control.Concurrent
import Control.Exception
import Data.Aeson
import qualified Data.ByteString.Lazy as BL
import qualified Data.Vector as V
import Foreign.C.String
import Foreign.C.Types (CInt)
import Foreign.ForeignPtr
import Foreign.Marshal
import Foreign.Ptr
import Foreign.StablePtr
import Foreign.Storable
import System.IO.Unsafe
import Temporal.Core.CTypes
import Temporal.Internal.FFI
initializeRuntime :: TelemetryOptions -> IO Runtime
initializeRuntime :: TelemetryOptions -> IO Runtime
initializeRuntime TelemetryOptions
opts = ByteString -> (Ptr (CArray Word8) -> IO Runtime) -> IO Runtime
forall b. ByteString -> (Ptr (CArray Word8) -> IO b) -> IO b
withCArrayBS (LazyByteString -> ByteString
BL.toStrict (LazyByteString -> ByteString) -> LazyByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ TelemetryOptions -> LazyByteString
forall a. ToJSON a => a -> LazyByteString
encode TelemetryOptions
opts) ((Ptr (CArray Word8) -> IO Runtime) -> IO Runtime)
-> (Ptr (CArray Word8) -> IO Runtime) -> IO Runtime
forall a b. (a -> b) -> a -> b
$ \Ptr (CArray Word8)
optsP ->
IO Runtime -> IO Runtime
forall a. IO a -> IO a
mask_ (IO Runtime -> IO Runtime) -> IO Runtime -> IO Runtime
forall a b. (a -> b) -> a -> b
$ do
rtP <- Ptr (CArray Word8) -> TryPutMVarFFI -> IO (Ptr Runtime)
initRuntime Ptr (CArray Word8)
optsP TryPutMVarFFI
tryPutMVarPtr
Runtime <$> newForeignPtr freeRuntime rtP
withRuntime :: Runtime -> (Ptr Runtime -> IO a) -> IO a
withRuntime :: forall a. Runtime -> (Ptr Runtime -> IO a) -> IO a
withRuntime (Runtime ForeignPtr Runtime
rvar) = ForeignPtr Runtime -> (Ptr Runtime -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Runtime
rvar
fetchLogs :: Runtime -> IO (V.Vector CoreLog)
fetchLogs :: Runtime -> IO (Vector CoreLog)
fetchLogs Runtime
r = Runtime
-> (Ptr Runtime -> IO (Vector CoreLog)) -> IO (Vector CoreLog)
forall a. Runtime -> (Ptr Runtime -> IO a) -> IO a
withRuntime Runtime
r ((Ptr Runtime -> IO (Vector CoreLog)) -> IO (Vector CoreLog))
-> (Ptr Runtime -> IO (Vector CoreLog)) -> IO (Vector CoreLog)
forall a b. (a -> b) -> a -> b
$ \Ptr Runtime
p -> do
IO (Ptr (CArray (CArray Word8)))
-> (Ptr (CArray (CArray Word8)) -> IO ())
-> (Ptr (CArray (CArray Word8)) -> IO (Vector CoreLog))
-> IO (Vector CoreLog)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Ptr Runtime -> IO (Ptr (CArray (CArray Word8)))
raw_fetchLogs Ptr Runtime
p) Ptr (CArray (CArray Word8)) -> IO ()
raw_freeLogs ((Ptr (CArray (CArray Word8)) -> IO (Vector CoreLog))
-> IO (Vector CoreLog))
-> (Ptr (CArray (CArray Word8)) -> IO (Vector CoreLog))
-> IO (Vector CoreLog)
forall a b. (a -> b) -> a -> b
$ \Ptr (CArray (CArray Word8))
clogs -> do
logs <- Ptr (CArray (CArray Word8)) -> IO (CArray (CArray Word8))
forall a. Storable a => Ptr a -> IO a
peek Ptr (CArray (CArray Word8))
clogs
vec <- cArrayToVector cArrayToByteString logs
V.mapM throwDecodeStrict vec