module Network.Google.FreebaseSearch.Types.Product where
import Network.Google.FreebaseSearch.Types.Sum
import Network.Google.Prelude
data ReconcileGetWarningItem = ReconcileGetWarningItem'
{ _rgwiLocation :: !(Maybe Text)
, _rgwiReason :: !(Maybe Text)
, _rgwiMessage :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
reconcileGetWarningItem
:: ReconcileGetWarningItem
reconcileGetWarningItem =
ReconcileGetWarningItem'
{ _rgwiLocation = Nothing
, _rgwiReason = Nothing
, _rgwiMessage = Nothing
}
rgwiLocation :: Lens' ReconcileGetWarningItem (Maybe Text)
rgwiLocation
= lens _rgwiLocation (\ s a -> s{_rgwiLocation = a})
rgwiReason :: Lens' ReconcileGetWarningItem (Maybe Text)
rgwiReason
= lens _rgwiReason (\ s a -> s{_rgwiReason = a})
rgwiMessage :: Lens' ReconcileGetWarningItem (Maybe Text)
rgwiMessage
= lens _rgwiMessage (\ s a -> s{_rgwiMessage = a})
instance FromJSON ReconcileGetWarningItem where
parseJSON
= withObject "ReconcileGetWarningItem"
(\ o ->
ReconcileGetWarningItem' <$>
(o .:? "location") <*> (o .:? "reason") <*>
(o .:? "message"))
instance ToJSON ReconcileGetWarningItem where
toJSON ReconcileGetWarningItem'{..}
= object
(catMaybes
[("location" .=) <$> _rgwiLocation,
("reason" .=) <$> _rgwiReason,
("message" .=) <$> _rgwiMessage])
data ReconcileGetCosts = ReconcileGetCosts'
{ _rgcHits :: !(Maybe (Textual Int32))
, _rgcMs :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
reconcileGetCosts
:: ReconcileGetCosts
reconcileGetCosts =
ReconcileGetCosts'
{ _rgcHits = Nothing
, _rgcMs = Nothing
}
rgcHits :: Lens' ReconcileGetCosts (Maybe Int32)
rgcHits
= lens _rgcHits (\ s a -> s{_rgcHits = a}) .
mapping _Coerce
rgcMs :: Lens' ReconcileGetCosts (Maybe Int32)
rgcMs
= lens _rgcMs (\ s a -> s{_rgcMs = a}) .
mapping _Coerce
instance FromJSON ReconcileGetCosts where
parseJSON
= withObject "ReconcileGetCosts"
(\ o ->
ReconcileGetCosts' <$>
(o .:? "hits") <*> (o .:? "ms"))
instance ToJSON ReconcileGetCosts where
toJSON ReconcileGetCosts'{..}
= object
(catMaybes
[("hits" .=) <$> _rgcHits, ("ms" .=) <$> _rgcMs])
data ReconcileGet = ReconcileGet'
{ _rgCandidate :: !(Maybe [ReconcileCandidate])
, _rgCosts :: !(Maybe ReconcileGetCosts)
, _rgWarning :: !(Maybe [ReconcileGetWarningItem])
, _rgMatch :: !(Maybe ReconcileCandidate)
} deriving (Eq,Show,Data,Typeable,Generic)
reconcileGet
:: ReconcileGet
reconcileGet =
ReconcileGet'
{ _rgCandidate = Nothing
, _rgCosts = Nothing
, _rgWarning = Nothing
, _rgMatch = Nothing
}
rgCandidate :: Lens' ReconcileGet [ReconcileCandidate]
rgCandidate
= lens _rgCandidate (\ s a -> s{_rgCandidate = a}) .
_Default
. _Coerce
rgCosts :: Lens' ReconcileGet (Maybe ReconcileGetCosts)
rgCosts = lens _rgCosts (\ s a -> s{_rgCosts = a})
rgWarning :: Lens' ReconcileGet [ReconcileGetWarningItem]
rgWarning
= lens _rgWarning (\ s a -> s{_rgWarning = a}) .
_Default
. _Coerce
rgMatch :: Lens' ReconcileGet (Maybe ReconcileCandidate)
rgMatch = lens _rgMatch (\ s a -> s{_rgMatch = a})
instance FromJSON ReconcileGet where
parseJSON
= withObject "ReconcileGet"
(\ o ->
ReconcileGet' <$>
(o .:? "candidate" .!= mempty) <*> (o .:? "costs")
<*> (o .:? "warning" .!= mempty)
<*> (o .:? "match"))
instance ToJSON ReconcileGet where
toJSON ReconcileGet'{..}
= object
(catMaybes
[("candidate" .=) <$> _rgCandidate,
("costs" .=) <$> _rgCosts,
("warning" .=) <$> _rgWarning,
("match" .=) <$> _rgMatch])
data ReconcileCandidateNotable = ReconcileCandidateNotable'
{ _rcnName :: !(Maybe Text)
, _rcnId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
reconcileCandidateNotable
:: ReconcileCandidateNotable
reconcileCandidateNotable =
ReconcileCandidateNotable'
{ _rcnName = Nothing
, _rcnId = Nothing
}
rcnName :: Lens' ReconcileCandidateNotable (Maybe Text)
rcnName = lens _rcnName (\ s a -> s{_rcnName = a})
rcnId :: Lens' ReconcileCandidateNotable (Maybe Text)
rcnId = lens _rcnId (\ s a -> s{_rcnId = a})
instance FromJSON ReconcileCandidateNotable where
parseJSON
= withObject "ReconcileCandidateNotable"
(\ o ->
ReconcileCandidateNotable' <$>
(o .:? "name") <*> (o .:? "id"))
instance ToJSON ReconcileCandidateNotable where
toJSON ReconcileCandidateNotable'{..}
= object
(catMaybes
[("name" .=) <$> _rcnName, ("id" .=) <$> _rcnId])
data ReconcileCandidate = ReconcileCandidate'
{ _rcLang :: !(Maybe Text)
, _rcConfidence :: !(Maybe (Textual Double))
, _rcName :: !(Maybe Text)
, _rcNotable :: !(Maybe ReconcileCandidateNotable)
, _rcMid :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
reconcileCandidate
:: ReconcileCandidate
reconcileCandidate =
ReconcileCandidate'
{ _rcLang = Nothing
, _rcConfidence = Nothing
, _rcName = Nothing
, _rcNotable = Nothing
, _rcMid = Nothing
}
rcLang :: Lens' ReconcileCandidate (Maybe Text)
rcLang = lens _rcLang (\ s a -> s{_rcLang = a})
rcConfidence :: Lens' ReconcileCandidate (Maybe Double)
rcConfidence
= lens _rcConfidence (\ s a -> s{_rcConfidence = a})
. mapping _Coerce
rcName :: Lens' ReconcileCandidate (Maybe Text)
rcName = lens _rcName (\ s a -> s{_rcName = a})
rcNotable :: Lens' ReconcileCandidate (Maybe ReconcileCandidateNotable)
rcNotable
= lens _rcNotable (\ s a -> s{_rcNotable = a})
rcMid :: Lens' ReconcileCandidate (Maybe Text)
rcMid = lens _rcMid (\ s a -> s{_rcMid = a})
instance FromJSON ReconcileCandidate where
parseJSON
= withObject "ReconcileCandidate"
(\ o ->
ReconcileCandidate' <$>
(o .:? "lang") <*> (o .:? "confidence") <*>
(o .:? "name")
<*> (o .:? "notable")
<*> (o .:? "mid"))
instance ToJSON ReconcileCandidate where
toJSON ReconcileCandidate'{..}
= object
(catMaybes
[("lang" .=) <$> _rcLang,
("confidence" .=) <$> _rcConfidence,
("name" .=) <$> _rcName,
("notable" .=) <$> _rcNotable,
("mid" .=) <$> _rcMid])