{-# LANGUAGE TemplateHaskell #-} {-| Module: Network.AWS.Machines.Images Description: Transduces the DescribeImages results. Also provides a summary type for essential information. Copyright: © 2017 All rights reserved. License: GPL-3 Maintainer: Evan Cofsky Stability: experimental Portability: POSIX -} module Network.AWS.Machines.Images where import Network.AWS.EC2 import Network.AWS.Machines.Filters import Network.AWS.Machines.AWS import Network.AWS.Data.Text (toText) import Time import Textual hiding (toText) import Data.Time.Format import Text images ∷ [RequestMod DescribeImages] → AWSSourceT m Image images ms = awsSource desrsImages ms describeImages newtype CreationDate = CreationDate {unCreationDate ∷ Time} deriving (Eq, Ord, Show, Printable, ParseTime, FormatTime) data ImageInfo = ImageInfo { _iiImageId ∷ Text, _iiName ∷ Text, _iiCreationDate ∷ CreationDate, _iiOwnerId ∷ OwnerId, _iiVirtualizationType ∷ VirtualizationType } deriving (Eq, Show) makeLenses ''ImageInfo instance Ord ImageInfo where a `compare` b = mconcat [ (a ^. iiCreationDate) `compare` (b ^. iiCreationDate), (a ^. iiOwnerId) `compare` (b ^. iiOwnerId), (a ^. iiName) `compare` (b ^. iiName), (a ^. iiImageId) `compare` (b ^. iiImageId), (b ^. iiVirtualizationType) `compare` (a ^. iiVirtualizationType) ] instance Printable ImageInfo where print (ImageInfo{..}) = hsep [print _iiImageId, print _iiName, print _iiCreationDate, print _iiOwnerId, print $ toText _iiVirtualizationType] imageInfo ∷ Getter Image ImageInfo imageInfo = to $ ii where ii i = ImageInfo (i ^. iImageId) (maybe "" id $ i ^. iName) (parseTimeOrError True defaultTimeLocale (iso8601DateFormat (Just "%H:%M:%S%Q%Z")) $ i ^. iCreationDate ^?! _Just ^. unpacked) (OwnerId $ (fromText $ i ^. iOwnerId) ^?! _Just) (i ^. iVirtualizationType) imagesInfo ∷ AWSProcessT m Image ImageInfo imagesInfo = mapping (view imageInfo) mostRecent ∷ AWSProcessT m ImageInfo ImageInfo mostRecent = fold1 max