{-# LINE 1 "src/Data/Emacs/Module/Runtime.hsc" #-}
----------------------------------------------------------------------------
-- |
-- Module      :  Data.Emacs.Module.Runtime
-- Copyright   :  (c) Sergey Vinokurov 2018
-- License     :  Apache-2.0 (see LICENSE)
-- Maintainer  :  serg.foo@gmail.com
----------------------------------------------------------------------------

{-# LANGUAGE UnliftedFFITypes #-}

module Data.Emacs.Module.Runtime
  ( Runtime(..)
  , validateRuntime
  , withEnvironment
  ) where

import Control.Monad.Base

import Foreign
import Foreign.C.Types

import Data.Emacs.Module.Env qualified as Emacs
import Data.Emacs.Module.Raw.Env.Internal (Env(..))
import Data.Emacs.Module.NonNullPtr

import Data.Emacs.Module.NonNullPtr.Internal



-- | Emacs environment, right from the 'emacs-module.h'.
newtype Runtime = Runtime { Runtime -> NonNullPtr Runtime
unRuntime :: NonNullPtr Runtime }

type GetEnvironentType = Runtime -> Emacs.Env

foreign import ccall unsafe "dynamic" emacs_get_environment
  :: FunPtr GetEnvironentType -> GetEnvironentType

validateRuntime :: MonadBase IO m => Ptr Runtime -> m (Maybe Runtime)
validateRuntime :: forall (m :: * -> *).
MonadBase IO m =>
Ptr Runtime -> m (Maybe Runtime)
validateRuntime !Ptr Runtime
ptr
  | Ptr Runtime
ptr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
  | Bool
otherwise      = forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase forall a b. (a -> b) -> a -> b
$ do
      CPtrdiff
size <- ((\Ptr Runtime
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Runtime
hsc_ptr Int
0)) Ptr Runtime
ptr
{-# LINE 43 "src/Data/Emacs/Module/Runtime.hsc" #-}
      pure $ if expectedSize <= size then Just (Runtime (NonNullPtr ptr)) else Nothing
  where
    expectedSize :: CPtrdiff
    expectedSize :: CPtrdiff
expectedSize = ((CPtrdiff
24))
{-# LINE 47 "src/Data/Emacs/Module/Runtime.hsc" #-}

withEnvironment :: Runtime -> (Emacs.Env -> IO a) -> IO a
withEnvironment :: forall a. Runtime -> (Env -> IO a) -> IO a
withEnvironment !Runtime
runtime Env -> IO a
k = do
  (FunPtr GetEnvironentType
funPtr :: FunPtr GetEnvironentType) <- ((\Ptr Runtime
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Runtime
hsc_ptr Int
16)) (forall a. NonNullPtr a -> Ptr a
unNonNullPtr forall a b. (a -> b) -> a -> b
$ Runtime -> NonNullPtr Runtime
unRuntime Runtime
runtime)
{-# LINE 51 "src/Data/Emacs/Module/Runtime.hsc" #-}
  k (emacs_get_environment funPtr runtime)