module Database.Neo4j.Http where
import Control.Exception.Base (Exception, throw, catch, toException)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Resource (runResourceT)
import Data.Default (def)
import Data.Maybe (fromMaybe)
import Data.Aeson ((.:))
import Data.Aeson.Types (parseMaybe)
import qualified Data.Aeson as J
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
import qualified Network.HTTP.Conduit as HC
import qualified Network.HTTP.Types as HT
import Database.Neo4j.Types
newConnection :: Hostname -> Port -> IO Connection
newConnection hostname port = do
mgr <- HC.newManager HC.conduitManagerSettings
return $ Connection hostname port mgr
withConnection :: Hostname -> Port -> Neo4j a -> IO a
withConnection hostname port cmds = runResourceT $ HC.withManager $
\mgr -> liftIO $ runNeo4j cmds $ Connection hostname port mgr
httpReq :: Connection -> HT.Method -> S.ByteString -> L.ByteString -> (HT.Status -> Bool) ->
IO (HC.Response L.ByteString)
httpReq (Connection h p m) method path body statusCheck = do
let request = def {
HC.host = h,
HC.port = p,
HC.path = path,
HC.method = method,
HC.requestBody = HC.RequestBodyLBS body,
HC.checkStatus = \s _ _ -> if statusCheck s
then Nothing
else Just (toException $ Neo4jUnexpectedResponseException s),
HC.requestHeaders = [(HT.hAccept, "application/json; charset=UTF-8"),
(HT.hContentType, "application/json")]}
liftIO $ HC.httpLbs request m `catch` wrapException
where wrapException :: HC.HttpException -> a
wrapException = throw . Neo4jHttpException . show
extractException :: HC.Response L.ByteString -> T.Text
extractException resp = fromMaybe "" $ do
resobj <- J.decode $ HC.responseBody resp
flip parseMaybe resobj $ \obj -> obj .: "exception"
httpCreate :: J.FromJSON a => Connection -> S.ByteString -> L.ByteString -> IO a
httpCreate conn path body = do
res <- httpReq conn HT.methodPost path body (`elem` [HT.status200, HT.status201])
let resBody = J.eitherDecode $ HC.responseBody res
return $ case resBody of
Right entity -> entity
Left e -> throw $ Neo4jParseException ("Error parsing created entity: " ++ e)
httpCreateWithHeaders :: J.FromJSON a => Connection -> S.ByteString -> L.ByteString -> IO (a, HT.ResponseHeaders)
httpCreateWithHeaders conn path body = do
res <- httpReq conn HT.methodPost path body (`elem` [HT.status200, HT.status201])
let resBody = J.eitherDecode $ HC.responseBody res
let result = case resBody of
Right entity -> entity
Left e -> throw $ Neo4jParseException ("Error parsing created entity: " ++ e)
let headers = HC.responseHeaders res
return (result, headers)
httpCreate500Explained :: J.FromJSON a => Connection -> S.ByteString -> L.ByteString ->
IO (Either L.ByteString a)
httpCreate500Explained conn path body = do
res <- httpReq conn HT.methodPost path body (`elem` [HT.status200, HT.status201, HT.status500])
let status = HC.responseStatus res
let resBody = HC.responseBody res
return $ if status == HT.status500 then Left resBody else parseBody resBody
where parseBody b = case J.eitherDecode b of
Right entity -> Right entity
Left e -> throw $ Neo4jParseException ("Error parsing created entity: " ++ e)
httpCreate4XXExplained :: J.FromJSON a => Connection -> S.ByteString -> L.ByteString -> IO (Either T.Text a)
httpCreate4XXExplained conn path body = do
res <- httpReq conn HT.methodPost path body (\s -> s `elem` validcodes ++ errcodes)
let status = HC.responseStatus res
return $ if status `elem` validcodes then parseBody res else Left $ extractException res
where parseBody resp = case J.eitherDecode $ HC.responseBody resp of
Right entity -> Right entity
Left e -> throw $ Neo4jParseException ("Error parsing created entity: " ++ e)
validcodes = [HT.status200, HT.status201]
errcodes = [HT.status404, HT.status400]
httpCreate_ :: Connection -> S.ByteString -> L.ByteString -> IO ()
httpCreate_ conn path body = do
_ <- httpReq conn HT.methodPost path body (\s -> s == HT.status201 || s == HT.status204)
return ()
httpRetrieve :: J.FromJSON a => Connection -> S.ByteString -> IO (Maybe a)
httpRetrieve conn path = do
res <- httpReq conn HT.methodGet path "" (\s -> s == HT.status200 || s == HT.status404)
let status = HC.responseStatus res
let body = if status == HT.status200
then Just $ J.eitherDecode $ HC.responseBody res
else Nothing
return $ case body of
Just (Right entity) -> Just entity
Just (Left e) -> throw $ Neo4jParseException ("Error parsing received entity: " ++ e)
Nothing -> Nothing
httpRetrieveSure :: J.FromJSON a => Connection -> S.ByteString -> IO a
httpRetrieveSure conn path = do
res <- httpReq conn HT.methodGet path "" (==HT.status200)
let body = J.eitherDecode $ HC.responseBody res
return $ case body of
Right entity -> entity
Left e -> throw $ Neo4jParseException ("Error parsing received entity: " ++ e)
httpRetrieveValue :: J.FromJSON a => Connection -> S.ByteString -> IO (Either T.Text a)
httpRetrieveValue conn path = do
res <- httpReq conn HT.methodGet path "" (\s -> s == HT.status200 || s == HT.status404)
let status = HC.responseStatus res
return $ if status == HT.status200 then parseBody res else Left $ extractException res
where parseBody resp = case J.eitherDecode $ "[" `L.append` HC.responseBody resp `L.append` "]" of
Right (entity:[]) -> Right entity
Right _ -> throw $ Neo4jParseException "Error parsing received entity"
Left e -> throw $ Neo4jParseException ("Error parsing received entity: " ++ e)
httpDelete :: Connection -> S.ByteString -> IO ()
httpDelete c pth = do
_ <- httpReq c HT.methodDelete pth "" (\s -> s == HT.status204 || s == HT.status404)
return ()
httpDeleteNo404 :: Connection -> S.ByteString -> IO ()
httpDeleteNo404 c pth = do
_ <- httpReq c HT.methodDelete pth "" (==HT.status204)
return ()
httpDelete404Explained :: Connection -> S.ByteString -> IO (Either T.Text ())
httpDelete404Explained c pth = do
res <- httpReq c HT.methodDelete pth "" (\s -> s == HT.status204 || s == HT.status404)
let status = HC.responseStatus res
return $ if status /= HT.status404 then Right () else Left $ extractException res
httpModify :: Connection -> S.ByteString -> L.ByteString -> IO ()
httpModify c path body = do
_ <- httpReq c HT.methodPut path body (\s -> s == HT.status200 || s == HT.status204)
return ()
httpModify404Explained :: Connection -> S.ByteString -> L.ByteString -> IO (Either T.Text ())
httpModify404Explained c path body = do
res <- httpReq c HT.methodPut path body (\s -> s == HT.status200 || s == HT.status204 || s == HT.status404)
let status = HC.responseStatus res
return $ if status /= HT.status404 then Right () else Left $ extractException res
proc404Exc :: Entity e => e -> Neo4jException -> a
proc404Exc e exc@(Neo4jUnexpectedResponseException s)
| s == HT.status404 = throw (Neo4jNoEntityException $ entityPath e)
| otherwise = throw exc
proc404Exc _ exc = throw exc