Skip to content

Commit

Permalink
Add APIKey{,s}
Browse files Browse the repository at this point in the history
  • Loading branch information
markandrus committed Oct 3, 2016
1 parent 093b0c5 commit 3d67227
Show file tree
Hide file tree
Showing 7 changed files with 163 additions and 6 deletions.
52 changes: 52 additions & 0 deletions src/Twilio/APIKey.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,52 @@
{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE OverloadedStrings #-}
{-#LANGUAGE ViewPatterns #-}

module Twilio.APIKey
( -- * Resource
APIKey(..)
, APIKeySID
, Twilio.APIKey.get
) where

import Control.Applicative
import Control.Monad
import Control.Monad.Catch
import Data.Aeson
import Data.Monoid
import Data.Text (Text)
import Data.Time.Clock
import Network.URI

import Control.Monad.Twilio
import Twilio.Internal.Parser
import Twilio.Internal.Request
import Twilio.Internal.Resource as Resource
import Twilio.Types

{- Resource -}

data APIKey = APIKey
{ sid :: !APIKeySID
, friendlyName :: !Text
, secret :: !(Maybe Text)
, dateCreated :: !UTCTime
, dateUpdated :: !UTCTime
} deriving (Show, Eq, Ord)

instance FromJSON APIKey where
parseJSON (Object v) = APIKey
<$> v .: "sid"
<*> v .: "friendly_name"
<*> v .:? "secret"
<*> (v .: "date_created" >>= parseDateTime)
<*> (v .: "date_updated" >>= parseDateTime)
parseJSON _ = mzero

instance Get1 APIKeySID APIKey where
get1 (getSID -> sid) = request parseJSONFromResponse =<< makeTwilioRequest
("/Keys/" <> sid <> ".json")

get :: MonadThrow m => APIKeySID -> TwilioT m APIKey
get = Resource.get
61 changes: 61 additions & 0 deletions src/Twilio/APIKeys.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,61 @@
{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE OverloadedStrings #-}
{-#LANGUAGE RankNTypes #-}

module Twilio.APIKeys
( -- * Resource
APIKeys(..)
, Twilio.APIKeys.get
) where

import Control.Applicative
import Control.Monad.Catch
import Data.Aeson
import Data.Maybe
import Data.Text (Text)
import Data.Text.Encoding

import Control.Monad.Twilio
import Twilio.APIKey
import Twilio.Internal.Request
import Twilio.Internal.Resource as Resource
import Twilio.Types

{- Resource -}

data APIKeys = APIKeys
{ pagingInformation :: !PagingInformation
, list :: ![APIKey]
} deriving (Show, Eq, Ord)

instance List APIKeys APIKey where
getListWrapper = wrap (APIKeys . fromJust)
getList = list
getPlural = Const "keys"

instance FromJSON APIKeys where
parseJSON = parseJSONToList

instance Get0 APIKeys where
get0 = request parseJSONFromResponse =<< makeTwilioRequest "/Keys.json"

{- | Get 'APIKeys'.
For example, you can fetch the 'APIKeys' resource in the 'IO' monad as follows:
>module Main where
>
>import Control.Monad.IO.Class (liftIO)
>import System.Environment (getEnv)
>import Twilio.APIKeys as APIKeys
>import Twilio.Types
>
>-- | Print API Keys.
>main :: IO ()
>main = runTwilio' (getEnv "ACCOUNT_SID")
> (getEnv "AUTH_TOKEN")
> $ APIKeys.get >>= liftIO . print
-}
get :: MonadThrow m => TwilioT m APIKeys
get = Resource.get
1 change: 1 addition & 0 deletions src/Twilio/Internal/Request.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,4 +69,5 @@ runRequest' credentials (RequestT (FreeT m)) = m >>= \case
else do
let body = responseBody response
body' <- LBS.fromChunks <$> brConsume body
print body'
go $ const body' <$> response
10 changes: 5 additions & 5 deletions src/Twilio/Types/List.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,11 +54,11 @@ data PagingInformation = PagingInformation
{ -- | The current page number. Zero-indexed, so the first page is 0.
pageNumber :: !Integer
-- | The total number of pages.
, numberOfPages :: !Integer
, numberOfPages :: !(Maybe Integer)
-- | How many items are in each page.
, pageSize :: !Integer
-- | The total number of items in the list.
, total :: !Integer
, total :: !(Maybe Integer)
-- | The position in the overall list of the first item in this page.
, start :: !Integer
-- | The position in the overall list of the last item in this page.
Expand All @@ -79,9 +79,9 @@ instance FromJSON PagingInformation where
parseJSON (Object v)
= PagingInformation
<$> v .: "page"
<*> v .: "num_pages"
<*> v .:? "num_pages"
<*> v .: "page_size"
<*> v .: "total"
<*> v .:? "total"
<*> v .: "start"
<*> v .: "end"
<*> (v .: "uri" <&> fmap parseRelativeReference
Expand All @@ -92,7 +92,7 @@ instance FromJSON PagingInformation where
>>= maybeReturn')
<*> (v .: "previous_page_uri" <&> fmap parseRelativeReference
>>= maybeReturn')
<*> (v .: "last_page_uri" <&> fmap parseRelativeReference
<*> (v .:? "last_page_uri" <&> fmap parseRelativeReference
>>= maybeReturn')
parseJSON _ = mzero

Expand Down
15 changes: 15 additions & 0 deletions src/Twilio/Types/SID.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Twilio.Types.SID
-- ** Instances
, AccountSID
, AddressSID
, APIKeySID
, ApplicationSID
, CallSID
, ConferenceSID
Expand Down Expand Up @@ -65,6 +66,20 @@ instance FromJSON AddressSID where
instance ToJSON AddressSID where
toJSON = sidToJSON

{- Api Key SID -}

newtype APIKeySID = APIKeySID { getAPIKeySID :: Text }
deriving (Data, Eq, Generic, Ord, Read, Show, Typeable)

instance SID APIKeySID where
getPrefix = Const ('S', 'K')

instance FromJSON APIKeySID where
parseJSON = parseSIDFromJSON

instance ToJSON APIKeySID where
toJSON = sidToJSON

{- Application SID -}

newtype ApplicationSID = ApplicationSID { getApplicationSID :: Text }
Expand Down
28 changes: 27 additions & 1 deletion test/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Main where
import Control.Exception.Base
import Control.Monad
import Control.Monad.IO.Class
import Data.Maybe (fromJust)
import Data.Monoid
import Data.Text (Text, unpack)
import Network.URI
Expand All @@ -17,6 +18,10 @@ import Twilio.Accounts (Accounts)
import Twilio.Accounts as Accounts
import Twilio.Addresses (Addresses)
import Twilio.Addresses as Addresses
import Twilio.APIKey (APIKey)
import Twilio.APIKey as APIKey
import Twilio.APIKeys (APIKeys)
import Twilio.APIKeys as APIKeys
import Twilio.Applications (Applications)
import Twilio.Applications as Applications
import Twilio.AuthorizedConnectApps (AuthorizedConnectApps)
Expand Down Expand Up @@ -52,6 +57,7 @@ import Twilio.UsageRecords as UsageRecords
import Twilio.UsageTriggers (UsageTriggers)
import Twilio.UsageTriggers as UsageTriggers

import Twilio.Types.SID (parseSID)
import Twilio.Internal.Resource (post)

main :: IO ()
Expand All @@ -76,9 +82,11 @@ main = runTwilio' (getEnv "ACCOUNT_SID")
, UsageTriggers.get >>= liftIO . print -} ]

-- account { sid = accountSID } <- testPOSTAccounts
-- accounts <- testGETAccounts
accounts <- testGETAccounts
-- testGETAccount accountSID

apiKeys <- testGETAPIKeys

Call { Call.sid = callSID } <- testPOSTCalls
calls <- testGETCalls
testGETCall callSID
Expand Down Expand Up @@ -121,6 +129,24 @@ testGETAccount accountSID = do
liftIO $ print account
return account

{- Api Keys -}

testGETAPIKeys :: Twilio APIKeys
testGETAPIKeys = do
liftIO $ putStrLn "GET /Keys"
apiKeys <- APIKeys.get
liftIO $ print apiKeys
return apiKeys

{- Api Key -}

testGETAPIKey :: APIKeySID -> Twilio APIKey
testGETAPIKey apiKeySID = do
liftIO . putStrLn . unpack $ "GET /Keys/" <> getSID apiKeySID
apiKey <- APIKey.get apiKeySID
liftIO $ print apiKey
return apiKey

{- Calls -}

testPOSTCalls :: Twilio Call
Expand Down
2 changes: 2 additions & 0 deletions twilio.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,8 @@ library
Twilio.Accounts,
Twilio.Address,
Twilio.Addresses,
Twilio.APIKey,
Twilio.APIKeys,
Twilio.Application,
Twilio.Applications,
Twilio.AuthorizedConnectApp,
Expand Down

0 comments on commit 3d67227

Please sign in to comment.