Skip to content

Commit

Permalink
Adding internal Base64 type to transparently handle bytes encoding
Browse files Browse the repository at this point in the history
Fixes #26
  • Loading branch information
brendanhay committed Jun 14, 2016
1 parent cdb65aa commit a254f07
Show file tree
Hide file tree
Showing 3 changed files with 81 additions and 25 deletions.
4 changes: 3 additions & 1 deletion core/gogol-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@ library
ghc-options: -Wall

exposed-modules:
Network.Google.Data.JSON
Network.Google.Data.Base64
, Network.Google.Data.JSON
, Network.Google.Data.Numeric
, Network.Google.Data.Time
, Network.Google.Prelude
Expand All @@ -58,6 +59,7 @@ library
, http-media >= 0.6
, http-types >= 0.8.6
, lens >= 4.4
, memory >= 0.8
, resourcet >= 1.1
, scientific >= 0.3
, servant >= 0.4.4
Expand Down
53 changes: 53 additions & 0 deletions core/src/Network/Google/Data/Base64.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-- |
-- Module : Network.Google.Data.Base64
-- Copyright : (c) 2013-2016 Brendan Hay
-- License : Mozilla Public License, v. 2.0.
-- Maintainer : Brendan Hay <[email protected]>
-- Stability : provisional
-- Portability : non-portable (GHC extensions)
--
module Network.Google.Data.Base64
( Base64 (..)
, _Base64
) where

import Control.Lens (Iso', iso)
import Data.Aeson (FromJSON (..), ToJSON (..))
import qualified Data.ByteArray.Encoding as BA
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS8
import Data.Data (Data, Typeable)
import Data.Hashable
import qualified Data.Text.Encoding as Text
import GHC.Generics (Generic)
import Network.Google.Data.JSON (parseJSONText, toJSONText)
import Web.HttpApiData (FromHttpApiData (..),
ToHttpApiData (..))

-- | Base64 encoded binary data.
--
-- Encoding\/decoding is automatically deferred to serialisation and deserialisation
-- respectively.
newtype Base64 = Base64 { unBase64 :: ByteString }
deriving (Eq, Read, Ord, Data, Typeable, Generic)

instance Hashable Base64

_Base64 :: Iso' Base64 ByteString
_Base64 = iso unBase64 Base64

instance ToHttpApiData Base64 where
toQueryParam = Text.decodeUtf8 . toHeader
toHeader = BA.convertToBase BA.Base64 . unBase64

instance FromHttpApiData Base64 where
parseQueryParam = parseHeader . Text.encodeUtf8
parseHeader = either fail (pure . Base64) . BA.convertFromBase BA.Base64

instance Show Base64 where show = show . BS8.unpack . unBase64
instance FromJSON Base64 where parseJSON = parseJSONText "Base64"
instance ToJSON Base64 where toJSON = toJSONText
49 changes: 25 additions & 24 deletions core/src/Network/Google/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,27 +10,28 @@ module Network.Google.Prelude
( module Export
) where

import Control.Lens as Export (Lens', lens, mapping,
( # ), (^.), _Just)
import Data.Data as Export (Data, Typeable)
import Data.Hashable as Export
import Data.HashMap.Strict as Export (HashMap)
import Data.Int as Export (Int32, Int64)
import Data.Maybe as Export
import Data.Monoid as Export (mempty, (<>))
import Data.Proxy as Export
import Data.Text as Export (Text)
import Data.Time as Export (Day, TimeOfDay, UTCTime)
import Data.Word as Export (Word32, Word64, Word8)
import GHC.Generics as Export (Generic)
import Network.Google.Data.JSON as Export
import Network.Google.Data.Numeric as Export
import Network.Google.Data.Time as Export
import Network.Google.Types as Export
import Network.HTTP.Client as Export (RequestBody)
import Numeric.Natural as Export (Natural)
import Prelude as Export hiding (product)
import Servant.API as Export hiding (getResponse)
import Servant.Utils.Links as Export hiding (Link)
import Web.HttpApiData as Export (FromHttpApiData (..),
ToHttpApiData (..))
import Control.Lens as Export (Lens', lens, mapping, ( # ), (^.), _Just)
import Data.ByteString as Export (ByteString)
import Data.Data as Export (Data, Typeable)
import Data.Hashable as Export
import Data.HashMap.Strict as Export (HashMap)
import Data.Int as Export (Int32, Int64)
import Data.Maybe as Export
import Data.Monoid as Export (mempty, (<>))
import Data.Proxy as Export
import Data.Text as Export (Text)
import Data.Time as Export (Day, TimeOfDay, UTCTime)
import Data.Word as Export (Word32, Word64, Word8)
import GHC.Generics as Export (Generic)
import Network.HTTP.Client as Export (RequestBody)
import Numeric.Natural as Export (Natural)
import Prelude as Export hiding (product)
import Servant.API as Export hiding (getResponse)
import Servant.Utils.Links as Export hiding (Link)
import Web.HttpApiData as Export (FromHttpApiData (..), ToHttpApiData (..))

import Network.Google.Data.Base64 as Export
import Network.Google.Data.JSON as Export
import Network.Google.Data.Numeric as Export
import Network.Google.Data.Time as Export
import Network.Google.Types as Export

0 comments on commit a254f07

Please sign in to comment.