module System.CloudFoundry.Environment.Internal.Services
( withLabel
, withName
, withTag
) where
import Control.Monad (join)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, listToMaybe)
import System.CloudFoundry.Environment.Internal.Types
withTag :: String
-> Services
-> [Service]
withTag searchTag = filter (elem searchTag . tags) . allServices
withName :: String
-> Services
-> Maybe Service
withName searchName = listToMaybe . filter ((== searchName) . name) . allServices
withLabel :: String
-> Services
-> [Service]
withLabel searchLabel (Services svcs) =
fromMaybe [] $ Map.lookup searchLabel svcs
allServices :: Services -> [Service]
allServices (Services svcs) = join $ Map.elems svcs