module OpenAI.V1.AutoOr
(
AutoOr(..)
) where
import OpenAI.Prelude
data AutoOr a = Auto | Specific a
deriving stock ((forall x. AutoOr a -> Rep (AutoOr a) x)
-> (forall x. Rep (AutoOr a) x -> AutoOr a) -> Generic (AutoOr a)
forall x. Rep (AutoOr a) x -> AutoOr a
forall x. AutoOr a -> Rep (AutoOr a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (AutoOr a) x -> AutoOr a
forall a x. AutoOr a -> Rep (AutoOr a) x
$cfrom :: forall a x. AutoOr a -> Rep (AutoOr a) x
from :: forall x. AutoOr a -> Rep (AutoOr a) x
$cto :: forall a x. Rep (AutoOr a) x -> AutoOr a
to :: forall x. Rep (AutoOr a) x -> AutoOr a
Generic, Int -> AutoOr a -> ShowS
[AutoOr a] -> ShowS
AutoOr a -> String
(Int -> AutoOr a -> ShowS)
-> (AutoOr a -> String) -> ([AutoOr a] -> ShowS) -> Show (AutoOr a)
forall a. Show a => Int -> AutoOr a -> ShowS
forall a. Show a => [AutoOr a] -> ShowS
forall a. Show a => AutoOr a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> AutoOr a -> ShowS
showsPrec :: Int -> AutoOr a -> ShowS
$cshow :: forall a. Show a => AutoOr a -> String
show :: AutoOr a -> String
$cshowList :: forall a. Show a => [AutoOr a] -> ShowS
showList :: [AutoOr a] -> ShowS
Show)
instance FromJSON a => FromJSON (AutoOr a) where
parseJSON :: Value -> Parser (AutoOr a)
parseJSON Value
"auto" = AutoOr a -> Parser (AutoOr a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AutoOr a
forall a. AutoOr a
Auto
parseJSON Value
value = (a -> AutoOr a) -> Parser a -> Parser (AutoOr a)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> AutoOr a
forall a. a -> AutoOr a
Specific (Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
value)
instance ToJSON a => ToJSON (AutoOr a) where
toJSON :: AutoOr a -> Value
toJSON AutoOr a
Auto = Value
"auto"
toJSON (Specific a
a) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a
instance IsString a => IsString (AutoOr a) where
fromString :: String -> AutoOr a
fromString String
string = a -> AutoOr a
forall a. a -> AutoOr a
Specific (String -> a
forall a. IsString a => String -> a
fromString String
string)