module Network.AWS.SNS.ListEndpointsByPlatformApplication
    (
    
      ListEndpointsByPlatformApplication
    
    , listEndpointsByPlatformApplication
    
    , lebpaNextToken
    , lebpaPlatformApplicationArn
    
    , ListEndpointsByPlatformApplicationResponse
    
    , listEndpointsByPlatformApplicationResponse
    
    , lebparEndpoints
    , lebparNextToken
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.Query
import Network.AWS.SNS.Types
import qualified GHC.Exts
data ListEndpointsByPlatformApplication = ListEndpointsByPlatformApplication
    { _lebpaNextToken              :: Maybe Text
    , _lebpaPlatformApplicationArn :: Text
    } deriving (Eq, Ord, Show)
listEndpointsByPlatformApplication :: Text 
                                   -> ListEndpointsByPlatformApplication
listEndpointsByPlatformApplication p1 = ListEndpointsByPlatformApplication
    { _lebpaPlatformApplicationArn = p1
    , _lebpaNextToken              = Nothing
    }
lebpaNextToken :: Lens' ListEndpointsByPlatformApplication (Maybe Text)
lebpaNextToken = lens _lebpaNextToken (\s a -> s { _lebpaNextToken = a })
lebpaPlatformApplicationArn :: Lens' ListEndpointsByPlatformApplication Text
lebpaPlatformApplicationArn =
    lens _lebpaPlatformApplicationArn
        (\s a -> s { _lebpaPlatformApplicationArn = a })
data ListEndpointsByPlatformApplicationResponse = ListEndpointsByPlatformApplicationResponse
    { _lebparEndpoints :: List "Endpoints" Endpoint
    , _lebparNextToken :: Maybe Text
    } deriving (Eq, Show)
listEndpointsByPlatformApplicationResponse :: ListEndpointsByPlatformApplicationResponse
listEndpointsByPlatformApplicationResponse = ListEndpointsByPlatformApplicationResponse
    { _lebparEndpoints = mempty
    , _lebparNextToken = Nothing
    }
lebparEndpoints :: Lens' ListEndpointsByPlatformApplicationResponse [Endpoint]
lebparEndpoints = lens _lebparEndpoints (\s a -> s { _lebparEndpoints = a }) . _List
lebparNextToken :: Lens' ListEndpointsByPlatformApplicationResponse (Maybe Text)
lebparNextToken = lens _lebparNextToken (\s a -> s { _lebparNextToken = a })
instance ToPath ListEndpointsByPlatformApplication where
    toPath = const "/"
instance ToQuery ListEndpointsByPlatformApplication where
    toQuery ListEndpointsByPlatformApplication{..} = mconcat
        [ "NextToken"              =? _lebpaNextToken
        , "PlatformApplicationArn" =? _lebpaPlatformApplicationArn
        ]
instance ToHeaders ListEndpointsByPlatformApplication
instance AWSRequest ListEndpointsByPlatformApplication where
    type Sv ListEndpointsByPlatformApplication = SNS
    type Rs ListEndpointsByPlatformApplication = ListEndpointsByPlatformApplicationResponse
    request  = post "ListEndpointsByPlatformApplication"
    response = xmlResponse
instance FromXML ListEndpointsByPlatformApplicationResponse where
    parseXML = withElement "ListEndpointsByPlatformApplicationResult" $ \x -> ListEndpointsByPlatformApplicationResponse
        <$> x .@  "Endpoints"
        <*> x .@? "NextToken"
instance AWSPager ListEndpointsByPlatformApplication where
    page rq rs
        | stop (rq ^. lebpaNextToken) = Nothing
        | otherwise = (\x -> rq & lebpaNextToken ?~ x)
            <$> (rs ^. lebparNextToken)