module Network.AWS.Pager
( AWSPager (..)
, AWSTruncated (..)
, stop
, choice
) where
import Control.Applicative
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as Map
import Data.List.NonEmpty (NonEmpty)
import Data.Maybe (isJust, fromMaybe)
import Data.Text (Text)
import Network.AWS.Data.Text (ToText (..))
import Network.AWS.Lens (Getter, to)
import Network.AWS.Types
class AWSRequest a => AWSPager a where
page :: a -> Rs a -> Maybe a
class AWSTruncated a where
truncated :: a -> Bool
instance AWSTruncated Bool where
truncated = id
instance AWSTruncated [a] where
truncated = not . null
instance AWSTruncated (HashMap k v) where
truncated = not . Map.null
instance AWSTruncated (Maybe a) where
truncated = isJust
instance AWSTruncated (Maybe Bool) where
truncated = fromMaybe False
stop :: AWSTruncated a => a -> Bool
stop = not . truncated
choice :: (Alternative f, ToText a, ToText b)
=> (s -> f a)
-> (s -> f b)
-> Getter s (f Text)
choice f g = to $ \x -> (toText <$> f x) <|> (toText <$> g x)