{-# LANGUAGE OverloadedStrings #-}
module Web.Stripe.Util
(
fromSeconds
, toSeconds
, paramsToByteString
, toText
, toTextLower
, getParams
, toBytestring
, (</>)
, toMetaData
, toExpandable
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B8
import Data.Monoid (Monoid, mconcat, mempty, (<>))
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Time.Clock (UTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime, utcTimeToPOSIXSeconds)
toText
:: Show a
=> a
-> Text
toText = T.pack . show
toTextLower
:: Show a
=> a
-> Text
toTextLower = T.toLower . T.pack . show
paramsToByteString
:: (Monoid m, IsString m)
=> [(m, m)]
-> m
paramsToByteString [] = mempty
paramsToByteString ((x,y) : []) = x <> "=" <> y
paramsToByteString ((x,y) : xs) =
mconcat [ x, "=", y, "&" ] <> paramsToByteString xs
(</>)
:: (Monoid m, IsString m)
=> m
-> m
-> m
m1 </> m2 = m1 <> "/" <> m2
fromSeconds
:: Integer
-> UTCTime
fromSeconds = posixSecondsToUTCTime . fromInteger
toSeconds
:: UTCTime
-> Integer
toSeconds = round . utcTimeToPOSIXSeconds
getParams
:: [(ByteString, Maybe Text)]
-> [(ByteString, ByteString)]
getParams xs = [ (x, T.encodeUtf8 y) | (x, Just y) <- xs ]
toBytestring :: Show a => a -> ByteString
toBytestring = B8.pack . show
toMetaData :: [(Text, Text)] -> [(ByteString, ByteString)]
toMetaData = map toKV
where
toKV (k,v) = ("metadata[" <> T.encodeUtf8 k <> "]", T.encodeUtf8 v)
toExpandable :: [Text] -> [(ByteString, ByteString)]
toExpandable = map toKV
where
toKV v = ("expand[]", T.encodeUtf8 v)