amazonka-guardduty-1.6.0: Amazon GuardDuty SDK.

Copyright(c) 2013-2018 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.GuardDuty

Contents

Description

Assess, monitor, manage, and remediate security issues across your AWS infrastructure, applications, and data.

Synopsis

Service Configuration

guardDuty :: Service Source #

API version 2017-11-28 of the Amazon GuardDuty SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by GuardDuty.

InternalServerErrorException

BadRequestException

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

CreateFilter

ListFindings (Paginated)

CreateIPSet

DeleteThreatIntelSet

UpdateThreatIntelSet

StopMonitoringMembers

ListThreatIntelSets (Paginated)

CreateThreatIntelSet

DeleteMembers

GetFindingsStatistics

GetIPSet

ListInvitations (Paginated)

GetThreatIntelSet

DeleteInvitations

GetMasterAccount

CreateDetector

DeclineInvitations

UpdateFilter

DeleteFilter

DisassociateMembers

DisassociateFromMasterAccount

AcceptInvitation

ListFilters (Paginated)

ListMembers (Paginated)

GetDetector

CreateSampleFindings

ArchiveFindings

CreateMembers

UnarchiveFindings

GetInvitationsCount

StartMonitoringMembers

InviteMembers

DeleteIPSet

UpdateIPSet

ListIPSets (Paginated)

GetMembers

GetFindings

ListDetectors (Paginated)

UpdateDetector

DeleteDetector

UpdateFindingsFeedback

GetFilter

Types

DetectorStatus

data DetectorStatus Source #

The status of detector.

Constructors

Disabled 
Enabled 

Instances

Bounded DetectorStatus Source # 
Enum DetectorStatus Source # 
Eq DetectorStatus Source # 
Data DetectorStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DetectorStatus -> c DetectorStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DetectorStatus #

toConstr :: DetectorStatus -> Constr #

dataTypeOf :: DetectorStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DetectorStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DetectorStatus) #

gmapT :: (forall b. Data b => b -> b) -> DetectorStatus -> DetectorStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DetectorStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DetectorStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> DetectorStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DetectorStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DetectorStatus -> m DetectorStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DetectorStatus -> m DetectorStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DetectorStatus -> m DetectorStatus #

Ord DetectorStatus Source # 
Read DetectorStatus Source # 
Show DetectorStatus Source # 
Generic DetectorStatus Source # 

Associated Types

type Rep DetectorStatus :: * -> * #

Hashable DetectorStatus Source # 
FromJSON DetectorStatus Source # 
NFData DetectorStatus Source # 

Methods

rnf :: DetectorStatus -> () #

ToHeader DetectorStatus Source # 
ToQuery DetectorStatus Source # 
ToByteString DetectorStatus Source # 
FromText DetectorStatus Source # 
ToText DetectorStatus Source # 
type Rep DetectorStatus Source # 
type Rep DetectorStatus = D1 * (MetaData "DetectorStatus" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * (C1 * (MetaCons "Disabled" PrefixI False) (U1 *)) (C1 * (MetaCons "Enabled" PrefixI False) (U1 *)))

Feedback

data Feedback Source #

Finding Feedback Value

Constructors

NotUseful 
Useful 

Instances

Bounded Feedback Source # 
Enum Feedback Source # 
Eq Feedback Source # 
Data Feedback Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Feedback -> c Feedback #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Feedback #

toConstr :: Feedback -> Constr #

dataTypeOf :: Feedback -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Feedback) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Feedback) #

gmapT :: (forall b. Data b => b -> b) -> Feedback -> Feedback #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Feedback -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Feedback -> r #

gmapQ :: (forall d. Data d => d -> u) -> Feedback -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Feedback -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Feedback -> m Feedback #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Feedback -> m Feedback #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Feedback -> m Feedback #

Ord Feedback Source # 
Read Feedback Source # 
Show Feedback Source # 
Generic Feedback Source # 

Associated Types

type Rep Feedback :: * -> * #

Methods

from :: Feedback -> Rep Feedback x #

to :: Rep Feedback x -> Feedback #

Hashable Feedback Source # 

Methods

hashWithSalt :: Int -> Feedback -> Int #

hash :: Feedback -> Int #

ToJSON Feedback Source # 
NFData Feedback Source # 

Methods

rnf :: Feedback -> () #

ToHeader Feedback Source # 

Methods

toHeader :: HeaderName -> Feedback -> [Header] #

ToQuery Feedback Source # 
ToByteString Feedback Source # 

Methods

toBS :: Feedback -> ByteString #

FromText Feedback Source # 
ToText Feedback Source # 

Methods

toText :: Feedback -> Text #

type Rep Feedback Source # 
type Rep Feedback = D1 * (MetaData "Feedback" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * (C1 * (MetaCons "NotUseful" PrefixI False) (U1 *)) (C1 * (MetaCons "Useful" PrefixI False) (U1 *)))

FilterAction

data FilterAction Source #

The action associated with a filter.

Constructors

Archive 
Noop 

Instances

Bounded FilterAction Source # 
Enum FilterAction Source # 
Eq FilterAction Source # 
Data FilterAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilterAction -> c FilterAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilterAction #

toConstr :: FilterAction -> Constr #

dataTypeOf :: FilterAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilterAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilterAction) #

gmapT :: (forall b. Data b => b -> b) -> FilterAction -> FilterAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilterAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilterAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilterAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilterAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilterAction -> m FilterAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterAction -> m FilterAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterAction -> m FilterAction #

Ord FilterAction Source # 
Read FilterAction Source # 
Show FilterAction Source # 
Generic FilterAction Source # 

Associated Types

type Rep FilterAction :: * -> * #

Hashable FilterAction Source # 
ToJSON FilterAction Source # 
FromJSON FilterAction Source # 
NFData FilterAction Source # 

Methods

rnf :: FilterAction -> () #

ToHeader FilterAction Source # 
ToQuery FilterAction Source # 
ToByteString FilterAction Source # 
FromText FilterAction Source # 
ToText FilterAction Source # 

Methods

toText :: FilterAction -> Text #

type Rep FilterAction Source # 
type Rep FilterAction = D1 * (MetaData "FilterAction" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * (C1 * (MetaCons "Archive" PrefixI False) (U1 *)) (C1 * (MetaCons "Noop" PrefixI False) (U1 *)))

FindingStatisticType

data FindingStatisticType Source #

The types of finding statistics.

Constructors

CountBySeverity 

Instances

Bounded FindingStatisticType Source # 
Enum FindingStatisticType Source # 
Eq FindingStatisticType Source # 
Data FindingStatisticType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FindingStatisticType -> c FindingStatisticType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FindingStatisticType #

toConstr :: FindingStatisticType -> Constr #

dataTypeOf :: FindingStatisticType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FindingStatisticType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FindingStatisticType) #

gmapT :: (forall b. Data b => b -> b) -> FindingStatisticType -> FindingStatisticType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FindingStatisticType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FindingStatisticType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FindingStatisticType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FindingStatisticType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FindingStatisticType -> m FindingStatisticType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FindingStatisticType -> m FindingStatisticType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FindingStatisticType -> m FindingStatisticType #

Ord FindingStatisticType Source # 
Read FindingStatisticType Source # 
Show FindingStatisticType Source # 
Generic FindingStatisticType Source # 
Hashable FindingStatisticType Source # 
ToJSON FindingStatisticType Source # 
NFData FindingStatisticType Source # 

Methods

rnf :: FindingStatisticType -> () #

ToHeader FindingStatisticType Source # 
ToQuery FindingStatisticType Source # 
ToByteString FindingStatisticType Source # 
FromText FindingStatisticType Source # 
ToText FindingStatisticType Source # 
type Rep FindingStatisticType Source # 
type Rep FindingStatisticType = D1 * (MetaData "FindingStatisticType" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "CountBySeverity" PrefixI False) (U1 *))

IPSetFormat

data IPSetFormat Source #

The format of the ipSet.

Instances

Bounded IPSetFormat Source # 
Enum IPSetFormat Source # 
Eq IPSetFormat Source # 
Data IPSetFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPSetFormat -> c IPSetFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPSetFormat #

toConstr :: IPSetFormat -> Constr #

dataTypeOf :: IPSetFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IPSetFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPSetFormat) #

gmapT :: (forall b. Data b => b -> b) -> IPSetFormat -> IPSetFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPSetFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPSetFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPSetFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPSetFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPSetFormat -> m IPSetFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPSetFormat -> m IPSetFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPSetFormat -> m IPSetFormat #

Ord IPSetFormat Source # 
Read IPSetFormat Source # 
Show IPSetFormat Source # 
Generic IPSetFormat Source # 

Associated Types

type Rep IPSetFormat :: * -> * #

Hashable IPSetFormat Source # 
ToJSON IPSetFormat Source # 
FromJSON IPSetFormat Source # 
NFData IPSetFormat Source # 

Methods

rnf :: IPSetFormat -> () #

ToHeader IPSetFormat Source # 
ToQuery IPSetFormat Source # 
ToByteString IPSetFormat Source # 
FromText IPSetFormat Source # 
ToText IPSetFormat Source # 

Methods

toText :: IPSetFormat -> Text #

type Rep IPSetFormat Source # 
type Rep IPSetFormat = D1 * (MetaData "IPSetFormat" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AlienVault" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FireEye" PrefixI False) (U1 *)) (C1 * (MetaCons "OtxCSV" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ProofPoint" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Stix" PrefixI False) (U1 *)) (C1 * (MetaCons "Txt" PrefixI False) (U1 *)))))

IPSetStatus

data IPSetStatus Source #

The status of ipSet file uploaded.

Instances

Bounded IPSetStatus Source # 
Enum IPSetStatus Source # 
Eq IPSetStatus Source # 
Data IPSetStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPSetStatus -> c IPSetStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPSetStatus #

toConstr :: IPSetStatus -> Constr #

dataTypeOf :: IPSetStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IPSetStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPSetStatus) #

gmapT :: (forall b. Data b => b -> b) -> IPSetStatus -> IPSetStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPSetStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPSetStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPSetStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPSetStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPSetStatus -> m IPSetStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPSetStatus -> m IPSetStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPSetStatus -> m IPSetStatus #

Ord IPSetStatus Source # 
Read IPSetStatus Source # 
Show IPSetStatus Source # 
Generic IPSetStatus Source # 

Associated Types

type Rep IPSetStatus :: * -> * #

Hashable IPSetStatus Source # 
FromJSON IPSetStatus Source # 
NFData IPSetStatus Source # 

Methods

rnf :: IPSetStatus -> () #

ToHeader IPSetStatus Source # 
ToQuery IPSetStatus Source # 
ToByteString IPSetStatus Source # 
FromText IPSetStatus Source # 
ToText IPSetStatus Source # 

Methods

toText :: IPSetStatus -> Text #

type Rep IPSetStatus Source # 
type Rep IPSetStatus = D1 * (MetaData "IPSetStatus" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ISSActivating" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ISSActive" PrefixI False) (U1 *)) (C1 * (MetaCons "ISSDeactivating" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "ISSDeletePending" PrefixI False) (U1 *)) (C1 * (MetaCons "ISSDeleted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ISSError'" PrefixI False) (U1 *)) (C1 * (MetaCons "ISSInactive" PrefixI False) (U1 *)))))

OrderBy

data OrderBy Source #

Constructors

Asc 
Desc 

Instances

Bounded OrderBy Source # 
Enum OrderBy Source # 
Eq OrderBy Source # 

Methods

(==) :: OrderBy -> OrderBy -> Bool #

(/=) :: OrderBy -> OrderBy -> Bool #

Data OrderBy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderBy -> c OrderBy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderBy #

toConstr :: OrderBy -> Constr #

dataTypeOf :: OrderBy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderBy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderBy) #

gmapT :: (forall b. Data b => b -> b) -> OrderBy -> OrderBy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderBy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderBy -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderBy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderBy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderBy -> m OrderBy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderBy -> m OrderBy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderBy -> m OrderBy #

Ord OrderBy Source # 
Read OrderBy Source # 
Show OrderBy Source # 
Generic OrderBy Source # 

Associated Types

type Rep OrderBy :: * -> * #

Methods

from :: OrderBy -> Rep OrderBy x #

to :: Rep OrderBy x -> OrderBy #

Hashable OrderBy Source # 

Methods

hashWithSalt :: Int -> OrderBy -> Int #

hash :: OrderBy -> Int #

ToJSON OrderBy Source # 
NFData OrderBy Source # 

Methods

rnf :: OrderBy -> () #

ToHeader OrderBy Source # 

Methods

toHeader :: HeaderName -> OrderBy -> [Header] #

ToQuery OrderBy Source # 
ToByteString OrderBy Source # 

Methods

toBS :: OrderBy -> ByteString #

FromText OrderBy Source # 
ToText OrderBy Source # 

Methods

toText :: OrderBy -> Text #

type Rep OrderBy Source # 
type Rep OrderBy = D1 * (MetaData "OrderBy" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * (C1 * (MetaCons "Asc" PrefixI False) (U1 *)) (C1 * (MetaCons "Desc" PrefixI False) (U1 *)))

ThreatIntelSetFormat

data ThreatIntelSetFormat Source #

The format of the threatIntelSet.

Instances

Bounded ThreatIntelSetFormat Source # 
Enum ThreatIntelSetFormat Source # 
Eq ThreatIntelSetFormat Source # 
Data ThreatIntelSetFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThreatIntelSetFormat -> c ThreatIntelSetFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThreatIntelSetFormat #

toConstr :: ThreatIntelSetFormat -> Constr #

dataTypeOf :: ThreatIntelSetFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ThreatIntelSetFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThreatIntelSetFormat) #

gmapT :: (forall b. Data b => b -> b) -> ThreatIntelSetFormat -> ThreatIntelSetFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThreatIntelSetFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThreatIntelSetFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThreatIntelSetFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThreatIntelSetFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThreatIntelSetFormat -> m ThreatIntelSetFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThreatIntelSetFormat -> m ThreatIntelSetFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThreatIntelSetFormat -> m ThreatIntelSetFormat #

Ord ThreatIntelSetFormat Source # 
Read ThreatIntelSetFormat Source # 
Show ThreatIntelSetFormat Source # 
Generic ThreatIntelSetFormat Source # 
Hashable ThreatIntelSetFormat Source # 
ToJSON ThreatIntelSetFormat Source # 
FromJSON ThreatIntelSetFormat Source # 
NFData ThreatIntelSetFormat Source # 

Methods

rnf :: ThreatIntelSetFormat -> () #

ToHeader ThreatIntelSetFormat Source # 
ToQuery ThreatIntelSetFormat Source # 
ToByteString ThreatIntelSetFormat Source # 
FromText ThreatIntelSetFormat Source # 
ToText ThreatIntelSetFormat Source # 
type Rep ThreatIntelSetFormat Source # 
type Rep ThreatIntelSetFormat = D1 * (MetaData "ThreatIntelSetFormat" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TISFAlienVault" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TISFFireEye" PrefixI False) (U1 *)) (C1 * (MetaCons "TISFOtxCSV" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "TISFProofPoint" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TISFStix" PrefixI False) (U1 *)) (C1 * (MetaCons "TISFTxt" PrefixI False) (U1 *)))))

ThreatIntelSetStatus

data ThreatIntelSetStatus Source #

The status of threatIntelSet file uploaded.

Instances

Bounded ThreatIntelSetStatus Source # 
Enum ThreatIntelSetStatus Source # 
Eq ThreatIntelSetStatus Source # 
Data ThreatIntelSetStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThreatIntelSetStatus -> c ThreatIntelSetStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThreatIntelSetStatus #

toConstr :: ThreatIntelSetStatus -> Constr #

dataTypeOf :: ThreatIntelSetStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ThreatIntelSetStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThreatIntelSetStatus) #

gmapT :: (forall b. Data b => b -> b) -> ThreatIntelSetStatus -> ThreatIntelSetStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThreatIntelSetStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThreatIntelSetStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThreatIntelSetStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThreatIntelSetStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThreatIntelSetStatus -> m ThreatIntelSetStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThreatIntelSetStatus -> m ThreatIntelSetStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThreatIntelSetStatus -> m ThreatIntelSetStatus #

Ord ThreatIntelSetStatus Source # 
Read ThreatIntelSetStatus Source # 
Show ThreatIntelSetStatus Source # 
Generic ThreatIntelSetStatus Source # 
Hashable ThreatIntelSetStatus Source # 
FromJSON ThreatIntelSetStatus Source # 
NFData ThreatIntelSetStatus Source # 

Methods

rnf :: ThreatIntelSetStatus -> () #

ToHeader ThreatIntelSetStatus Source # 
ToQuery ThreatIntelSetStatus Source # 
ToByteString ThreatIntelSetStatus Source # 
FromText ThreatIntelSetStatus Source # 
ToText ThreatIntelSetStatus Source # 
type Rep ThreatIntelSetStatus Source # 
type Rep ThreatIntelSetStatus = D1 * (MetaData "ThreatIntelSetStatus" "Network.AWS.GuardDuty.Types.Sum" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Activating" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Active" PrefixI False) (U1 *)) (C1 * (MetaCons "Deactivating" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "DeletePending" PrefixI False) (U1 *)) (C1 * (MetaCons "Deleted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Error'" PrefixI False) (U1 *)) (C1 * (MetaCons "Inactive" PrefixI False) (U1 *)))))

AWSAPICallAction

data AWSAPICallAction Source #

Information about the AWS_API_CALL action described in this finding.

See: awsAPICallAction smart constructor.

Instances

Eq AWSAPICallAction Source # 
Data AWSAPICallAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AWSAPICallAction -> c AWSAPICallAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AWSAPICallAction #

toConstr :: AWSAPICallAction -> Constr #

dataTypeOf :: AWSAPICallAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AWSAPICallAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AWSAPICallAction) #

gmapT :: (forall b. Data b => b -> b) -> AWSAPICallAction -> AWSAPICallAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AWSAPICallAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AWSAPICallAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> AWSAPICallAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AWSAPICallAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AWSAPICallAction -> m AWSAPICallAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AWSAPICallAction -> m AWSAPICallAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AWSAPICallAction -> m AWSAPICallAction #

Read AWSAPICallAction Source # 
Show AWSAPICallAction Source # 
Generic AWSAPICallAction Source # 
Hashable AWSAPICallAction Source # 
FromJSON AWSAPICallAction Source # 
NFData AWSAPICallAction Source # 

Methods

rnf :: AWSAPICallAction -> () #

type Rep AWSAPICallAction Source # 
type Rep AWSAPICallAction = D1 * (MetaData "AWSAPICallAction" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "AWSAPICallAction'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_aacaRemoteIPDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RemoteIPDetails))) (S1 * (MetaSel (Just Symbol "_aacaCallerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aacaDomainDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DomainDetails))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aacaServiceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_aacaAPI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

awsAPICallAction :: AWSAPICallAction Source #

Creates a value of AWSAPICallAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aacaRemoteIPDetails :: Lens' AWSAPICallAction (Maybe RemoteIPDetails) Source #

Remote IP information of the connection.

aacaDomainDetails :: Lens' AWSAPICallAction (Maybe DomainDetails) Source #

Domain information for the AWS API call.

aacaServiceName :: Lens' AWSAPICallAction (Maybe Text) Source #

AWS service name whose API was invoked.

AccessKeyDetails

data AccessKeyDetails Source #

The IAM access key details (IAM user information) of a user that engaged in the activity that prompted GuardDuty to generate a finding.

See: accessKeyDetails smart constructor.

Instances

Eq AccessKeyDetails Source # 
Data AccessKeyDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccessKeyDetails -> c AccessKeyDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccessKeyDetails #

toConstr :: AccessKeyDetails -> Constr #

dataTypeOf :: AccessKeyDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccessKeyDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccessKeyDetails) #

gmapT :: (forall b. Data b => b -> b) -> AccessKeyDetails -> AccessKeyDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccessKeyDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccessKeyDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccessKeyDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccessKeyDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccessKeyDetails -> m AccessKeyDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccessKeyDetails -> m AccessKeyDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccessKeyDetails -> m AccessKeyDetails #

Read AccessKeyDetails Source # 
Show AccessKeyDetails Source # 
Generic AccessKeyDetails Source # 
Hashable AccessKeyDetails Source # 
FromJSON AccessKeyDetails Source # 
NFData AccessKeyDetails Source # 

Methods

rnf :: AccessKeyDetails -> () #

type Rep AccessKeyDetails Source # 
type Rep AccessKeyDetails = D1 * (MetaData "AccessKeyDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "AccessKeyDetails'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_akdPrincipalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_akdUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_akdAccessKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_akdUserType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

accessKeyDetails :: AccessKeyDetails Source #

Creates a value of AccessKeyDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

akdPrincipalId :: Lens' AccessKeyDetails (Maybe Text) Source #

The principal ID of the user.

akdUserName :: Lens' AccessKeyDetails (Maybe Text) Source #

The name of the user.

akdAccessKeyId :: Lens' AccessKeyDetails (Maybe Text) Source #

Access key ID of the user.

akdUserType :: Lens' AccessKeyDetails (Maybe Text) Source #

The type of the user.

AccountDetail

data AccountDetail Source #

An object containing the member's accountId and email address.

See: accountDetail smart constructor.

Instances

Eq AccountDetail Source # 
Data AccountDetail Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountDetail -> c AccountDetail #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountDetail #

toConstr :: AccountDetail -> Constr #

dataTypeOf :: AccountDetail -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountDetail) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountDetail) #

gmapT :: (forall b. Data b => b -> b) -> AccountDetail -> AccountDetail #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountDetail -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountDetail -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountDetail -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountDetail -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountDetail -> m AccountDetail #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountDetail -> m AccountDetail #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountDetail -> m AccountDetail #

Read AccountDetail Source # 
Show AccountDetail Source # 
Generic AccountDetail Source # 

Associated Types

type Rep AccountDetail :: * -> * #

Hashable AccountDetail Source # 
ToJSON AccountDetail Source # 
NFData AccountDetail Source # 

Methods

rnf :: AccountDetail -> () #

type Rep AccountDetail Source # 
type Rep AccountDetail = D1 * (MetaData "AccountDetail" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "AccountDetail'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_adEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_adAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

accountDetail Source #

Creates a value of AccountDetail with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

adEmail :: Lens' AccountDetail Text Source #

Member account's email address.

Action

data Action Source #

Information about the activity described in a finding.

See: action smart constructor.

Instances

Eq Action Source # 

Methods

(==) :: Action -> Action -> Bool #

(/=) :: Action -> Action -> Bool #

Data Action Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Action -> c Action #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Action #

toConstr :: Action -> Constr #

dataTypeOf :: Action -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Action) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Action) #

gmapT :: (forall b. Data b => b -> b) -> Action -> Action #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Action -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Action -> r #

gmapQ :: (forall d. Data d => d -> u) -> Action -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Action -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Action -> m Action #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Action -> m Action #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Action -> m Action #

Read Action Source # 
Show Action Source # 
Generic Action Source # 

Associated Types

type Rep Action :: * -> * #

Methods

from :: Action -> Rep Action x #

to :: Rep Action x -> Action #

Hashable Action Source # 

Methods

hashWithSalt :: Int -> Action -> Int #

hash :: Action -> Int #

FromJSON Action Source # 
NFData Action Source # 

Methods

rnf :: Action -> () #

type Rep Action Source # 
type Rep Action = D1 * (MetaData "Action" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Action'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_aNetworkConnectionAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe NetworkConnectionAction))) (S1 * (MetaSel (Just Symbol "_aPortProbeAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PortProbeAction)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aActionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_aDNSRequestAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DNSRequestAction))) (S1 * (MetaSel (Just Symbol "_aAWSAPICallAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AWSAPICallAction)))))))

action :: Action Source #

Creates a value of Action with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aNetworkConnectionAction :: Lens' Action (Maybe NetworkConnectionAction) Source #

Information about the NETWORK_CONNECTION action described in this finding.

aPortProbeAction :: Lens' Action (Maybe PortProbeAction) Source #

Information about the PORT_PROBE action described in this finding.

aActionType :: Lens' Action (Maybe Text) Source #

GuardDuty Finding activity type.

aDNSRequestAction :: Lens' Action (Maybe DNSRequestAction) Source #

Information about the DNS_REQUEST action described in this finding.

aAWSAPICallAction :: Lens' Action (Maybe AWSAPICallAction) Source #

Information about the AWS_API_CALL action described in this finding.

City

data City Source #

City information of the remote IP address.

See: city smart constructor.

Instances

Eq City Source # 

Methods

(==) :: City -> City -> Bool #

(/=) :: City -> City -> Bool #

Data City Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> City -> c City #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c City #

toConstr :: City -> Constr #

dataTypeOf :: City -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c City) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c City) #

gmapT :: (forall b. Data b => b -> b) -> City -> City #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> City -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> City -> r #

gmapQ :: (forall d. Data d => d -> u) -> City -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> City -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> City -> m City #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> City -> m City #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> City -> m City #

Read City Source # 
Show City Source # 

Methods

showsPrec :: Int -> City -> ShowS #

show :: City -> String #

showList :: [City] -> ShowS #

Generic City Source # 

Associated Types

type Rep City :: * -> * #

Methods

from :: City -> Rep City x #

to :: Rep City x -> City #

Hashable City Source # 

Methods

hashWithSalt :: Int -> City -> Int #

hash :: City -> Int #

FromJSON City Source # 
NFData City Source # 

Methods

rnf :: City -> () #

type Rep City Source # 
type Rep City = D1 * (MetaData "City" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" True) (C1 * (MetaCons "City'" PrefixI True) (S1 * (MetaSel (Just Symbol "_cCityName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

city :: City Source #

Creates a value of City with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cCityName - City name of the remote IP address.

cCityName :: Lens' City (Maybe Text) Source #

City name of the remote IP address.

Condition

data Condition Source #

Finding attribute (for example, accountId) for which conditions and values must be specified when querying findings.

See: condition smart constructor.

Instances

Eq Condition Source # 
Data Condition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Condition -> c Condition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Condition #

toConstr :: Condition -> Constr #

dataTypeOf :: Condition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Condition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Condition) #

gmapT :: (forall b. Data b => b -> b) -> Condition -> Condition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Condition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

Read Condition Source # 
Show Condition Source # 
Generic Condition Source # 

Associated Types

type Rep Condition :: * -> * #

Hashable Condition Source # 
ToJSON Condition Source # 
FromJSON Condition Source # 
NFData Condition Source # 

Methods

rnf :: Condition -> () #

type Rep Condition Source # 

condition :: Condition Source #

Creates a value of Condition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cEQ - Represents the equal condition to be applied to a single field when querying for findings.
  • cLte - Represents the less than equal condition to be applied to a single field when querying for findings.
  • cGT - Represents the greater than condition to be applied to a single field when querying for findings.
  • cNeq - Represents the not equal condition to be applied to a single field when querying for findings.
  • cLT - Represents the less than condition to be applied to a single field when querying for findings.
  • cGte - Represents the greater than equal condition to be applied to a single field when querying for findings.

cEQ :: Lens' Condition [Text] Source #

Represents the equal condition to be applied to a single field when querying for findings.

cLte :: Lens' Condition (Maybe Int) Source #

Represents the less than equal condition to be applied to a single field when querying for findings.

cGT :: Lens' Condition (Maybe Int) Source #

Represents the greater than condition to be applied to a single field when querying for findings.

cNeq :: Lens' Condition [Text] Source #

Represents the not equal condition to be applied to a single field when querying for findings.

cLT :: Lens' Condition (Maybe Int) Source #

Represents the less than condition to be applied to a single field when querying for findings.

cGte :: Lens' Condition (Maybe Int) Source #

Represents the greater than equal condition to be applied to a single field when querying for findings.

Country

data Country Source #

Country information of the remote IP address.

See: country smart constructor.

Instances

Eq Country Source # 

Methods

(==) :: Country -> Country -> Bool #

(/=) :: Country -> Country -> Bool #

Data Country Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Country -> c Country #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Country #

toConstr :: Country -> Constr #

dataTypeOf :: Country -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Country) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Country) #

gmapT :: (forall b. Data b => b -> b) -> Country -> Country #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r #

gmapQ :: (forall d. Data d => d -> u) -> Country -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Country -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Country -> m Country #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country #

Read Country Source # 
Show Country Source # 
Generic Country Source # 

Associated Types

type Rep Country :: * -> * #

Methods

from :: Country -> Rep Country x #

to :: Rep Country x -> Country #

Hashable Country Source # 

Methods

hashWithSalt :: Int -> Country -> Int #

hash :: Country -> Int #

FromJSON Country Source # 
NFData Country Source # 

Methods

rnf :: Country -> () #

type Rep Country Source # 
type Rep Country = D1 * (MetaData "Country" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Country'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cCountryName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cCountryCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

country :: Country Source #

Creates a value of Country with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cCountryName :: Lens' Country (Maybe Text) Source #

Country name of the remote IP address.

cCountryCode :: Lens' Country (Maybe Text) Source #

Country code of the remote IP address.

DNSRequestAction

data DNSRequestAction Source #

Information about the DNS_REQUEST action described in this finding.

See: dnsRequestAction smart constructor.

Instances

Eq DNSRequestAction Source # 
Data DNSRequestAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DNSRequestAction -> c DNSRequestAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DNSRequestAction #

toConstr :: DNSRequestAction -> Constr #

dataTypeOf :: DNSRequestAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DNSRequestAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DNSRequestAction) #

gmapT :: (forall b. Data b => b -> b) -> DNSRequestAction -> DNSRequestAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DNSRequestAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DNSRequestAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> DNSRequestAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DNSRequestAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DNSRequestAction -> m DNSRequestAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DNSRequestAction -> m DNSRequestAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DNSRequestAction -> m DNSRequestAction #

Read DNSRequestAction Source # 
Show DNSRequestAction Source # 
Generic DNSRequestAction Source # 
Hashable DNSRequestAction Source # 
FromJSON DNSRequestAction Source # 
NFData DNSRequestAction Source # 

Methods

rnf :: DNSRequestAction -> () #

type Rep DNSRequestAction Source # 
type Rep DNSRequestAction = D1 * (MetaData "DNSRequestAction" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" True) (C1 * (MetaCons "DNSRequestAction'" PrefixI True) (S1 * (MetaSel (Just Symbol "_draDomain") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

dnsRequestAction :: DNSRequestAction Source #

Creates a value of DNSRequestAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • draDomain - Domain information for the DNS request.

draDomain :: Lens' DNSRequestAction (Maybe Text) Source #

Domain information for the DNS request.

DomainDetails

data DomainDetails Source #

Domain information for the AWS API call.

See: domainDetails smart constructor.

Instances

Eq DomainDetails Source # 
Data DomainDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DomainDetails -> c DomainDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DomainDetails #

toConstr :: DomainDetails -> Constr #

dataTypeOf :: DomainDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DomainDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DomainDetails) #

gmapT :: (forall b. Data b => b -> b) -> DomainDetails -> DomainDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DomainDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DomainDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> DomainDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DomainDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DomainDetails -> m DomainDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DomainDetails -> m DomainDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DomainDetails -> m DomainDetails #

Read DomainDetails Source # 
Show DomainDetails Source # 
Generic DomainDetails Source # 

Associated Types

type Rep DomainDetails :: * -> * #

Hashable DomainDetails Source # 
FromJSON DomainDetails Source # 
NFData DomainDetails Source # 

Methods

rnf :: DomainDetails -> () #

type Rep DomainDetails Source # 
type Rep DomainDetails = D1 * (MetaData "DomainDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "DomainDetails'" PrefixI False) (U1 *))

domainDetails :: DomainDetails Source #

Creates a value of DomainDetails with the minimum fields required to make a request.

Finding

data Finding Source #

Representation of a abnormal or suspicious activity.

See: finding smart constructor.

Instances

Eq Finding Source # 

Methods

(==) :: Finding -> Finding -> Bool #

(/=) :: Finding -> Finding -> Bool #

Data Finding Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Finding -> c Finding #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Finding #

toConstr :: Finding -> Constr #

dataTypeOf :: Finding -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Finding) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Finding) #

gmapT :: (forall b. Data b => b -> b) -> Finding -> Finding #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Finding -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Finding -> r #

gmapQ :: (forall d. Data d => d -> u) -> Finding -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Finding -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Finding -> m Finding #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Finding -> m Finding #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Finding -> m Finding #

Read Finding Source # 
Show Finding Source # 
Generic Finding Source # 

Associated Types

type Rep Finding :: * -> * #

Methods

from :: Finding -> Rep Finding x #

to :: Rep Finding x -> Finding #

Hashable Finding Source # 

Methods

hashWithSalt :: Int -> Finding -> Int #

hash :: Finding -> Int #

FromJSON Finding Source # 
NFData Finding Source # 

Methods

rnf :: Finding -> () #

type Rep Finding Source # 
type Rep Finding = D1 * (MetaData "Finding" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Finding'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fService") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ServiceInfo))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_fPartition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_fDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_fSchemaVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_fResource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Resource))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fSeverity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "_fUpdatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_fRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_fARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))))

finding Source #

Creates a value of Finding with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • fService - Additional information assigned to the generated finding by GuardDuty.
  • fConfidence - The confidence level of a finding.
  • fPartition - The AWS resource partition.
  • fTitle - The title of a finding.
  • fDescription - The description of a finding.
  • fAccountId - AWS account ID where the activity occurred that prompted GuardDuty to generate a finding.
  • fSchemaVersion - Findings' schema version.
  • fCreatedAt - The time stamp at which a finding was generated.
  • fResource - The AWS resource associated with the activity that prompted GuardDuty to generate a finding.
  • fSeverity - The severity of a finding.
  • fUpdatedAt - The time stamp at which a finding was last updated.
  • fType - The type of a finding described by the action.
  • fRegion - The AWS region where the activity occurred that prompted GuardDuty to generate a finding.
  • fId - The identifier that corresponds to a finding described by the action.
  • fARN - The ARN of a finding described by the action.

fService :: Lens' Finding (Maybe ServiceInfo) Source #

Additional information assigned to the generated finding by GuardDuty.

fConfidence :: Lens' Finding (Maybe Double) Source #

The confidence level of a finding.

fPartition :: Lens' Finding (Maybe Text) Source #

The AWS resource partition.

fTitle :: Lens' Finding (Maybe Text) Source #

The title of a finding.

fDescription :: Lens' Finding (Maybe Text) Source #

The description of a finding.

fAccountId :: Lens' Finding Text Source #

AWS account ID where the activity occurred that prompted GuardDuty to generate a finding.

fSchemaVersion :: Lens' Finding Text Source #

Findings' schema version.

fCreatedAt :: Lens' Finding Text Source #

The time stamp at which a finding was generated.

fResource :: Lens' Finding Resource Source #

The AWS resource associated with the activity that prompted GuardDuty to generate a finding.

fSeverity :: Lens' Finding Double Source #

The severity of a finding.

fUpdatedAt :: Lens' Finding Text Source #

The time stamp at which a finding was last updated.

fType :: Lens' Finding Text Source #

The type of a finding described by the action.

fRegion :: Lens' Finding Text Source #

The AWS region where the activity occurred that prompted GuardDuty to generate a finding.

fId :: Lens' Finding Text Source #

The identifier that corresponds to a finding described by the action.

fARN :: Lens' Finding Text Source #

The ARN of a finding described by the action.

FindingCriteria

data FindingCriteria Source #

Represents the criteria used for querying findings.

See: findingCriteria smart constructor.

Instances

Eq FindingCriteria Source # 
Data FindingCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FindingCriteria -> c FindingCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FindingCriteria #

toConstr :: FindingCriteria -> Constr #

dataTypeOf :: FindingCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FindingCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FindingCriteria) #

gmapT :: (forall b. Data b => b -> b) -> FindingCriteria -> FindingCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FindingCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FindingCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> FindingCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FindingCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FindingCriteria -> m FindingCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FindingCriteria -> m FindingCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FindingCriteria -> m FindingCriteria #

Read FindingCriteria Source # 
Show FindingCriteria Source # 
Generic FindingCriteria Source # 
Hashable FindingCriteria Source # 
ToJSON FindingCriteria Source # 
FromJSON FindingCriteria Source # 
NFData FindingCriteria Source # 

Methods

rnf :: FindingCriteria -> () #

type Rep FindingCriteria Source # 
type Rep FindingCriteria = D1 * (MetaData "FindingCriteria" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" True) (C1 * (MetaCons "FindingCriteria'" PrefixI True) (S1 * (MetaSel (Just Symbol "_fcCriterion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Map Text Condition)))))

findingCriteria :: FindingCriteria Source #

Creates a value of FindingCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • fcCriterion - Represents a map of finding properties that match specified conditions and values when querying findings.

fcCriterion :: Lens' FindingCriteria (HashMap Text Condition) Source #

Represents a map of finding properties that match specified conditions and values when querying findings.

FindingStatistics

data FindingStatistics Source #

Finding statistics object.

See: findingStatistics smart constructor.

Instances

Eq FindingStatistics Source # 
Data FindingStatistics Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FindingStatistics -> c FindingStatistics #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FindingStatistics #

toConstr :: FindingStatistics -> Constr #

dataTypeOf :: FindingStatistics -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FindingStatistics) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FindingStatistics) #

gmapT :: (forall b. Data b => b -> b) -> FindingStatistics -> FindingStatistics #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FindingStatistics -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FindingStatistics -> r #

gmapQ :: (forall d. Data d => d -> u) -> FindingStatistics -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FindingStatistics -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FindingStatistics -> m FindingStatistics #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FindingStatistics -> m FindingStatistics #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FindingStatistics -> m FindingStatistics #

Read FindingStatistics Source # 
Show FindingStatistics Source # 
Generic FindingStatistics Source # 
Hashable FindingStatistics Source # 
FromJSON FindingStatistics Source # 
NFData FindingStatistics Source # 

Methods

rnf :: FindingStatistics -> () #

type Rep FindingStatistics Source # 
type Rep FindingStatistics = D1 * (MetaData "FindingStatistics" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" True) (C1 * (MetaCons "FindingStatistics'" PrefixI True) (S1 * (MetaSel (Just Symbol "_fsCountBySeverity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Map Text Int)))))

findingStatistics :: FindingStatistics Source #

Creates a value of FindingStatistics with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • fsCountBySeverity - Represents a map of severity to count statistic for a set of findings

fsCountBySeverity :: Lens' FindingStatistics (HashMap Text Int) Source #

Represents a map of severity to count statistic for a set of findings

GeoLocation

data GeoLocation Source #

Location information of the remote IP address.

See: geoLocation smart constructor.

Instances

Eq GeoLocation Source # 
Data GeoLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoLocation -> c GeoLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoLocation #

toConstr :: GeoLocation -> Constr #

dataTypeOf :: GeoLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoLocation) #

gmapT :: (forall b. Data b => b -> b) -> GeoLocation -> GeoLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoLocation -> m GeoLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoLocation -> m GeoLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoLocation -> m GeoLocation #

Read GeoLocation Source # 
Show GeoLocation Source # 
Generic GeoLocation Source # 

Associated Types

type Rep GeoLocation :: * -> * #

Hashable GeoLocation Source # 
FromJSON GeoLocation Source # 
NFData GeoLocation Source # 

Methods

rnf :: GeoLocation -> () #

type Rep GeoLocation Source # 
type Rep GeoLocation = D1 * (MetaData "GeoLocation" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "GeoLocation'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_glLat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double))) (S1 * (MetaSel (Just Symbol "_glLon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))))

geoLocation :: GeoLocation Source #

Creates a value of GeoLocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • glLat - Latitude information of remote IP address.
  • glLon - Longitude information of remote IP address.

glLat :: Lens' GeoLocation (Maybe Double) Source #

Latitude information of remote IP address.

glLon :: Lens' GeoLocation (Maybe Double) Source #

Longitude information of remote IP address.

IAMInstanceProfile

data IAMInstanceProfile Source #

The profile information of the EC2 instance.

See: iamInstanceProfile smart constructor.

Instances

Eq IAMInstanceProfile Source # 
Data IAMInstanceProfile Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IAMInstanceProfile -> c IAMInstanceProfile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IAMInstanceProfile #

toConstr :: IAMInstanceProfile -> Constr #

dataTypeOf :: IAMInstanceProfile -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IAMInstanceProfile) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IAMInstanceProfile) #

gmapT :: (forall b. Data b => b -> b) -> IAMInstanceProfile -> IAMInstanceProfile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IAMInstanceProfile -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IAMInstanceProfile -> r #

gmapQ :: (forall d. Data d => d -> u) -> IAMInstanceProfile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IAMInstanceProfile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IAMInstanceProfile -> m IAMInstanceProfile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IAMInstanceProfile -> m IAMInstanceProfile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IAMInstanceProfile -> m IAMInstanceProfile #

Read IAMInstanceProfile Source # 
Show IAMInstanceProfile Source # 
Generic IAMInstanceProfile Source # 
Hashable IAMInstanceProfile Source # 
FromJSON IAMInstanceProfile Source # 
NFData IAMInstanceProfile Source # 

Methods

rnf :: IAMInstanceProfile -> () #

type Rep IAMInstanceProfile Source # 
type Rep IAMInstanceProfile = D1 * (MetaData "IAMInstanceProfile" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "IAMInstanceProfile'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_iapARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iapId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

iamInstanceProfile :: IAMInstanceProfile Source #

Creates a value of IAMInstanceProfile with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • iapARN - AWS EC2 instance profile ARN.
  • iapId - AWS EC2 instance profile ID.

iapARN :: Lens' IAMInstanceProfile (Maybe Text) Source #

AWS EC2 instance profile ARN.

iapId :: Lens' IAMInstanceProfile (Maybe Text) Source #

AWS EC2 instance profile ID.

InstanceDetails

data InstanceDetails Source #

The information about the EC2 instance associated with the activity that prompted GuardDuty to generate a finding.

See: instanceDetails smart constructor.

Instances

Eq InstanceDetails Source # 
Data InstanceDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstanceDetails -> c InstanceDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstanceDetails #

toConstr :: InstanceDetails -> Constr #

dataTypeOf :: InstanceDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InstanceDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstanceDetails) #

gmapT :: (forall b. Data b => b -> b) -> InstanceDetails -> InstanceDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstanceDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstanceDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstanceDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstanceDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstanceDetails -> m InstanceDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceDetails -> m InstanceDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstanceDetails -> m InstanceDetails #

Read InstanceDetails Source # 
Show InstanceDetails Source # 
Generic InstanceDetails Source # 
Hashable InstanceDetails Source # 
FromJSON InstanceDetails Source # 
NFData InstanceDetails Source # 

Methods

rnf :: InstanceDetails -> () #

type Rep InstanceDetails Source # 
type Rep InstanceDetails = D1 * (MetaData "InstanceDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "InstanceDetails'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_idInstanceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_idPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_idLaunchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_idNetworkInterfaces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [NetworkInterface]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_idInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_idAvailabilityZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_idIAMInstanceProfile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe IAMInstanceProfile))) ((:*:) * (S1 * (MetaSel (Just Symbol "_idImageId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_idProductCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ProductCode]))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_idInstanceState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_idTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Tag]))) (S1 * (MetaSel (Just Symbol "_idImageDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

instanceDetails :: InstanceDetails Source #

Creates a value of InstanceDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

idInstanceId :: Lens' InstanceDetails (Maybe Text) Source #

The ID of the EC2 instance.

idPlatform :: Lens' InstanceDetails (Maybe Text) Source #

The platform of the EC2 instance.

idLaunchTime :: Lens' InstanceDetails (Maybe Text) Source #

The launch time of the EC2 instance.

idNetworkInterfaces :: Lens' InstanceDetails [NetworkInterface] Source #

The network interface information of the EC2 instance.

idInstanceType :: Lens' InstanceDetails (Maybe Text) Source #

The type of the EC2 instance.

idAvailabilityZone :: Lens' InstanceDetails (Maybe Text) Source #

The availability zone of the EC2 instance.

idImageId :: Lens' InstanceDetails (Maybe Text) Source #

The image ID of the EC2 instance.

idProductCodes :: Lens' InstanceDetails [ProductCode] Source #

The product code of the EC2 instance.

idInstanceState :: Lens' InstanceDetails (Maybe Text) Source #

The state of the EC2 instance.

idTags :: Lens' InstanceDetails [Tag] Source #

The tags of the EC2 instance.

idImageDescription :: Lens' InstanceDetails (Maybe Text) Source #

The image description of the EC2 instance.

Invitation

data Invitation Source #

Invitation from an AWS account to become the current account's master.

See: invitation smart constructor.

Instances

Eq Invitation Source # 
Data Invitation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Invitation -> c Invitation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Invitation #

toConstr :: Invitation -> Constr #

dataTypeOf :: Invitation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Invitation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Invitation) #

gmapT :: (forall b. Data b => b -> b) -> Invitation -> Invitation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Invitation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Invitation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Invitation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Invitation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Invitation -> m Invitation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Invitation -> m Invitation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Invitation -> m Invitation #

Read Invitation Source # 
Show Invitation Source # 
Generic Invitation Source # 

Associated Types

type Rep Invitation :: * -> * #

Hashable Invitation Source # 
FromJSON Invitation Source # 
NFData Invitation Source # 

Methods

rnf :: Invitation -> () #

type Rep Invitation Source # 
type Rep Invitation = D1 * (MetaData "Invitation" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Invitation'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_iInvitedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iRelationshipStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_iInvitationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_iAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

invitation :: Invitation Source #

Creates a value of Invitation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • iInvitedAt - Timestamp at which the invitation was sent
  • iRelationshipStatus - The status of the relationship between the inviter and invitee accounts.
  • iInvitationId - This value is used to validate the inviter account to the member account.
  • iAccountId - Inviter account ID

iInvitedAt :: Lens' Invitation (Maybe Text) Source #

Timestamp at which the invitation was sent

iRelationshipStatus :: Lens' Invitation (Maybe Text) Source #

The status of the relationship between the inviter and invitee accounts.

iInvitationId :: Lens' Invitation (Maybe Text) Source #

This value is used to validate the inviter account to the member account.

iAccountId :: Lens' Invitation (Maybe Text) Source #

Inviter account ID

LocalPortDetails

data LocalPortDetails Source #

Local port information of the connection.

See: localPortDetails smart constructor.

Instances

Eq LocalPortDetails Source # 
Data LocalPortDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalPortDetails -> c LocalPortDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalPortDetails #

toConstr :: LocalPortDetails -> Constr #

dataTypeOf :: LocalPortDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocalPortDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalPortDetails) #

gmapT :: (forall b. Data b => b -> b) -> LocalPortDetails -> LocalPortDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalPortDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalPortDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalPortDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalPortDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalPortDetails -> m LocalPortDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalPortDetails -> m LocalPortDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalPortDetails -> m LocalPortDetails #

Read LocalPortDetails Source # 
Show LocalPortDetails Source # 
Generic LocalPortDetails Source # 
Hashable LocalPortDetails Source # 
FromJSON LocalPortDetails Source # 
NFData LocalPortDetails Source # 

Methods

rnf :: LocalPortDetails -> () #

type Rep LocalPortDetails Source # 
type Rep LocalPortDetails = D1 * (MetaData "LocalPortDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "LocalPortDetails'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lpdPortName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lpdPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))

localPortDetails :: LocalPortDetails Source #

Creates a value of LocalPortDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lpdPortName - Port name of the local connection.
  • lpdPort - Port number of the local connection.

lpdPortName :: Lens' LocalPortDetails (Maybe Text) Source #

Port name of the local connection.

lpdPort :: Lens' LocalPortDetails (Maybe Int) Source #

Port number of the local connection.

Master

data Master Source #

Contains details about the master account.

See: master smart constructor.

Instances

Eq Master Source # 

Methods

(==) :: Master -> Master -> Bool #

(/=) :: Master -> Master -> Bool #

Data Master Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Master -> c Master #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Master #

toConstr :: Master -> Constr #

dataTypeOf :: Master -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Master) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Master) #

gmapT :: (forall b. Data b => b -> b) -> Master -> Master #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Master -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Master -> r #

gmapQ :: (forall d. Data d => d -> u) -> Master -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Master -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Master -> m Master #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Master -> m Master #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Master -> m Master #

Read Master Source # 
Show Master Source # 
Generic Master Source # 

Associated Types

type Rep Master :: * -> * #

Methods

from :: Master -> Rep Master x #

to :: Rep Master x -> Master #

Hashable Master Source # 

Methods

hashWithSalt :: Int -> Master -> Int #

hash :: Master -> Int #

FromJSON Master Source # 
NFData Master Source # 

Methods

rnf :: Master -> () #

type Rep Master Source # 
type Rep Master = D1 * (MetaData "Master" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Master'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_masInvitedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_masRelationshipStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_masInvitationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_masAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

master :: Master Source #

Creates a value of Master with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

masInvitedAt :: Lens' Master (Maybe Text) Source #

Timestamp at which the invitation was sent

masRelationshipStatus :: Lens' Master (Maybe Text) Source #

The status of the relationship between the master and member accounts.

masInvitationId :: Lens' Master (Maybe Text) Source #

This value is used to validate the master account to the member account.

masAccountId :: Lens' Master (Maybe Text) Source #

Master account ID

Member

data Member Source #

Contains details about the member account.

See: member smart constructor.

Instances

Eq Member Source # 

Methods

(==) :: Member -> Member -> Bool #

(/=) :: Member -> Member -> Bool #

Data Member Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Member -> c Member #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Member #

toConstr :: Member -> Constr #

dataTypeOf :: Member -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Member) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Member) #

gmapT :: (forall b. Data b => b -> b) -> Member -> Member #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Member -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Member -> r #

gmapQ :: (forall d. Data d => d -> u) -> Member -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Member -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Member -> m Member #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Member -> m Member #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Member -> m Member #

Read Member Source # 
Show Member Source # 
Generic Member Source # 

Associated Types

type Rep Member :: * -> * #

Methods

from :: Member -> Rep Member x #

to :: Rep Member x -> Member #

Hashable Member Source # 

Methods

hashWithSalt :: Int -> Member -> Int #

hash :: Member -> Int #

FromJSON Member Source # 
NFData Member Source # 

Methods

rnf :: Member -> () #

type Rep Member Source # 

member Source #

Creates a value of Member with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mInvitedAt :: Lens' Member (Maybe Text) Source #

Timestamp at which the invitation was sent

mDetectorId :: Lens' Member (Maybe Text) Source #

Undocumented member.

mEmail :: Lens' Member Text Source #

Member account's email address.

mAccountId :: Lens' Member Text Source #

Undocumented member.

mMasterId :: Lens' Member Text Source #

Undocumented member.

mUpdatedAt :: Lens' Member Text Source #

Undocumented member.

mRelationshipStatus :: Lens' Member Text Source #

The status of the relationship between the member and the master.

NetworkConnectionAction

data NetworkConnectionAction Source #

Information about the NETWORK_CONNECTION action described in this finding.

See: networkConnectionAction smart constructor.

Instances

Eq NetworkConnectionAction Source # 
Data NetworkConnectionAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NetworkConnectionAction -> c NetworkConnectionAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NetworkConnectionAction #

toConstr :: NetworkConnectionAction -> Constr #

dataTypeOf :: NetworkConnectionAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NetworkConnectionAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NetworkConnectionAction) #

gmapT :: (forall b. Data b => b -> b) -> NetworkConnectionAction -> NetworkConnectionAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NetworkConnectionAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NetworkConnectionAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> NetworkConnectionAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NetworkConnectionAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NetworkConnectionAction -> m NetworkConnectionAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkConnectionAction -> m NetworkConnectionAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkConnectionAction -> m NetworkConnectionAction #

Read NetworkConnectionAction Source # 
Show NetworkConnectionAction Source # 
Generic NetworkConnectionAction Source # 
Hashable NetworkConnectionAction Source # 
FromJSON NetworkConnectionAction Source # 
NFData NetworkConnectionAction Source # 

Methods

rnf :: NetworkConnectionAction -> () #

type Rep NetworkConnectionAction Source # 
type Rep NetworkConnectionAction = D1 * (MetaData "NetworkConnectionAction" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "NetworkConnectionAction'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ncaRemoteIPDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RemoteIPDetails))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ncaProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ncaRemotePortDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RemotePortDetails))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ncaBlocked") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ncaConnectionDirection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ncaLocalPortDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LocalPortDetails)))))))

networkConnectionAction :: NetworkConnectionAction Source #

Creates a value of NetworkConnectionAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ncaRemoteIPDetails :: Lens' NetworkConnectionAction (Maybe RemoteIPDetails) Source #

Remote IP information of the connection.

ncaProtocol :: Lens' NetworkConnectionAction (Maybe Text) Source #

Network connection protocol.

ncaRemotePortDetails :: Lens' NetworkConnectionAction (Maybe RemotePortDetails) Source #

Remote port information of the connection.

ncaBlocked :: Lens' NetworkConnectionAction (Maybe Bool) Source #

Network connection blocked information.

ncaLocalPortDetails :: Lens' NetworkConnectionAction (Maybe LocalPortDetails) Source #

Local port information of the connection.

NetworkInterface

data NetworkInterface Source #

The network interface information of the EC2 instance.

See: networkInterface smart constructor.

Instances

Eq NetworkInterface Source # 
Data NetworkInterface Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NetworkInterface -> c NetworkInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NetworkInterface #

toConstr :: NetworkInterface -> Constr #

dataTypeOf :: NetworkInterface -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NetworkInterface) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NetworkInterface) #

gmapT :: (forall b. Data b => b -> b) -> NetworkInterface -> NetworkInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NetworkInterface -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NetworkInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> NetworkInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NetworkInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NetworkInterface -> m NetworkInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkInterface -> m NetworkInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NetworkInterface -> m NetworkInterface #

Read NetworkInterface Source # 
Show NetworkInterface Source # 
Generic NetworkInterface Source # 
Hashable NetworkInterface Source # 
FromJSON NetworkInterface Source # 
NFData NetworkInterface Source # 

Methods

rnf :: NetworkInterface -> () #

type Rep NetworkInterface Source # 
type Rep NetworkInterface = D1 * (MetaData "NetworkInterface" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "NetworkInterface'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_niPrivateIPAddresses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [PrivateIPAddressDetails]))) (S1 * (MetaSel (Just Symbol "_niPublicDNSName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_niSecurityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [SecurityGroup]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_niVPCId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_niNetworkInterfaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_niSubnetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_niPrivateIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_niPublicIP") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_niPrivateDNSName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_niIPv6Addresses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))))))))

networkInterface :: NetworkInterface Source #

Creates a value of NetworkInterface with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

niPrivateIPAddresses :: Lens' NetworkInterface [PrivateIPAddressDetails] Source #

Other private IP address information of the EC2 instance.

niPublicDNSName :: Lens' NetworkInterface (Maybe Text) Source #

Public DNS name of the EC2 instance.

niSecurityGroups :: Lens' NetworkInterface [SecurityGroup] Source #

Security groups associated with the EC2 instance.

niVPCId :: Lens' NetworkInterface (Maybe Text) Source #

The VPC ID of the EC2 instance.

niNetworkInterfaceId :: Lens' NetworkInterface (Maybe Text) Source #

The ID of the network interface

niSubnetId :: Lens' NetworkInterface (Maybe Text) Source #

The subnet ID of the EC2 instance.

niPrivateIPAddress :: Lens' NetworkInterface (Maybe Text) Source #

Private IP address of the EC2 instance.

niPublicIP :: Lens' NetworkInterface (Maybe Text) Source #

Public IP address of the EC2 instance.

niPrivateDNSName :: Lens' NetworkInterface (Maybe Text) Source #

Private DNS name of the EC2 instance.

niIPv6Addresses :: Lens' NetworkInterface [Text] Source #

A list of EC2 instance IPv6 address information.

Organization

data Organization Source #

ISP Organization information of the remote IP address.

See: organization smart constructor.

Instances

Eq Organization Source # 
Data Organization Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Organization -> c Organization #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Organization #

toConstr :: Organization -> Constr #

dataTypeOf :: Organization -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Organization) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Organization) #

gmapT :: (forall b. Data b => b -> b) -> Organization -> Organization #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Organization -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Organization -> r #

gmapQ :: (forall d. Data d => d -> u) -> Organization -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Organization -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Organization -> m Organization #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Organization -> m Organization #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Organization -> m Organization #

Read Organization Source # 
Show Organization Source # 
Generic Organization Source # 

Associated Types

type Rep Organization :: * -> * #

Hashable Organization Source # 
FromJSON Organization Source # 
NFData Organization Source # 

Methods

rnf :: Organization -> () #

type Rep Organization Source # 
type Rep Organization = D1 * (MetaData "Organization" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Organization'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_oOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_oASNOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_oASN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_oIsp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

organization :: Organization Source #

Creates a value of Organization with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • oOrg - Name of the internet provider.
  • oASNOrg - Organization that registered this ASN.
  • oASN - Autonomous system number of the internet provider of the remote IP address.
  • oIsp - ISP information for the internet provider.

oOrg :: Lens' Organization (Maybe Text) Source #

Name of the internet provider.

oASNOrg :: Lens' Organization (Maybe Text) Source #

Organization that registered this ASN.

oASN :: Lens' Organization (Maybe Text) Source #

Autonomous system number of the internet provider of the remote IP address.

oIsp :: Lens' Organization (Maybe Text) Source #

ISP information for the internet provider.

PortProbeAction

data PortProbeAction Source #

Information about the PORT_PROBE action described in this finding.

See: portProbeAction smart constructor.

Instances

Eq PortProbeAction Source # 
Data PortProbeAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PortProbeAction -> c PortProbeAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PortProbeAction #

toConstr :: PortProbeAction -> Constr #

dataTypeOf :: PortProbeAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PortProbeAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortProbeAction) #

gmapT :: (forall b. Data b => b -> b) -> PortProbeAction -> PortProbeAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PortProbeAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PortProbeAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> PortProbeAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PortProbeAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PortProbeAction -> m PortProbeAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PortProbeAction -> m PortProbeAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PortProbeAction -> m PortProbeAction #

Read PortProbeAction Source # 
Show PortProbeAction Source # 
Generic PortProbeAction Source # 
Hashable PortProbeAction Source # 
FromJSON PortProbeAction Source # 
NFData PortProbeAction Source # 

Methods

rnf :: PortProbeAction -> () #

type Rep PortProbeAction Source # 
type Rep PortProbeAction = D1 * (MetaData "PortProbeAction" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "PortProbeAction'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ppaPortProbeDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [PortProbeDetail]))) (S1 * (MetaSel (Just Symbol "_ppaBlocked") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))))

portProbeAction :: PortProbeAction Source #

Creates a value of PortProbeAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ppaPortProbeDetails :: Lens' PortProbeAction [PortProbeDetail] Source #

A list of port probe details objects.

ppaBlocked :: Lens' PortProbeAction (Maybe Bool) Source #

Port probe blocked information.

PortProbeDetail

data PortProbeDetail Source #

Details about the port probe finding.

See: portProbeDetail smart constructor.

Instances

Eq PortProbeDetail Source # 
Data PortProbeDetail Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PortProbeDetail -> c PortProbeDetail #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PortProbeDetail #

toConstr :: PortProbeDetail -> Constr #

dataTypeOf :: PortProbeDetail -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PortProbeDetail) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortProbeDetail) #

gmapT :: (forall b. Data b => b -> b) -> PortProbeDetail -> PortProbeDetail #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PortProbeDetail -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PortProbeDetail -> r #

gmapQ :: (forall d. Data d => d -> u) -> PortProbeDetail -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PortProbeDetail -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PortProbeDetail -> m PortProbeDetail #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PortProbeDetail -> m PortProbeDetail #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PortProbeDetail -> m PortProbeDetail #

Read PortProbeDetail Source # 
Show PortProbeDetail Source # 
Generic PortProbeDetail Source # 
Hashable PortProbeDetail Source # 
FromJSON PortProbeDetail Source # 
NFData PortProbeDetail Source # 

Methods

rnf :: PortProbeDetail -> () #

type Rep PortProbeDetail Source # 
type Rep PortProbeDetail = D1 * (MetaData "PortProbeDetail" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "PortProbeDetail'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ppdRemoteIPDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RemoteIPDetails))) (S1 * (MetaSel (Just Symbol "_ppdLocalPortDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LocalPortDetails)))))

portProbeDetail :: PortProbeDetail Source #

Creates a value of PortProbeDetail with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ppdRemoteIPDetails :: Lens' PortProbeDetail (Maybe RemoteIPDetails) Source #

Remote IP information of the connection.

ppdLocalPortDetails :: Lens' PortProbeDetail (Maybe LocalPortDetails) Source #

Local port information of the connection.

PrivateIPAddressDetails

data PrivateIPAddressDetails Source #

Other private IP address information of the EC2 instance.

See: privateIPAddressDetails smart constructor.

Instances

Eq PrivateIPAddressDetails Source # 
Data PrivateIPAddressDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrivateIPAddressDetails -> c PrivateIPAddressDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrivateIPAddressDetails #

toConstr :: PrivateIPAddressDetails -> Constr #

dataTypeOf :: PrivateIPAddressDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PrivateIPAddressDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateIPAddressDetails) #

gmapT :: (forall b. Data b => b -> b) -> PrivateIPAddressDetails -> PrivateIPAddressDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrivateIPAddressDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrivateIPAddressDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrivateIPAddressDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateIPAddressDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrivateIPAddressDetails -> m PrivateIPAddressDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateIPAddressDetails -> m PrivateIPAddressDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateIPAddressDetails -> m PrivateIPAddressDetails #

Read PrivateIPAddressDetails Source # 
Show PrivateIPAddressDetails Source # 
Generic PrivateIPAddressDetails Source # 
Hashable PrivateIPAddressDetails Source # 
FromJSON PrivateIPAddressDetails Source # 
NFData PrivateIPAddressDetails Source # 

Methods

rnf :: PrivateIPAddressDetails -> () #

type Rep PrivateIPAddressDetails Source # 
type Rep PrivateIPAddressDetails = D1 * (MetaData "PrivateIPAddressDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "PrivateIPAddressDetails'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_piadPrivateIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_piadPrivateDNSName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

privateIPAddressDetails :: PrivateIPAddressDetails Source #

Creates a value of PrivateIPAddressDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

piadPrivateIPAddress :: Lens' PrivateIPAddressDetails (Maybe Text) Source #

Private IP address of the EC2 instance.

piadPrivateDNSName :: Lens' PrivateIPAddressDetails (Maybe Text) Source #

Private DNS name of the EC2 instance.

ProductCode

data ProductCode Source #

The product code of the EC2 instance.

See: productCode smart constructor.

Instances

Eq ProductCode Source # 
Data ProductCode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProductCode -> c ProductCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProductCode #

toConstr :: ProductCode -> Constr #

dataTypeOf :: ProductCode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProductCode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProductCode) #

gmapT :: (forall b. Data b => b -> b) -> ProductCode -> ProductCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProductCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProductCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProductCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProductCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProductCode -> m ProductCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProductCode -> m ProductCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProductCode -> m ProductCode #

Read ProductCode Source # 
Show ProductCode Source # 
Generic ProductCode Source # 

Associated Types

type Rep ProductCode :: * -> * #

Hashable ProductCode Source # 
FromJSON ProductCode Source # 
NFData ProductCode Source # 

Methods

rnf :: ProductCode -> () #

type Rep ProductCode Source # 
type Rep ProductCode = D1 * (MetaData "ProductCode" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "ProductCode'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pcProductType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_pcCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

productCode :: ProductCode Source #

Creates a value of ProductCode with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pcCode :: Lens' ProductCode (Maybe Text) Source #

Product code information.

RemoteIPDetails

data RemoteIPDetails Source #

Remote IP information of the connection.

See: remoteIPDetails smart constructor.

Instances

Eq RemoteIPDetails Source # 
Data RemoteIPDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemoteIPDetails -> c RemoteIPDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemoteIPDetails #

toConstr :: RemoteIPDetails -> Constr #

dataTypeOf :: RemoteIPDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemoteIPDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemoteIPDetails) #

gmapT :: (forall b. Data b => b -> b) -> RemoteIPDetails -> RemoteIPDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemoteIPDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemoteIPDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemoteIPDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemoteIPDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemoteIPDetails -> m RemoteIPDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemoteIPDetails -> m RemoteIPDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemoteIPDetails -> m RemoteIPDetails #

Read RemoteIPDetails Source # 
Show RemoteIPDetails Source # 
Generic RemoteIPDetails Source # 
Hashable RemoteIPDetails Source # 
FromJSON RemoteIPDetails Source # 
NFData RemoteIPDetails Source # 

Methods

rnf :: RemoteIPDetails -> () #

type Rep RemoteIPDetails Source # 
type Rep RemoteIPDetails = D1 * (MetaData "RemoteIPDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "RemoteIPDetails'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ridCountry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Country))) (S1 * (MetaSel (Just Symbol "_ridCity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe City)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ridIPAddressV4") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ridGeoLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe GeoLocation))) (S1 * (MetaSel (Just Symbol "_ridOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Organization)))))))

remoteIPDetails :: RemoteIPDetails Source #

Creates a value of RemoteIPDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ridCountry :: Lens' RemoteIPDetails (Maybe Country) Source #

Country code of the remote IP address.

ridCity :: Lens' RemoteIPDetails (Maybe City) Source #

City information of the remote IP address.

ridIPAddressV4 :: Lens' RemoteIPDetails (Maybe Text) Source #

IPV4 remote address of the connection.

ridGeoLocation :: Lens' RemoteIPDetails (Maybe GeoLocation) Source #

Location information of the remote IP address.

ridOrganization :: Lens' RemoteIPDetails (Maybe Organization) Source #

ISP Organization information of the remote IP address.

RemotePortDetails

data RemotePortDetails Source #

Remote port information of the connection.

See: remotePortDetails smart constructor.

Instances

Eq RemotePortDetails Source # 
Data RemotePortDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemotePortDetails -> c RemotePortDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemotePortDetails #

toConstr :: RemotePortDetails -> Constr #

dataTypeOf :: RemotePortDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemotePortDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemotePortDetails) #

gmapT :: (forall b. Data b => b -> b) -> RemotePortDetails -> RemotePortDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemotePortDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemotePortDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemotePortDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemotePortDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemotePortDetails -> m RemotePortDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemotePortDetails -> m RemotePortDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemotePortDetails -> m RemotePortDetails #

Read RemotePortDetails Source # 
Show RemotePortDetails Source # 
Generic RemotePortDetails Source # 
Hashable RemotePortDetails Source # 
FromJSON RemotePortDetails Source # 
NFData RemotePortDetails Source # 

Methods

rnf :: RemotePortDetails -> () #

type Rep RemotePortDetails Source # 
type Rep RemotePortDetails = D1 * (MetaData "RemotePortDetails" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "RemotePortDetails'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rpdPortName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rpdPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))

remotePortDetails :: RemotePortDetails Source #

Creates a value of RemotePortDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rpdPortName - Port name of the remote connection.
  • rpdPort - Port number of the remote connection.

rpdPortName :: Lens' RemotePortDetails (Maybe Text) Source #

Port name of the remote connection.

rpdPort :: Lens' RemotePortDetails (Maybe Int) Source #

Port number of the remote connection.

Resource

data Resource Source #

The AWS resource associated with the activity that prompted GuardDuty to generate a finding.

See: resource smart constructor.

Instances

Eq Resource Source # 
Data Resource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Resource -> c Resource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Resource #

toConstr :: Resource -> Constr #

dataTypeOf :: Resource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Resource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Resource) #

gmapT :: (forall b. Data b => b -> b) -> Resource -> Resource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Resource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Resource -> r #

gmapQ :: (forall d. Data d => d -> u) -> Resource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Resource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Resource -> m Resource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Resource -> m Resource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Resource -> m Resource #

Read Resource Source # 
Show Resource Source # 
Generic Resource Source # 

Associated Types

type Rep Resource :: * -> * #

Methods

from :: Resource -> Rep Resource x #

to :: Rep Resource x -> Resource #

Hashable Resource Source # 

Methods

hashWithSalt :: Int -> Resource -> Int #

hash :: Resource -> Int #

FromJSON Resource Source # 
NFData Resource Source # 

Methods

rnf :: Resource -> () #

type Rep Resource Source # 
type Rep Resource = D1 * (MetaData "Resource" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Resource'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rInstanceDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe InstanceDetails))) (S1 * (MetaSel (Just Symbol "_rAccessKeyDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AccessKeyDetails))))))

resource :: Resource Source #

Creates a value of Resource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rResourceType :: Lens' Resource (Maybe Text) Source #

The type of the AWS resource.

SecurityGroup

data SecurityGroup Source #

Security groups associated with the EC2 instance.

See: securityGroup smart constructor.

Instances

Eq SecurityGroup Source # 
Data SecurityGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecurityGroup -> c SecurityGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecurityGroup #

toConstr :: SecurityGroup -> Constr #

dataTypeOf :: SecurityGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecurityGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecurityGroup) #

gmapT :: (forall b. Data b => b -> b) -> SecurityGroup -> SecurityGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecurityGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecurityGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecurityGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecurityGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecurityGroup -> m SecurityGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityGroup -> m SecurityGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecurityGroup -> m SecurityGroup #

Read SecurityGroup Source # 
Show SecurityGroup Source # 
Generic SecurityGroup Source # 

Associated Types

type Rep SecurityGroup :: * -> * #

Hashable SecurityGroup Source # 
FromJSON SecurityGroup Source # 
NFData SecurityGroup Source # 

Methods

rnf :: SecurityGroup -> () #

type Rep SecurityGroup Source # 
type Rep SecurityGroup = D1 * (MetaData "SecurityGroup" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "SecurityGroup'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sgGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_sgGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

securityGroup :: SecurityGroup Source #

Creates a value of SecurityGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sgGroupId :: Lens' SecurityGroup (Maybe Text) Source #

EC2 instance's security group ID.

sgGroupName :: Lens' SecurityGroup (Maybe Text) Source #

EC2 instance's security group name.

ServiceInfo

data ServiceInfo Source #

Additional information assigned to the generated finding by GuardDuty.

See: serviceInfo smart constructor.

Instances

Eq ServiceInfo Source # 
Data ServiceInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ServiceInfo -> c ServiceInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ServiceInfo #

toConstr :: ServiceInfo -> Constr #

dataTypeOf :: ServiceInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ServiceInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ServiceInfo) #

gmapT :: (forall b. Data b => b -> b) -> ServiceInfo -> ServiceInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ServiceInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ServiceInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> ServiceInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ServiceInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ServiceInfo -> m ServiceInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ServiceInfo -> m ServiceInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ServiceInfo -> m ServiceInfo #

Read ServiceInfo Source # 
Show ServiceInfo Source # 
Generic ServiceInfo Source # 

Associated Types

type Rep ServiceInfo :: * -> * #

Hashable ServiceInfo Source # 
FromJSON ServiceInfo Source # 
NFData ServiceInfo Source # 

Methods

rnf :: ServiceInfo -> () #

type Rep ServiceInfo Source # 

serviceInfo :: ServiceInfo Source #

Creates a value of ServiceInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • siCount - Total count of the occurrences of this finding type.
  • siEventFirstSeen - First seen timestamp of the activity that prompted GuardDuty to generate this finding.
  • siAction - Information about the activity described in a finding.
  • siDetectorId - Detector ID for the GuardDuty service.
  • siServiceName - The name of the AWS service (GuardDuty) that generated a finding.
  • siUserFeedback - Feedback left about the finding.
  • siEventLastSeen - Last seen timestamp of the activity that prompted GuardDuty to generate this finding.
  • siResourceRole - Resource role information for this finding.
  • siArchived - Indicates whether this finding is archived.

siCount :: Lens' ServiceInfo (Maybe Int) Source #

Total count of the occurrences of this finding type.

siEventFirstSeen :: Lens' ServiceInfo (Maybe Text) Source #

First seen timestamp of the activity that prompted GuardDuty to generate this finding.

siAction :: Lens' ServiceInfo (Maybe Action) Source #

Information about the activity described in a finding.

siDetectorId :: Lens' ServiceInfo (Maybe Text) Source #

Detector ID for the GuardDuty service.

siServiceName :: Lens' ServiceInfo (Maybe Text) Source #

The name of the AWS service (GuardDuty) that generated a finding.

siUserFeedback :: Lens' ServiceInfo (Maybe Text) Source #

Feedback left about the finding.

siEventLastSeen :: Lens' ServiceInfo (Maybe Text) Source #

Last seen timestamp of the activity that prompted GuardDuty to generate this finding.

siResourceRole :: Lens' ServiceInfo (Maybe Text) Source #

Resource role information for this finding.

siArchived :: Lens' ServiceInfo (Maybe Bool) Source #

Indicates whether this finding is archived.

SortCriteria

data SortCriteria Source #

Represents the criteria used for sorting findings.

See: sortCriteria smart constructor.

Instances

Eq SortCriteria Source # 
Data SortCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortCriteria -> c SortCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortCriteria #

toConstr :: SortCriteria -> Constr #

dataTypeOf :: SortCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SortCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortCriteria) #

gmapT :: (forall b. Data b => b -> b) -> SortCriteria -> SortCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortCriteria -> m SortCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortCriteria -> m SortCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortCriteria -> m SortCriteria #

Read SortCriteria Source # 
Show SortCriteria Source # 
Generic SortCriteria Source # 

Associated Types

type Rep SortCriteria :: * -> * #

Hashable SortCriteria Source # 
ToJSON SortCriteria Source # 
NFData SortCriteria Source # 

Methods

rnf :: SortCriteria -> () #

type Rep SortCriteria Source # 
type Rep SortCriteria = D1 * (MetaData "SortCriteria" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "SortCriteria'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scOrderBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe OrderBy))) (S1 * (MetaSel (Just Symbol "_scAttributeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

sortCriteria :: SortCriteria Source #

Creates a value of SortCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • scOrderBy - Order by which the sorted findings are to be displayed.
  • scAttributeName - Represents the finding attribute (for example, accountId) by which to sort findings.

scOrderBy :: Lens' SortCriteria (Maybe OrderBy) Source #

Order by which the sorted findings are to be displayed.

scAttributeName :: Lens' SortCriteria (Maybe Text) Source #

Represents the finding attribute (for example, accountId) by which to sort findings.

Tag

data Tag Source #

A tag of the EC2 instance.

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

FromJSON Tag Source # 
NFData Tag Source # 

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
type Rep Tag = D1 * (MetaData "Tag" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "Tag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

tag :: Tag Source #

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tagValue :: Lens' Tag (Maybe Text) Source #

EC2 instance tag value.

tagKey :: Lens' Tag (Maybe Text) Source #

EC2 instance tag key.

UnprocessedAccount

data UnprocessedAccount Source #

An object containing the unprocessed account and a result string explaining why it was unprocessed.

See: unprocessedAccount smart constructor.

Instances

Eq UnprocessedAccount Source # 
Data UnprocessedAccount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnprocessedAccount -> c UnprocessedAccount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnprocessedAccount #

toConstr :: UnprocessedAccount -> Constr #

dataTypeOf :: UnprocessedAccount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UnprocessedAccount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnprocessedAccount) #

gmapT :: (forall b. Data b => b -> b) -> UnprocessedAccount -> UnprocessedAccount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnprocessedAccount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnprocessedAccount -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnprocessedAccount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnprocessedAccount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnprocessedAccount -> m UnprocessedAccount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnprocessedAccount -> m UnprocessedAccount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnprocessedAccount -> m UnprocessedAccount #

Read UnprocessedAccount Source # 
Show UnprocessedAccount Source # 
Generic UnprocessedAccount Source # 
Hashable UnprocessedAccount Source # 
FromJSON UnprocessedAccount Source # 
NFData UnprocessedAccount Source # 

Methods

rnf :: UnprocessedAccount -> () #

type Rep UnprocessedAccount Source # 
type Rep UnprocessedAccount = D1 * (MetaData "UnprocessedAccount" "Network.AWS.GuardDuty.Types.Product" "amazonka-guardduty-1.6.0-KbE83ZKqiO93fxfUnyqRWA" False) (C1 * (MetaCons "UnprocessedAccount'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_uaAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_uaResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

unprocessedAccount Source #

Creates a value of UnprocessedAccount with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uaResult :: Lens' UnprocessedAccount Text Source #

A reason why the account hasn't been processed.