module Hetzner.DNS (
Token (..)
, getTokenFromEnv
, ZoneID (..)
, ZoneStatus (..)
, Zone (..)
, getZones
, getZone
, updateZone
, deleteZone
, RecordID (..)
, RecordType (..)
, allRecordTypes
, Record (..)
, getRecords
, getRecord
, createRecord
, updateRecord
, deleteRecord
, DNSException (..)
, streamPages
, streamToList
, dnsQuery
, noBody
, WithKey (..)
, WithMeta (..)
, ResponseMeta (..)
, Pagination (..)
) where
import Hetzner.Cloud
( WithKey (..), WithMeta (..)
, ResponseMeta (..), Pagination (..), noBody
, streamPages, streamToList
)
import Data.String (IsString, fromString)
import Data.Maybe (maybeToList)
import System.Environment qualified as System
import Control.Exception (Exception, throwIO)
import Data.Foldable (find)
import Data.ByteString (ByteString)
import Data.Aeson (FromJSON, ToJSON, (.:), (.:?), (.!=), (.=))
import Data.Aeson qualified as JSON
import Network.HTTP.Simple as HTTP
import Data.Time (ZonedTime, parseTimeM, defaultTimeLocale)
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Text.Encoding (encodeUtf8)
newtype Token = Token ByteString deriving (Int -> Token -> ShowS
[Token] -> ShowS
Token -> String
(Int -> Token -> ShowS)
-> (Token -> String) -> ([Token] -> ShowS) -> Show Token
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Token -> ShowS
showsPrec :: Int -> Token -> ShowS
$cshow :: Token -> String
show :: Token -> String
$cshowList :: [Token] -> ShowS
showList :: [Token] -> ShowS
Show, Token -> Token -> Bool
(Token -> Token -> Bool) -> (Token -> Token -> Bool) -> Eq Token
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Token -> Token -> Bool
== :: Token -> Token -> Bool
$c/= :: Token -> Token -> Bool
/= :: Token -> Token -> Bool
Eq, Eq Token
Eq Token =>
(Token -> Token -> Ordering)
-> (Token -> Token -> Bool)
-> (Token -> Token -> Bool)
-> (Token -> Token -> Bool)
-> (Token -> Token -> Bool)
-> (Token -> Token -> Token)
-> (Token -> Token -> Token)
-> Ord Token
Token -> Token -> Bool
Token -> Token -> Ordering
Token -> Token -> Token
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Token -> Token -> Ordering
compare :: Token -> Token -> Ordering
$c< :: Token -> Token -> Bool
< :: Token -> Token -> Bool
$c<= :: Token -> Token -> Bool
<= :: Token -> Token -> Bool
$c> :: Token -> Token -> Bool
> :: Token -> Token -> Bool
$c>= :: Token -> Token -> Bool
>= :: Token -> Token -> Bool
$cmax :: Token -> Token -> Token
max :: Token -> Token -> Token
$cmin :: Token -> Token -> Token
min :: Token -> Token -> Token
Ord)
instance IsString Token where
fromString :: String -> Token
fromString = ByteString -> Token
Token (ByteString -> Token) -> (String -> ByteString) -> String -> Token
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
forall a. IsString a => String -> a
fromString
getTokenFromEnv :: IO (Maybe Token)
getTokenFromEnv :: IO (Maybe Token)
getTokenFromEnv = (String -> Token) -> Maybe String -> Maybe Token
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Token
forall a. IsString a => String -> a
fromString (Maybe String -> Maybe Token)
-> IO (Maybe String) -> IO (Maybe Token)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
System.lookupEnv String
"HETZNER_DNS_TOKEN"
data DNSException =
DNSError (HTTP.Response ByteString)
| JSONError (HTTP.Response ByteString) String
deriving Int -> DNSException -> ShowS
[DNSException] -> ShowS
DNSException -> String
(Int -> DNSException -> ShowS)
-> (DNSException -> String)
-> ([DNSException] -> ShowS)
-> Show DNSException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DNSException -> ShowS
showsPrec :: Int -> DNSException -> ShowS
$cshow :: DNSException -> String
show :: DNSException -> String
$cshowList :: [DNSException] -> ShowS
showList :: [DNSException] -> ShowS
Show
instance Exception DNSException
dnsQuery
:: (ToJSON body, FromJSON a)
=> ByteString
-> ByteString
-> Maybe body
-> HTTP.Query
-> Token
-> Maybe Int
-> IO a
dnsQuery :: forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
method ByteString
path Maybe body
mbody Query
query (Token ByteString
token) Maybe Int
mpage = do
let req :: Request
req = ByteString -> Request -> Request
HTTP.setRequestMethod ByteString
method
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ Bool -> Request -> Request
HTTP.setRequestSecure Bool
True
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ ByteString -> Request -> Request
HTTP.setRequestHost ByteString
"dns.hetzner.com"
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ Int -> Request -> Request
HTTP.setRequestPort Int
443
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ ByteString -> Request -> Request
HTTP.setRequestPath (ByteString
"/api/v1" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
path)
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ (Request -> Request)
-> (body -> Request -> Request) -> Maybe body -> Request -> Request
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Request -> Request
forall a. a -> a
id body -> Request -> Request
forall a. ToJSON a => a -> Request -> Request
HTTP.setRequestBodyJSON Maybe body
mbody
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ HeaderName -> ByteString -> Request -> Request
HTTP.addRequestHeader HeaderName
"Auth-API-Token" ByteString
token
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ Query -> Request -> Request
HTTP.addToRequestQueryString Query
query
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ (Request -> Request)
-> (Int -> Request -> Request) -> Maybe Int -> Request -> Request
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Request -> Request
forall a. a -> a
id (\Int
page -> Query -> Request -> Request
HTTP.addToRequestQueryString
[(ByteString
"page", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
page)]) Maybe Int
mpage
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ Request
HTTP.defaultRequest
Response ByteString
resp <- Request -> IO (Response ByteString)
forall (m :: * -> *).
MonadIO m =>
Request -> m (Response ByteString)
HTTP.httpBS Request
req
let body :: ByteString
body = Response ByteString -> ByteString
forall a. Response a -> a
HTTP.getResponseBody Response ByteString
resp
case Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod (Response ByteString -> Int
forall a. Response a -> Int
HTTP.getResponseStatusCode Response ByteString
resp) Int
100 of
(Int
2,Int
m) ->
let body' :: ByteString
body' = if Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 then ByteString
"{}" else ByteString
body
in case ByteString -> Either String a
forall a. FromJSON a => ByteString -> Either String a
JSON.eitherDecodeStrict ByteString
body' of
Left String
err -> DNSException -> IO a
forall e a. Exception e => e -> IO a
throwIO (DNSException -> IO a) -> DNSException -> IO a
forall a b. (a -> b) -> a -> b
$ Response ByteString -> String -> DNSException
JSONError Response ByteString
resp String
err
Right a
x -> a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
(Int, Int)
_ -> DNSException -> IO a
forall e a. Exception e => e -> IO a
throwIO (DNSException -> IO a) -> DNSException -> IO a
forall a b. (a -> b) -> a -> b
$ Response ByteString -> DNSException
DNSError Response ByteString
resp
newtype DNSTime = DNSTime { DNSTime -> ZonedTime
dnsTime :: ZonedTime }
instance FromJSON DNSTime where
parseJSON :: Value -> Parser DNSTime
parseJSON = String -> (Text -> Parser DNSTime) -> Value -> Parser DNSTime
forall a. String -> (Text -> Parser a) -> Value -> Parser a
JSON.withText String
"DNSTime" ((Text -> Parser DNSTime) -> Value -> Parser DNSTime)
-> (Text -> Parser DNSTime) -> Value -> Parser DNSTime
forall a b. (a -> b) -> a -> b
$
let format :: String
format = String
"%F %T%Q %z %Z"
in (ZonedTime -> DNSTime) -> Parser ZonedTime -> Parser DNSTime
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ZonedTime -> DNSTime
DNSTime (Parser ZonedTime -> Parser DNSTime)
-> (Text -> Parser ZonedTime) -> Text -> Parser DNSTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> TimeLocale -> String -> String -> Parser ZonedTime
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
parseTimeM Bool
False TimeLocale
defaultTimeLocale String
format (String -> Parser ZonedTime)
-> (Text -> String) -> Text -> Parser ZonedTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
newtype ZoneID = ZoneID Text deriving (ZoneID -> ZoneID -> Bool
(ZoneID -> ZoneID -> Bool)
-> (ZoneID -> ZoneID -> Bool) -> Eq ZoneID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ZoneID -> ZoneID -> Bool
== :: ZoneID -> ZoneID -> Bool
$c/= :: ZoneID -> ZoneID -> Bool
/= :: ZoneID -> ZoneID -> Bool
Eq, Eq ZoneID
Eq ZoneID =>
(ZoneID -> ZoneID -> Ordering)
-> (ZoneID -> ZoneID -> Bool)
-> (ZoneID -> ZoneID -> Bool)
-> (ZoneID -> ZoneID -> Bool)
-> (ZoneID -> ZoneID -> Bool)
-> (ZoneID -> ZoneID -> ZoneID)
-> (ZoneID -> ZoneID -> ZoneID)
-> Ord ZoneID
ZoneID -> ZoneID -> Bool
ZoneID -> ZoneID -> Ordering
ZoneID -> ZoneID -> ZoneID
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ZoneID -> ZoneID -> Ordering
compare :: ZoneID -> ZoneID -> Ordering
$c< :: ZoneID -> ZoneID -> Bool
< :: ZoneID -> ZoneID -> Bool
$c<= :: ZoneID -> ZoneID -> Bool
<= :: ZoneID -> ZoneID -> Bool
$c> :: ZoneID -> ZoneID -> Bool
> :: ZoneID -> ZoneID -> Bool
$c>= :: ZoneID -> ZoneID -> Bool
>= :: ZoneID -> ZoneID -> Bool
$cmax :: ZoneID -> ZoneID -> ZoneID
max :: ZoneID -> ZoneID -> ZoneID
$cmin :: ZoneID -> ZoneID -> ZoneID
min :: ZoneID -> ZoneID -> ZoneID
Ord, Int -> ZoneID -> ShowS
[ZoneID] -> ShowS
ZoneID -> String
(Int -> ZoneID -> ShowS)
-> (ZoneID -> String) -> ([ZoneID] -> ShowS) -> Show ZoneID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ZoneID -> ShowS
showsPrec :: Int -> ZoneID -> ShowS
$cshow :: ZoneID -> String
show :: ZoneID -> String
$cshowList :: [ZoneID] -> ShowS
showList :: [ZoneID] -> ShowS
Show, Maybe ZoneID
Value -> Parser [ZoneID]
Value -> Parser ZoneID
(Value -> Parser ZoneID)
-> (Value -> Parser [ZoneID]) -> Maybe ZoneID -> FromJSON ZoneID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ZoneID
parseJSON :: Value -> Parser ZoneID
$cparseJSONList :: Value -> Parser [ZoneID]
parseJSONList :: Value -> Parser [ZoneID]
$comittedField :: Maybe ZoneID
omittedField :: Maybe ZoneID
FromJSON, [ZoneID] -> Value
[ZoneID] -> Encoding
ZoneID -> Bool
ZoneID -> Value
ZoneID -> Encoding
(ZoneID -> Value)
-> (ZoneID -> Encoding)
-> ([ZoneID] -> Value)
-> ([ZoneID] -> Encoding)
-> (ZoneID -> Bool)
-> ToJSON ZoneID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ZoneID -> Value
toJSON :: ZoneID -> Value
$ctoEncoding :: ZoneID -> Encoding
toEncoding :: ZoneID -> Encoding
$ctoJSONList :: [ZoneID] -> Value
toJSONList :: [ZoneID] -> Value
$ctoEncodingList :: [ZoneID] -> Encoding
toEncodingList :: [ZoneID] -> Encoding
$comitField :: ZoneID -> Bool
omitField :: ZoneID -> Bool
ToJSON)
data ZoneStatus = Verified | Failed | Pending deriving Int -> ZoneStatus -> ShowS
[ZoneStatus] -> ShowS
ZoneStatus -> String
(Int -> ZoneStatus -> ShowS)
-> (ZoneStatus -> String)
-> ([ZoneStatus] -> ShowS)
-> Show ZoneStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ZoneStatus -> ShowS
showsPrec :: Int -> ZoneStatus -> ShowS
$cshow :: ZoneStatus -> String
show :: ZoneStatus -> String
$cshowList :: [ZoneStatus] -> ShowS
showList :: [ZoneStatus] -> ShowS
Show
instance FromJSON ZoneStatus where
parseJSON :: Value -> Parser ZoneStatus
parseJSON = String -> (Text -> Parser ZoneStatus) -> Value -> Parser ZoneStatus
forall a. String -> (Text -> Parser a) -> Value -> Parser a
JSON.withText String
"ZoneStatus" ((Text -> Parser ZoneStatus) -> Value -> Parser ZoneStatus)
-> (Text -> Parser ZoneStatus) -> Value -> Parser ZoneStatus
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text
t of
Text
"verified" -> ZoneStatus -> Parser ZoneStatus
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ZoneStatus
Verified
Text
"failed" -> ZoneStatus -> Parser ZoneStatus
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ZoneStatus
Failed
Text
"pending" -> ZoneStatus -> Parser ZoneStatus
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ZoneStatus
Pending
Text
_ -> String -> Parser ZoneStatus
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ZoneStatus) -> String -> Parser ZoneStatus
forall a b. (a -> b) -> a -> b
$ String
"Invalid zone status: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
t
data Zone = Zone
{ Zone -> ZonedTime
zoneCreated :: ZonedTime
, Zone -> ZonedTime
zoneModified :: ZonedTime
, Zone -> ZoneID
zoneID :: ZoneID
, Zone -> Text
zoneName :: Text
, Zone -> Bool
zoneIsSecondary :: Bool
, Zone -> ZoneStatus
zoneStatus :: ZoneStatus
, Zone -> Int
zoneRecordCount :: Int
, Zone -> Int
zoneTTL :: Int
} deriving Int -> Zone -> ShowS
[Zone] -> ShowS
Zone -> String
(Int -> Zone -> ShowS)
-> (Zone -> String) -> ([Zone] -> ShowS) -> Show Zone
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Zone -> ShowS
showsPrec :: Int -> Zone -> ShowS
$cshow :: Zone -> String
show :: Zone -> String
$cshowList :: [Zone] -> ShowS
showList :: [Zone] -> ShowS
Show
instance FromJSON Zone where
parseJSON :: Value -> Parser Zone
parseJSON = String -> (Object -> Parser Zone) -> Value -> Parser Zone
forall a. String -> (Object -> Parser a) -> Value -> Parser a
JSON.withObject String
"Zone" ((Object -> Parser Zone) -> Value -> Parser Zone)
-> (Object -> Parser Zone) -> Value -> Parser Zone
forall a b. (a -> b) -> a -> b
$ \Object
o -> ZonedTime
-> ZonedTime
-> ZoneID
-> Text
-> Bool
-> ZoneStatus
-> Int
-> Int
-> Zone
Zone
(ZonedTime
-> ZonedTime
-> ZoneID
-> Text
-> Bool
-> ZoneStatus
-> Int
-> Int
-> Zone)
-> Parser ZonedTime
-> Parser
(ZonedTime
-> ZoneID -> Text -> Bool -> ZoneStatus -> Int -> Int -> Zone)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DNSTime -> ZonedTime
dnsTime (DNSTime -> ZonedTime) -> Parser DNSTime -> Parser ZonedTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser DNSTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created")
Parser
(ZonedTime
-> ZoneID -> Text -> Bool -> ZoneStatus -> Int -> Int -> Zone)
-> Parser ZonedTime
-> Parser
(ZoneID -> Text -> Bool -> ZoneStatus -> Int -> Int -> Zone)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DNSTime -> ZonedTime
dnsTime (DNSTime -> ZonedTime) -> Parser DNSTime -> Parser ZonedTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser DNSTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"modified")
Parser (ZoneID -> Text -> Bool -> ZoneStatus -> Int -> Int -> Zone)
-> Parser ZoneID
-> Parser (Text -> Bool -> ZoneStatus -> Int -> Int -> Zone)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ZoneID
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Text -> Bool -> ZoneStatus -> Int -> Int -> Zone)
-> Parser Text -> Parser (Bool -> ZoneStatus -> Int -> Int -> Zone)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (Bool -> ZoneStatus -> Int -> Int -> Zone)
-> Parser Bool -> Parser (ZoneStatus -> Int -> Int -> Zone)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"is_secondary_dns"
Parser (ZoneStatus -> Int -> Int -> Zone)
-> Parser ZoneStatus -> Parser (Int -> Int -> Zone)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ZoneStatus
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"status"
Parser (Int -> Int -> Zone) -> Parser Int -> Parser (Int -> Zone)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"records_count"
Parser (Int -> Zone) -> Parser Int -> Parser Zone
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ttl"
getZones :: Token -> Maybe Int -> IO (WithMeta "zones" [Zone])
getZones :: Token -> Maybe Int -> IO (WithMeta "zones" [Zone])
getZones = ByteString
-> ByteString
-> Maybe Void
-> Query
-> Token
-> Maybe Int
-> IO (WithMeta "zones" [Zone])
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"GET" ByteString
"/zones" Maybe Void
noBody []
getZone :: Token -> ZoneID -> IO Zone
getZone :: Token -> ZoneID -> IO Zone
getZone Token
token (ZoneID Text
i) = forall (key :: Symbol) a. WithKey key a -> a
withoutKey @"zone" (WithKey "zone" Zone -> Zone)
-> IO (WithKey "zone" Zone) -> IO Zone
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString
-> ByteString
-> Maybe Void
-> Query
-> Token
-> Maybe Int
-> IO (WithKey "zone" Zone)
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"GET" (ByteString
"/zones/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
i) Maybe Void
noBody [] Token
token Maybe Int
forall a. Maybe a
Nothing
updateZone
:: Token
-> ZoneID
-> Text
-> Maybe Int
-> IO Zone
updateZone :: Token -> ZoneID -> Text -> Maybe Int -> IO Zone
updateZone Token
token (ZoneID Text
i) Text
name Maybe Int
mttl = forall (key :: Symbol) a. WithKey key a -> a
withoutKey @"zone" (WithKey "zone" Zone -> Zone)
-> IO (WithKey "zone" Zone) -> IO Zone
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
let body :: Value
body = [Pair] -> Value
JSON.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ (Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name) Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Maybe Pair -> [Pair]
forall a. Maybe a -> [a]
maybeToList ((Int -> Pair) -> Maybe Int -> Maybe Pair
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key
"ttl" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) Maybe Int
mttl)
in ByteString
-> ByteString
-> Maybe Value
-> Query
-> Token
-> Maybe Int
-> IO (WithKey "zone" Zone)
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"PUT" (ByteString
"/zones/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
i) (Value -> Maybe Value
forall a. a -> Maybe a
Just Value
body) [] Token
token Maybe Int
forall a. Maybe a
Nothing
deleteZone :: Token -> ZoneID -> IO ()
deleteZone :: Token -> ZoneID -> IO ()
deleteZone Token
token (ZoneID Text
i) = ByteString
-> ByteString -> Maybe Void -> Query -> Token -> Maybe Int -> IO ()
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"DELETE" (ByteString
"/zones/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
i) Maybe Void
noBody [] Token
token Maybe Int
forall a. Maybe a
Nothing
newtype RecordID = RecordID Text deriving (RecordID -> RecordID -> Bool
(RecordID -> RecordID -> Bool)
-> (RecordID -> RecordID -> Bool) -> Eq RecordID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecordID -> RecordID -> Bool
== :: RecordID -> RecordID -> Bool
$c/= :: RecordID -> RecordID -> Bool
/= :: RecordID -> RecordID -> Bool
Eq, Eq RecordID
Eq RecordID =>
(RecordID -> RecordID -> Ordering)
-> (RecordID -> RecordID -> Bool)
-> (RecordID -> RecordID -> Bool)
-> (RecordID -> RecordID -> Bool)
-> (RecordID -> RecordID -> Bool)
-> (RecordID -> RecordID -> RecordID)
-> (RecordID -> RecordID -> RecordID)
-> Ord RecordID
RecordID -> RecordID -> Bool
RecordID -> RecordID -> Ordering
RecordID -> RecordID -> RecordID
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RecordID -> RecordID -> Ordering
compare :: RecordID -> RecordID -> Ordering
$c< :: RecordID -> RecordID -> Bool
< :: RecordID -> RecordID -> Bool
$c<= :: RecordID -> RecordID -> Bool
<= :: RecordID -> RecordID -> Bool
$c> :: RecordID -> RecordID -> Bool
> :: RecordID -> RecordID -> Bool
$c>= :: RecordID -> RecordID -> Bool
>= :: RecordID -> RecordID -> Bool
$cmax :: RecordID -> RecordID -> RecordID
max :: RecordID -> RecordID -> RecordID
$cmin :: RecordID -> RecordID -> RecordID
min :: RecordID -> RecordID -> RecordID
Ord, Int -> RecordID -> ShowS
[RecordID] -> ShowS
RecordID -> String
(Int -> RecordID -> ShowS)
-> (RecordID -> String) -> ([RecordID] -> ShowS) -> Show RecordID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RecordID -> ShowS
showsPrec :: Int -> RecordID -> ShowS
$cshow :: RecordID -> String
show :: RecordID -> String
$cshowList :: [RecordID] -> ShowS
showList :: [RecordID] -> ShowS
Show, Maybe RecordID
Value -> Parser [RecordID]
Value -> Parser RecordID
(Value -> Parser RecordID)
-> (Value -> Parser [RecordID])
-> Maybe RecordID
-> FromJSON RecordID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RecordID
parseJSON :: Value -> Parser RecordID
$cparseJSONList :: Value -> Parser [RecordID]
parseJSONList :: Value -> Parser [RecordID]
$comittedField :: Maybe RecordID
omittedField :: Maybe RecordID
FromJSON, [RecordID] -> Value
[RecordID] -> Encoding
RecordID -> Bool
RecordID -> Value
RecordID -> Encoding
(RecordID -> Value)
-> (RecordID -> Encoding)
-> ([RecordID] -> Value)
-> ([RecordID] -> Encoding)
-> (RecordID -> Bool)
-> ToJSON RecordID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: RecordID -> Value
toJSON :: RecordID -> Value
$ctoEncoding :: RecordID -> Encoding
toEncoding :: RecordID -> Encoding
$ctoJSONList :: [RecordID] -> Value
toJSONList :: [RecordID] -> Value
$ctoEncodingList :: [RecordID] -> Encoding
toEncodingList :: [RecordID] -> Encoding
$comitField :: RecordID -> Bool
omitField :: RecordID -> Bool
ToJSON)
data RecordType =
A | AAAA | CAA | CNAME | DANE | DS | HINFO | MX | NS | PTR | RP | SOA | SRV | TLS | TXT
deriving (RecordType -> RecordType -> Bool
(RecordType -> RecordType -> Bool)
-> (RecordType -> RecordType -> Bool) -> Eq RecordType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecordType -> RecordType -> Bool
== :: RecordType -> RecordType -> Bool
$c/= :: RecordType -> RecordType -> Bool
/= :: RecordType -> RecordType -> Bool
Eq, Int -> RecordType -> ShowS
[RecordType] -> ShowS
RecordType -> String
(Int -> RecordType -> ShowS)
-> (RecordType -> String)
-> ([RecordType] -> ShowS)
-> Show RecordType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RecordType -> ShowS
showsPrec :: Int -> RecordType -> ShowS
$cshow :: RecordType -> String
show :: RecordType -> String
$cshowList :: [RecordType] -> ShowS
showList :: [RecordType] -> ShowS
Show, Int -> RecordType
RecordType -> Int
RecordType -> [RecordType]
RecordType -> RecordType
RecordType -> RecordType -> [RecordType]
RecordType -> RecordType -> RecordType -> [RecordType]
(RecordType -> RecordType)
-> (RecordType -> RecordType)
-> (Int -> RecordType)
-> (RecordType -> Int)
-> (RecordType -> [RecordType])
-> (RecordType -> RecordType -> [RecordType])
-> (RecordType -> RecordType -> [RecordType])
-> (RecordType -> RecordType -> RecordType -> [RecordType])
-> Enum RecordType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RecordType -> RecordType
succ :: RecordType -> RecordType
$cpred :: RecordType -> RecordType
pred :: RecordType -> RecordType
$ctoEnum :: Int -> RecordType
toEnum :: Int -> RecordType
$cfromEnum :: RecordType -> Int
fromEnum :: RecordType -> Int
$cenumFrom :: RecordType -> [RecordType]
enumFrom :: RecordType -> [RecordType]
$cenumFromThen :: RecordType -> RecordType -> [RecordType]
enumFromThen :: RecordType -> RecordType -> [RecordType]
$cenumFromTo :: RecordType -> RecordType -> [RecordType]
enumFromTo :: RecordType -> RecordType -> [RecordType]
$cenumFromThenTo :: RecordType -> RecordType -> RecordType -> [RecordType]
enumFromThenTo :: RecordType -> RecordType -> RecordType -> [RecordType]
Enum)
allRecordTypes :: [RecordType]
allRecordTypes :: [RecordType]
allRecordTypes = [RecordType
A ..]
instance FromJSON RecordType where
parseJSON :: Value -> Parser RecordType
parseJSON = String -> (Text -> Parser RecordType) -> Value -> Parser RecordType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
JSON.withText String
"RecordType" ((Text -> Parser RecordType) -> Value -> Parser RecordType)
-> (Text -> Parser RecordType) -> Value -> Parser RecordType
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case (RecordType -> Bool) -> [RecordType] -> Maybe RecordType
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==) Text
t (Text -> Bool) -> (RecordType -> Text) -> RecordType -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (RecordType -> String) -> RecordType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RecordType -> String
forall a. Show a => a -> String
show) [RecordType]
allRecordTypes of
Just RecordType
rtype -> RecordType -> Parser RecordType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure RecordType
rtype
Maybe RecordType
_ -> String -> Parser RecordType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser RecordType) -> String -> Parser RecordType
forall a b. (a -> b) -> a -> b
$ String
"Invalid record type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
t
instance ToJSON RecordType where
toJSON :: RecordType -> Value
toJSON = Text -> Value
JSON.String (Text -> Value) -> (RecordType -> Text) -> RecordType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (RecordType -> String) -> RecordType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RecordType -> String
forall a. Show a => a -> String
show
data Record = Record
{ Record -> ZonedTime
recordCreated :: ZonedTime
, Record -> ZonedTime
recordModified :: ZonedTime
, Record -> RecordID
recordID :: RecordID
, Record -> Text
recordName :: Text
, Record -> RecordType
recordType :: RecordType
, Record -> Text
recordValue :: Text
, Record -> Int
recordTTL :: Int
, Record -> ZoneID
recordZone :: ZoneID
} deriving Int -> Record -> ShowS
[Record] -> ShowS
Record -> String
(Int -> Record -> ShowS)
-> (Record -> String) -> ([Record] -> ShowS) -> Show Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Record -> ShowS
showsPrec :: Int -> Record -> ShowS
$cshow :: Record -> String
show :: Record -> String
$cshowList :: [Record] -> ShowS
showList :: [Record] -> ShowS
Show
instance FromJSON Record where
parseJSON :: Value -> Parser Record
parseJSON = String -> (Object -> Parser Record) -> Value -> Parser Record
forall a. String -> (Object -> Parser a) -> Value -> Parser a
JSON.withObject String
"Record" ((Object -> Parser Record) -> Value -> Parser Record)
-> (Object -> Parser Record) -> Value -> Parser Record
forall a b. (a -> b) -> a -> b
$ \Object
o -> ZonedTime
-> ZonedTime
-> RecordID
-> Text
-> RecordType
-> Text
-> Int
-> ZoneID
-> Record
Record
(ZonedTime
-> ZonedTime
-> RecordID
-> Text
-> RecordType
-> Text
-> Int
-> ZoneID
-> Record)
-> Parser ZonedTime
-> Parser
(ZonedTime
-> RecordID
-> Text
-> RecordType
-> Text
-> Int
-> ZoneID
-> Record)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DNSTime -> ZonedTime
dnsTime (DNSTime -> ZonedTime) -> Parser DNSTime -> Parser ZonedTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser DNSTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created")
Parser
(ZonedTime
-> RecordID
-> Text
-> RecordType
-> Text
-> Int
-> ZoneID
-> Record)
-> Parser ZonedTime
-> Parser
(RecordID -> Text -> RecordType -> Text -> Int -> ZoneID -> Record)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DNSTime -> ZonedTime
dnsTime (DNSTime -> ZonedTime) -> Parser DNSTime -> Parser ZonedTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser DNSTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"modified")
Parser
(RecordID -> Text -> RecordType -> Text -> Int -> ZoneID -> Record)
-> Parser RecordID
-> Parser (Text -> RecordType -> Text -> Int -> ZoneID -> Record)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser RecordID
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Text -> RecordType -> Text -> Int -> ZoneID -> Record)
-> Parser Text
-> Parser (RecordType -> Text -> Int -> ZoneID -> Record)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (RecordType -> Text -> Int -> ZoneID -> Record)
-> Parser RecordType -> Parser (Text -> Int -> ZoneID -> Record)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser RecordType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (Text -> Int -> ZoneID -> Record)
-> Parser Text -> Parser (Int -> ZoneID -> Record)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"value"
Parser (Int -> ZoneID -> Record)
-> Parser Int -> Parser (ZoneID -> Record)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ttl" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
86400
Parser (ZoneID -> Record) -> Parser ZoneID -> Parser Record
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ZoneID
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"zone_id"
getRecords
:: Token
-> Maybe ZoneID
-> IO [Record]
getRecords :: Token -> Maybe ZoneID -> IO [Record]
getRecords Token
token Maybe ZoneID
mzone = forall (key :: Symbol) a. WithKey key a -> a
withoutKey @"records" (WithKey "records" [Record] -> [Record])
-> IO (WithKey "records" [Record]) -> IO [Record]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
let query :: Query
query = Query -> (ZoneID -> Query) -> Maybe ZoneID -> Query
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\(ZoneID Text
zone) -> [(ByteString
"zone_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
zone)]) Maybe ZoneID
mzone
in ByteString
-> ByteString
-> Maybe Void
-> Query
-> Token
-> Maybe Int
-> IO (WithKey "records" [Record])
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"GET" ByteString
"/records" Maybe Void
noBody Query
query Token
token Maybe Int
forall a. Maybe a
Nothing
getRecord :: Token -> RecordID -> IO Record
getRecord :: Token -> RecordID -> IO Record
getRecord Token
token (RecordID Text
i) = forall (key :: Symbol) a. WithKey key a -> a
withoutKey @"record" (WithKey "record" Record -> Record)
-> IO (WithKey "record" Record) -> IO Record
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ByteString
-> ByteString
-> Maybe Void
-> Query
-> Token
-> Maybe Int
-> IO (WithKey "record" Record)
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"GET" (ByteString
"/records/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
i) Maybe Void
noBody [] Token
token Maybe Int
forall a. Maybe a
Nothing
createRecord
:: Token
-> ZoneID
-> Text
-> RecordType
-> Text
-> Maybe Int
-> IO Record
createRecord :: Token
-> ZoneID -> Text -> RecordType -> Text -> Maybe Int -> IO Record
createRecord Token
token ZoneID
zone Text
name RecordType
rtype Text
value Maybe Int
mttl = forall (key :: Symbol) a. WithKey key a -> a
withoutKey @"record" (WithKey "record" Record -> Record)
-> IO (WithKey "record" Record) -> IO Record
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
let body :: Value
body = [Pair] -> Value
JSON.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"zone_id" Key -> ZoneID -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ZoneID
zone
, Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name
, Key
"type" Key -> RecordType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= RecordType
rtype
, Key
"value" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
value
] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
"ttl" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=)) Maybe Int
mttl
in ByteString
-> ByteString
-> Maybe Value
-> Query
-> Token
-> Maybe Int
-> IO (WithKey "record" Record)
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"POST" ByteString
"/records" (Value -> Maybe Value
forall a. a -> Maybe a
Just Value
body) [] Token
token Maybe Int
forall a. Maybe a
Nothing
updateRecord
:: Token
-> RecordID
-> ZoneID
-> Text
-> RecordType
-> Text
-> Maybe Int
-> IO Record
updateRecord :: Token
-> RecordID
-> ZoneID
-> Text
-> RecordType
-> Text
-> Maybe Int
-> IO Record
updateRecord Token
token (RecordID Text
i) ZoneID
zone Text
name RecordType
rtype Text
value Maybe Int
mttl = forall (key :: Symbol) a. WithKey key a -> a
withoutKey @"record" (WithKey "record" Record -> Record)
-> IO (WithKey "record" Record) -> IO Record
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
let body :: Value
body = [Pair] -> Value
JSON.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"zone_id" Key -> ZoneID -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ZoneID
zone
, Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name
, Key
"type" Key -> RecordType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= RecordType
rtype
, Key
"value" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
value
] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
"ttl" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=)) Maybe Int
mttl
in ByteString
-> ByteString
-> Maybe Value
-> Query
-> Token
-> Maybe Int
-> IO (WithKey "record" Record)
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"PUT" (ByteString
"/records/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
i) (Value -> Maybe Value
forall a. a -> Maybe a
Just Value
body) [] Token
token Maybe Int
forall a. Maybe a
Nothing
deleteRecord :: Token -> RecordID -> IO ()
deleteRecord :: Token -> RecordID -> IO ()
deleteRecord Token
token (RecordID Text
i) =
ByteString
-> ByteString -> Maybe Void -> Query -> Token -> Maybe Int -> IO ()
forall body a.
(ToJSON body, FromJSON a) =>
ByteString
-> ByteString -> Maybe body -> Query -> Token -> Maybe Int -> IO a
dnsQuery ByteString
"DELETE" (ByteString
"/records/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
i) Maybe Void
noBody [] Token
token Maybe Int
forall a. Maybe a
Nothing