{-# LANGUAGE OverloadedStrings #-} module Network.Cloudflare.DNS.DNSSEC where import Control.Lens hiding ((.=)) import Data.Aeson import Data.Maybe import Data.Text (Text) import qualified Data.Text as Text import qualified Data.Text.Encoding as Text import Data.Time import Data.Word import Network.Cloudflare.Types import Network.Wreq -- https://developers.cloudflare.com/dns/dnssec/multi-signer-dnssec/setup/ -- | Get the DNSSEC settings for a zone getDNSSEC :: CloudflareAuth -> Text -> IO (Either String (ResultResponse DNSECDetails)) getDNSSEC authInfo zone = do let opts = defaults & header "Authorization" .~ ["Bearer " <> Text.encodeUtf8 (cloudflareAuthToken authInfo)] url = "https://api.cloudflare.com/client/v4/zones/" <> Text.unpack zone <> "/dnssec" r <- getWith opts url print r pure $ r ^. responseBody . to eitherDecode -- | Edit DNSSEC settings for a zone editDNSSEC :: CloudflareAuth -> Text -> EditDNSSECStatus -> IO (Either String (ResultResponse DNSSEC)) editDNSSEC authInfo zone edit = do let opts = defaults & header "Authorization" .~ ["Bearer " <> Text.encodeUtf8 (cloudflareAuthToken authInfo)] url = "https://api.cloudflare.com/client/v4/zones/" <> Text.unpack zone <> "/dnssec" r <- patchWith opts url $ toJSON edit pure $ r ^. responseBody . to eitherDecode -- | Edit DNSSEC settings for a zone, fields set to Nothing will not be changed data EditDNSSECStatus = EditDNSSECStatus { editDNSSECMultiSigner :: Maybe Bool -- ^ Enable or disable multi-signer DNSSEC , editDNSSECPresigned :: Maybe Bool -- ^ Enable or disable presigned DNSSEC , editDNSSECStatus :: Maybe DNSSECStatus -- ^ Enable or disable DNSSEC } deriving (Eq, Ord, Show) instance ToJSON EditDNSSECStatus where toJSON (EditDNSSECStatus multiSigner presigned status) = object $ catMaybes [ ("multi_signer" .=) <$> multiSigner , ("presigned" .=) <$> presigned , ("status" .=) <$> status ] -- | Status of DNSSec for a zone data DNSSECStatus = DNSSECActive | DNSSECDisabled deriving (Eq, Ord, Show) instance ToJSON DNSSECStatus where toJSON = String . dnssecStatusToText -- | Text representation of DNSSECStatus dnssecStatusToText :: DNSSECStatus -> Text dnssecStatusToText DNSSECActive = "active" dnssecStatusToText DNSSECDisabled = "disabled" -- data DNSECDetails = DNSSecActive DNSSEC | DNSSecDisabled | DNSSecPending DNSSEC deriving (Eq, Ord, Show) instance FromJSON DNSECDetails where parseJSON = withObject "DNSECDetails" $ \o -> do status <- o .: "status" case status of "active" -> DNSSecActive <$> parseJSON (Object o) "disabled" -> pure DNSSecDisabled "pending" -> DNSSecPending <$> parseJSON (Object o) _ -> fail $ "Unknown DNSSEC status: " <> status data DNSSEC = DNSSEC { dnssecAlgorithm :: Maybe Text , dnssecDigest :: Maybe Text , dnssecDigestType :: Maybe Text , dnssecMultiSigner :: Maybe Bool , dnssecPresigned :: Maybe Bool , dnssecDS :: Text , dnssecFlags :: Word8 , dnssecKeyTag :: Word16 , dnssecKeyType :: Text , dnssecModifiedOn :: UTCTime , dnssecPublicKey :: Text , dnssecStatus :: Text -- TODO this could be an enum with the status values but it's different from the existing DNSSECStatus } deriving (Eq, Ord, Show) instance FromJSON DNSSEC where parseJSON = withObject "EditDNSSEC" $ \o -> do algorithm <- o .:? "algorithm" digest <- o .:? "digest" digestType <- o .:? "digest_type" multiSigner <- o .:? "multi_signer" presigned <- o .:? "presigned" ds <- o .: "ds" flags <- o .: "flags" keyTag <- o .: "key_tag" keyType <- o .: "key_type" modifiedOn <- o .: "modified_on" pubKey <- o .: "public_key" status <- o .: "status" pure $ DNSSEC algorithm digest digestType multiSigner presigned ds flags keyTag keyType modifiedOn pubKey status