{-# Language TemplateHaskell #-}

{-|
Module:             Network.AWS.Machines.SpotPrices
Description:        Stream the spot price history.
Copyright:          © 2017 All rights reserved.
License:            GPL-3
Maintainer:         Evan Cofsky <evan@theunixman.com>
Stability:          experimental
Portability:        POSIX
-}

module Network.AWS.Machines.SpotPrices where

import Lawless hiding (filtered, mapping)
import Network.AWS.EC2
import Network.AWS.Machines.AWS
import Network.AWS.Machines.Types
import Network.AWS.Data.Text (toText)

import Time
import Data.Fixed
import Textual (Textual(..), Printable(..), fromText, hcat, fsep)
import Text
import Machine

-- | An 'AWSSourceT' for 'SpotPrice's.
type SpotPriceSourceT m = AWSSourceT m SpotPrice

-- | A 'Process' for transducing 'SpotPrice's to something else.
type SpotPriceProcess b = Process SpotPrice b

-- | A 'Num' instance for representing US Dollars.
newtype Dollars = Dollars {unDollars  Centi}
    deriving (Eq, Show, Ord, Enum, Num, Real)

instance Printable Dollars where
    print d = hcat ["$",  print (unDollars d)]

instance Textual Dollars where
    textual = Dollars <$> textual

-- | The hourly spot price at a specific 'Time', 'InstanceType', and
-- 'Zone'.
data PricePoint = PricePoint {
    _ppTime  Time -- ^ The time for this price
    , _ppInstanceType  InstanceType -- ^ The instance type of this price
    , _ppZone  Text -- ^ The zone of this price
    , _ppDollars  Dollars -- ^ The hourly price in USD
    } deriving (Eq, Ord, Show)
makeLenses ''PricePoint

instance Printable PricePoint where
    print (PricePoint {..}) = fsep "\t" [
        print _ppTime,
        print  toText $ _ppInstanceType,
        print _ppZone,
        print _ppDollars]

pricePoint  SpotPrice  Maybe PricePoint
pricePoint sp = PricePoint
                <$> (review _Time <$> sp ^. sTimestamp)
                <*> sp ^. sInstanceType
                <*> sp ^. sAvailabilityZone
                <*> (sp ^. sSpotPrice >>= fromText)

-- | Streams the historic spot price history for a region.
spotPriceHistory 
    [RequestMod DescribeSpotPriceHistory]
     SpotPriceSourceT m -- ^ The spot price history
spotPriceHistory ms =
    pagedSource dsphrsSpotPriceHistory ms describeSpotPriceHistory

pricePoints  SpotPriceProcess PricePoint
pricePoints = mapping pricePoint
    ~> filtered (has _Just)
    ~> mapping (\(Just m)  m)