stratosphere-1.0.0: EDSL for AWS CloudFormation
Safe HaskellNone
LanguageHaskell2010

Stratosphere.Value

Synopsis

Documentation

data Value a where Source #

This type is a wrapper around any values in a template. A value can be a Literal, a Ref, or an intrinsic function. See: http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/intrinsic-function-reference.html

Constructors

Literal :: forall a. a -> Value a 
Ref :: forall a. Text -> Value a 
If :: forall a. Text -> Value a -> Value a -> Value a 
And :: Value Bool -> Value Bool -> Value Bool 
Equals :: forall a1. (Show a1, ToJSON a1, Eq a1, Typeable a1) => Value a1 -> Value a1 -> Value Bool 
Or :: Value Bool -> Value Bool -> Value Bool 
Not :: Value Bool -> Value Bool 
GetAtt :: forall a. Text -> Text -> Value a 
Base64 :: Value Text -> Value Text 
Join :: Text -> ValueList Text -> Value Text 
Select :: forall a. Integer -> ValueList a -> Value a 
FindInMap 

Fields

ImportValue 

Fields

  • :: forall a. Value Text
     
  • -> Value a

    The account-and-region-unique exported name of the value to import

Sub 

Fields

Instances

Instances details
ToJSON a => ToJSON (Value a) Source # 
Instance details

Defined in Stratosphere.Value

IsString a => IsString (Value a) Source # 
Instance details

Defined in Stratosphere.Value

Methods

fromString :: String -> Value a #

Show a => Show (Value a) Source # 
Instance details

Defined in Stratosphere.Value

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Eq a => Eq (Value a) Source # 
Instance details

Defined in Stratosphere.Value

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

class ToRef a b where Source #

Class used to create a Ref from another type.

Methods

toRef :: a -> Value b Source #

Instances

Instances details
ToRef Output b Source # 
Instance details

Defined in Stratosphere.Output

Methods

toRef :: Output -> Value b Source #

ToRef Parameter b Source # 
Instance details

Defined in Stratosphere.Parameter

Methods

toRef :: Parameter -> Value b Source #

ToRef Resource b Source # 
Instance details

Defined in Stratosphere.Resource

Methods

toRef :: Resource -> Value b Source #

data ValueList a Source #

ValueList is like Value, except it is used in place of lists of values in templates. For example, if you have a parameter called SubnetIds of type ListAWS::EC2::Subnet::Id then, you can use RefList SubnetIds to reference it.

Instances

Instances details
ToJSON a => ToJSON (ValueList a) Source # 
Instance details

Defined in Stratosphere.Value

IsList (ValueList a) Source # 
Instance details

Defined in Stratosphere.Value

Associated Types

type Item (ValueList a) 
Instance details

Defined in Stratosphere.Value

type Item (ValueList a) = Value a

Methods

fromList :: [Item (ValueList a)] -> ValueList a #

fromListN :: Int -> [Item (ValueList a)] -> ValueList a #

toList :: ValueList a -> [Item (ValueList a)] #

Show a => Show (ValueList a) Source # 
Instance details

Defined in Stratosphere.Value

Eq a => Eq (ValueList a) Source # 
Instance details

Defined in Stratosphere.Value

Methods

(==) :: ValueList a -> ValueList a -> Bool #

(/=) :: ValueList a -> ValueList a -> Bool #

type Item (ValueList a) Source # 
Instance details

Defined in Stratosphere.Value

type Item (ValueList a) = Value a

sub :: Text -> Value Text Source #

Simple version of Sub without a map of values.