-- Copyright (C) 2013, 2014 Fraser Tweedale -- -- Licensed under the Apache License, Version 2.0 (the "License"); -- you may not use this file except in compliance with the License. -- You may obtain a copy of the License at -- -- http://www.apache.org/licenses/LICENSE-2.0 -- -- Unless required by applicable law or agreed to in writing, software -- distributed under the License is distributed on an "AS IS" BASIS, -- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. -- See the License for the specific language governing permissions and -- limitations under the License. {-# LANGUAGE OverloadedStrings #-} {-| Internal utility functions for encoding/decoding JOSE types. -} module Crypto.JOSE.Types.Internal where import Data.Tuple (swap) import Data.Aeson.Types import qualified Data.ByteString as B import qualified Data.ByteString.Base64 as B64 import qualified Data.ByteString.Base64.URL as B64U import qualified Data.HashMap.Strict as M import qualified Data.Text as T import qualified Data.Text.Encoding as E -- | Convert a JSON object into a list of pairs or the empty list -- if the JSON value is not an object. -- objectPairs :: Value -> [Pair] objectPairs (Object o) = M.toList o objectPairs _ = [] -- | Produce a parser of base64 encoded text from a bytestring parser. -- parseB64 :: FromJSON a => (B.ByteString -> Parser a) -> T.Text -> Parser a parseB64 f = either fail f . decodeB64 where decodeB64 = B64.decode . E.encodeUtf8 -- | Convert a bytestring to a base64 encoded JSON 'String' -- encodeB64 :: B.ByteString -> Value encodeB64 = String . E.decodeUtf8 . B64.encode -- | Add appropriate base64 '=' padding. -- pad :: B.ByteString -> B.ByteString pad s = s `B.append` B.replicate ((4 - B.length s `mod` 4) `mod` 4) 61 -- | Strip base64 '=' padding. -- unpad :: B.ByteString -> B.ByteString unpad = B.reverse . B.dropWhile (== 61) . B.reverse -- | Produce a parser of base64url encoded text from a bytestring parser. -- parseB64Url :: FromJSON a => (B.ByteString -> Parser a) -> T.Text -> Parser a parseB64Url f = either fail f . B64U.decode . pad . E.encodeUtf8 -- | Convert a bytestring to a base64url encoded JSON 'String' -- encodeB64Url :: B.ByteString -> Value encodeB64Url = String . E.decodeUtf8 . unpad . B64U.encode -- | Convert an unsigned big endian octet sequence to the integer -- it represents. -- bsToInteger :: B.ByteString -> Integer bsToInteger = B.foldl (\acc x -> acc * 256 + toInteger x) 0 -- | Convert an integer to its unsigned big endian representation as -- an octet sequence. -- integerToBS :: Integer -> B.ByteString integerToBS = B.reverse . B.unfoldr (fmap swap . f) where f x = if x == 0 then Nothing else Just (toWord8 $ quotRem x 256) toWord8 (seed, x) = (seed, fromIntegral x) sizedIntegerToBS :: Int -> Integer -> B.ByteString sizedIntegerToBS w = zeroPad . integerToBS where zeroPad xs = B.replicate (w - B.length xs) 0 `B.append` xs