-- | -- Module : PowerDNS.Internal.Utils -- Description : Assorted utilities for the PowerDNS API {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE OverloadedStrings #-} module PowerDNS.Internal.Utils ( strip , map1 , Empty(..) , GEmpty(..) ) where import Data.List (stripPrefix) import GHC.Generics -- | A variant of 'stripPrefix' that defaults to id if the prefix is not found. strip :: Eq a => [a] -> [a] -> [a] strip p xs = case stripPrefix p xs of Just ys -> ys Nothing -> xs -- | Version of map that applies the function to the first element only map1 :: (a -> a) -> [a] -> [a] map1 f (x:xs) = f x : xs map1 _ xss = xss -- | Typeclass of things we can generate empty values of. -- This is used to quickly build values from parameters to PowerDNS, because -- you often only need a few fields. -- @ -- empty { someField = Just 1 -- , otherField = Just "foo" } -- @ class Empty a where -- | Produce an empty value empty :: a default empty :: (Generic a, GEmpty (Rep a)) => a empty = to gempty instance Empty (Maybe a) where empty = Nothing class GEmpty f where gempty :: f p instance GEmpty U1 where gempty = U1 instance GEmpty f => GEmpty (M1 i t f) where gempty = M1 gempty instance Empty a => GEmpty (K1 i a) where gempty = K1 empty instance (GEmpty f, GEmpty g) => GEmpty (f :*: g) where gempty = gempty :*: gempty