module Extism.PDK.HTTP where

import Extism.Manifest(toString, HTTPRequest(..), method, headers, url)
import Extism.JSON(Nullable(..), decode, JSON, Result(..))
import Extism.PDK.Bindings
import Extism.PDK
import Data.Word
import Data.ByteString as B

-- | HTTP Request
type Request = HTTPRequest

-- | HTTP Response
data Response = Response
  {
    Response -> Int
statusCode :: Int
  , Response -> Memory
memory :: Memory
  }

-- | Creates a new 'Request'
newRequest :: String -> Request
newRequest :: String -> Request
newRequest String
url =
  HTTPRequest {
    url :: String
url = String
url
  , headers :: Nullable [(String, String)]
headers = Nullable [(String, String)]
forall a. Nullable a
Null
  , method :: Nullable String
method = Nullable String
forall a. Nullable a
Null
  }

-- | Update a 'Request' with the provided HTTP request method (GET, POST, PUT, DELETE, ...)
withMethod :: String -> Request -> Request
withMethod :: String -> Request -> Request
withMethod String
meth Request
req =
  Request
req { method = NotNull meth }

-- | Update a 'Request' with the provided HTTP request headers
withHeaders :: [(String, String)] -> Request -> Request
withHeaders :: [(String, String)] -> Request -> Request
withHeaders [(String, String)]
h Request
req =
  Request
req { headers = NotNull h }

-- | Access the Memory block associated with a 'Response'
responseMemory :: Response -> Memory
responseMemory :: Response -> Memory
responseMemory (Response Int
_ Memory
mem) = Memory
mem

-- | Get the 'Response' body as a 'ByteString'
responseByteString :: Response -> IO ByteString
responseByteString :: Response -> IO ByteString
responseByteString (Response Int
_ Memory
mem) = Memory -> IO ByteString
forall a. FromBytes a => Memory -> IO a
load Memory
mem

-- | Get the 'Response' body as a 'String'
responseString :: Response -> IO String
responseString :: Response -> IO String
responseString (Response Int
_ Memory
mem) = Memory -> IO String
loadString Memory
mem

-- | Get the 'Response' body as JSON
responseJSON :: JSON a => Response -> IO (Either String a)
responseJSON :: forall a. JSON a => Response -> IO (Either String a)
responseJSON (Response Int
_ Memory
mem) = do
  Result a
json <- String -> Result a
forall a. JSON a => String -> Result a
decode (String -> Result a) -> IO String -> IO (Result a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Memory -> IO String
loadString Memory
mem
  case Result a
json of
    Ok a
json -> Either String a -> IO (Either String a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String a -> IO (Either String a))
-> Either String a -> IO (Either String a)
forall a b. (a -> b) -> a -> b
$ a -> Either String a
forall a b. b -> Either a b
Right a
json
    Extism.JSON.Error String
msg -> Either String a -> IO (Either String a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String a
forall a b. a -> Either a b
Left String
msg)


-- | Send HTTP request with an optional request body
sendRequest :: Request -> Maybe ByteString -> IO Response
sendRequest :: Request -> Maybe ByteString -> IO Response
sendRequest Request
req Maybe ByteString
b =
  let json :: String
json = Request -> String
forall a. JSON a => a -> String
Extism.Manifest.toString Request
req in
  let bodyMem :: IO Memory
bodyMem = case Maybe ByteString
b of
               Maybe ByteString
Nothing -> Memory -> IO Memory
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Memory -> IO Memory) -> Memory -> IO Memory
forall a b. (a -> b) -> a -> b
$ MemoryOffset -> MemoryOffset -> Memory
Memory MemoryOffset
0 MemoryOffset
0
               Just ByteString
b -> ByteString -> IO Memory
allocByteString ByteString
b
  in
  do
    Memory
body <- IO Memory
bodyMem
    Memory
j <- String -> IO Memory
allocString String
json
    MemoryOffset
res <- MemoryOffset -> MemoryOffset -> IO MemoryOffset
extismHTTPRequest (Memory -> MemoryOffset
memoryOffset Memory
j) (Memory -> MemoryOffset
memoryOffset Memory
body)
    Memory -> IO ()
free Memory
j
    Memory -> IO ()
free Memory
body
    Int32
code <- IO Int32
extismHTTPStatusCode
    if MemoryOffset
res MemoryOffset -> MemoryOffset -> Bool
forall a. Eq a => a -> a -> Bool
== MemoryOffset
0 then
      Response -> IO Response
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Memory -> Response
Response (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
code) (MemoryOffset -> MemoryOffset -> Memory
Memory MemoryOffset
0 MemoryOffset
0))
    else do
      Memory
mem <- MemoryOffset -> IO Memory
findMemory MemoryOffset
res
      Response -> IO Response
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Memory -> Response
Response (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
code) Memory
mem)