{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module GitHub.REST.Endpoint
( GHEndpoint(..)
, EndpointVals
, GitHubData
, endpointPath
, renderMethod
) where
import Data.Maybe (fromMaybe)
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
import Data.Text (Text)
import qualified Data.Text as Text
import Network.HTTP.Types (Method, StdMethod, renderStdMethod)
import GitHub.REST.KeyValue (KeyValue, kvToText)
type EndpointVals = [KeyValue]
type GitHubData = [KeyValue]
data GHEndpoint = GHEndpoint
{ method :: StdMethod
, endpoint :: Text
, endpointVals :: EndpointVals
, ghData :: GitHubData
}
endpointPath :: GHEndpoint -> Text
endpointPath GHEndpoint{..} = Text.intercalate "/" . map populate . Text.splitOn "/" $ endpoint
where
values = map kvToText endpointVals
populate t = case Text.uncons t of
Just (':', key) -> fromMaybe
(fail' $ "Could not find value for key '" <> key <> "'")
$ lookup key values
_ -> t
fail' msg = error . Text.unpack $ msg <> ": " <> endpoint
renderMethod :: GHEndpoint -> Method
renderMethod = renderStdMethod . method