module Network.AWS.DirectConnect.CreateInterconnect
    (
    
      CreateInterconnect
    
    , createInterconnect
    
    , ciBandwidth
    , ciInterconnectName
    , ciLocation
    
    , CreateInterconnectResponse
    
    , createInterconnectResponse
    
    , cirBandwidth
    , cirInterconnectId
    , cirInterconnectName
    , cirInterconnectState
    , cirLocation
    , cirRegion
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.JSON
import Network.AWS.DirectConnect.Types
import qualified GHC.Exts
data CreateInterconnect = CreateInterconnect
    { _ciBandwidth        :: Text
    , _ciInterconnectName :: Text
    , _ciLocation         :: Text
    } deriving (Eq, Ord, Show)
createInterconnect :: Text 
                   -> Text 
                   -> Text 
                   -> CreateInterconnect
createInterconnect p1 p2 p3 = CreateInterconnect
    { _ciInterconnectName = p1
    , _ciBandwidth        = p2
    , _ciLocation         = p3
    }
ciBandwidth :: Lens' CreateInterconnect Text
ciBandwidth = lens _ciBandwidth (\s a -> s { _ciBandwidth = a })
ciInterconnectName :: Lens' CreateInterconnect Text
ciInterconnectName =
    lens _ciInterconnectName (\s a -> s { _ciInterconnectName = a })
ciLocation :: Lens' CreateInterconnect Text
ciLocation = lens _ciLocation (\s a -> s { _ciLocation = a })
data CreateInterconnectResponse = CreateInterconnectResponse
    { _cirBandwidth         :: Maybe Text
    , _cirInterconnectId    :: Maybe Text
    , _cirInterconnectName  :: Maybe Text
    , _cirInterconnectState :: Maybe InterconnectState
    , _cirLocation          :: Maybe Text
    , _cirRegion            :: Maybe Text
    } deriving (Eq, Show)
createInterconnectResponse :: CreateInterconnectResponse
createInterconnectResponse = CreateInterconnectResponse
    { _cirInterconnectId    = Nothing
    , _cirInterconnectName  = Nothing
    , _cirInterconnectState = Nothing
    , _cirRegion            = Nothing
    , _cirLocation          = Nothing
    , _cirBandwidth         = Nothing
    }
cirBandwidth :: Lens' CreateInterconnectResponse (Maybe Text)
cirBandwidth = lens _cirBandwidth (\s a -> s { _cirBandwidth = a })
cirInterconnectId :: Lens' CreateInterconnectResponse (Maybe Text)
cirInterconnectId =
    lens _cirInterconnectId (\s a -> s { _cirInterconnectId = a })
cirInterconnectName :: Lens' CreateInterconnectResponse (Maybe Text)
cirInterconnectName =
    lens _cirInterconnectName (\s a -> s { _cirInterconnectName = a })
cirInterconnectState :: Lens' CreateInterconnectResponse (Maybe InterconnectState)
cirInterconnectState =
    lens _cirInterconnectState (\s a -> s { _cirInterconnectState = a })
cirLocation :: Lens' CreateInterconnectResponse (Maybe Text)
cirLocation = lens _cirLocation (\s a -> s { _cirLocation = a })
cirRegion :: Lens' CreateInterconnectResponse (Maybe Text)
cirRegion = lens _cirRegion (\s a -> s { _cirRegion = a })
instance ToPath CreateInterconnect where
    toPath = const "/"
instance ToQuery CreateInterconnect where
    toQuery = const mempty
instance ToHeaders CreateInterconnect
instance ToJSON CreateInterconnect where
    toJSON CreateInterconnect{..} = object
        [ "interconnectName" .= _ciInterconnectName
        , "bandwidth"        .= _ciBandwidth
        , "location"         .= _ciLocation
        ]
instance AWSRequest CreateInterconnect where
    type Sv CreateInterconnect = DirectConnect
    type Rs CreateInterconnect = CreateInterconnectResponse
    request  = post "CreateInterconnect"
    response = jsonResponse
instance FromJSON CreateInterconnectResponse where
    parseJSON = withObject "CreateInterconnectResponse" $ \o -> CreateInterconnectResponse
        <$> o .:? "bandwidth"
        <*> o .:? "interconnectId"
        <*> o .:? "interconnectName"
        <*> o .:? "interconnectState"
        <*> o .:? "location"
        <*> o .:? "region"