{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.QuickSight.Types.LayoutElementType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.QuickSight.Types.LayoutElementType
  ( LayoutElementType
      ( ..,
        LayoutElementType_FILTER_CONTROL,
        LayoutElementType_PARAMETER_CONTROL,
        LayoutElementType_TEXT_BOX,
        LayoutElementType_VISUAL
      ),
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

newtype LayoutElementType = LayoutElementType'
  { LayoutElementType -> Text
fromLayoutElementType ::
      Data.Text
  }
  deriving stock
    ( Int -> LayoutElementType -> ShowS
[LayoutElementType] -> ShowS
LayoutElementType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LayoutElementType] -> ShowS
$cshowList :: [LayoutElementType] -> ShowS
show :: LayoutElementType -> String
$cshow :: LayoutElementType -> String
showsPrec :: Int -> LayoutElementType -> ShowS
$cshowsPrec :: Int -> LayoutElementType -> ShowS
Prelude.Show,
      ReadPrec [LayoutElementType]
ReadPrec LayoutElementType
Int -> ReadS LayoutElementType
ReadS [LayoutElementType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LayoutElementType]
$creadListPrec :: ReadPrec [LayoutElementType]
readPrec :: ReadPrec LayoutElementType
$creadPrec :: ReadPrec LayoutElementType
readList :: ReadS [LayoutElementType]
$creadList :: ReadS [LayoutElementType]
readsPrec :: Int -> ReadS LayoutElementType
$creadsPrec :: Int -> ReadS LayoutElementType
Prelude.Read,
      LayoutElementType -> LayoutElementType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutElementType -> LayoutElementType -> Bool
$c/= :: LayoutElementType -> LayoutElementType -> Bool
== :: LayoutElementType -> LayoutElementType -> Bool
$c== :: LayoutElementType -> LayoutElementType -> Bool
Prelude.Eq,
      Eq LayoutElementType
LayoutElementType -> LayoutElementType -> Bool
LayoutElementType -> LayoutElementType -> Ordering
LayoutElementType -> LayoutElementType -> LayoutElementType
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
min :: LayoutElementType -> LayoutElementType -> LayoutElementType
$cmin :: LayoutElementType -> LayoutElementType -> LayoutElementType
max :: LayoutElementType -> LayoutElementType -> LayoutElementType
$cmax :: LayoutElementType -> LayoutElementType -> LayoutElementType
>= :: LayoutElementType -> LayoutElementType -> Bool
$c>= :: LayoutElementType -> LayoutElementType -> Bool
> :: LayoutElementType -> LayoutElementType -> Bool
$c> :: LayoutElementType -> LayoutElementType -> Bool
<= :: LayoutElementType -> LayoutElementType -> Bool
$c<= :: LayoutElementType -> LayoutElementType -> Bool
< :: LayoutElementType -> LayoutElementType -> Bool
$c< :: LayoutElementType -> LayoutElementType -> Bool
compare :: LayoutElementType -> LayoutElementType -> Ordering
$ccompare :: LayoutElementType -> LayoutElementType -> Ordering
Prelude.Ord,
      forall x. Rep LayoutElementType x -> LayoutElementType
forall x. LayoutElementType -> Rep LayoutElementType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LayoutElementType x -> LayoutElementType
$cfrom :: forall x. LayoutElementType -> Rep LayoutElementType x
Prelude.Generic
    )
  deriving newtype
    ( Eq LayoutElementType
Int -> LayoutElementType -> Int
LayoutElementType -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: LayoutElementType -> Int
$chash :: LayoutElementType -> Int
hashWithSalt :: Int -> LayoutElementType -> Int
$chashWithSalt :: Int -> LayoutElementType -> Int
Prelude.Hashable,
      LayoutElementType -> ()
forall a. (a -> ()) -> NFData a
rnf :: LayoutElementType -> ()
$crnf :: LayoutElementType -> ()
Prelude.NFData,
      Text -> Either String LayoutElementType
forall a. (Text -> Either String a) -> FromText a
fromText :: Text -> Either String LayoutElementType
$cfromText :: Text -> Either String LayoutElementType
Data.FromText,
      LayoutElementType -> Text
forall a. (a -> Text) -> ToText a
toText :: LayoutElementType -> Text
$ctoText :: LayoutElementType -> Text
Data.ToText,
      LayoutElementType -> ByteString
forall a. (a -> ByteString) -> ToByteString a
toBS :: LayoutElementType -> ByteString
$ctoBS :: LayoutElementType -> ByteString
Data.ToByteString,
      LayoutElementType -> ByteStringBuilder
forall a. (a -> ByteStringBuilder) -> ToLog a
build :: LayoutElementType -> ByteStringBuilder
$cbuild :: LayoutElementType -> ByteStringBuilder
Data.ToLog,
      HeaderName -> LayoutElementType -> [Header]
forall a. (HeaderName -> a -> [Header]) -> ToHeader a
toHeader :: HeaderName -> LayoutElementType -> [Header]
$ctoHeader :: HeaderName -> LayoutElementType -> [Header]
Data.ToHeader,
      LayoutElementType -> QueryString
forall a. (a -> QueryString) -> ToQuery a
toQuery :: LayoutElementType -> QueryString
$ctoQuery :: LayoutElementType -> QueryString
Data.ToQuery,
      Value -> Parser [LayoutElementType]
Value -> Parser LayoutElementType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [LayoutElementType]
$cparseJSONList :: Value -> Parser [LayoutElementType]
parseJSON :: Value -> Parser LayoutElementType
$cparseJSON :: Value -> Parser LayoutElementType
Data.FromJSON,
      FromJSONKeyFunction [LayoutElementType]
FromJSONKeyFunction LayoutElementType
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [LayoutElementType]
$cfromJSONKeyList :: FromJSONKeyFunction [LayoutElementType]
fromJSONKey :: FromJSONKeyFunction LayoutElementType
$cfromJSONKey :: FromJSONKeyFunction LayoutElementType
Data.FromJSONKey,
      [LayoutElementType] -> Encoding
[LayoutElementType] -> Value
LayoutElementType -> Encoding
LayoutElementType -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [LayoutElementType] -> Encoding
$ctoEncodingList :: [LayoutElementType] -> Encoding
toJSONList :: [LayoutElementType] -> Value
$ctoJSONList :: [LayoutElementType] -> Value
toEncoding :: LayoutElementType -> Encoding
$ctoEncoding :: LayoutElementType -> Encoding
toJSON :: LayoutElementType -> Value
$ctoJSON :: LayoutElementType -> Value
Data.ToJSON,
      ToJSONKeyFunction [LayoutElementType]
ToJSONKeyFunction LayoutElementType
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [LayoutElementType]
$ctoJSONKeyList :: ToJSONKeyFunction [LayoutElementType]
toJSONKey :: ToJSONKeyFunction LayoutElementType
$ctoJSONKey :: ToJSONKeyFunction LayoutElementType
Data.ToJSONKey,
      [Node] -> Either String LayoutElementType
forall a. ([Node] -> Either String a) -> FromXML a
parseXML :: [Node] -> Either String LayoutElementType
$cparseXML :: [Node] -> Either String LayoutElementType
Data.FromXML,
      LayoutElementType -> XML
forall a. (a -> XML) -> ToXML a
toXML :: LayoutElementType -> XML
$ctoXML :: LayoutElementType -> XML
Data.ToXML
    )

pattern LayoutElementType_FILTER_CONTROL :: LayoutElementType
pattern $bLayoutElementType_FILTER_CONTROL :: LayoutElementType
$mLayoutElementType_FILTER_CONTROL :: forall {r}. LayoutElementType -> ((# #) -> r) -> ((# #) -> r) -> r
LayoutElementType_FILTER_CONTROL = LayoutElementType' "FILTER_CONTROL"

pattern LayoutElementType_PARAMETER_CONTROL :: LayoutElementType
pattern $bLayoutElementType_PARAMETER_CONTROL :: LayoutElementType
$mLayoutElementType_PARAMETER_CONTROL :: forall {r}. LayoutElementType -> ((# #) -> r) -> ((# #) -> r) -> r
LayoutElementType_PARAMETER_CONTROL = LayoutElementType' "PARAMETER_CONTROL"

pattern LayoutElementType_TEXT_BOX :: LayoutElementType
pattern $bLayoutElementType_TEXT_BOX :: LayoutElementType
$mLayoutElementType_TEXT_BOX :: forall {r}. LayoutElementType -> ((# #) -> r) -> ((# #) -> r) -> r
LayoutElementType_TEXT_BOX = LayoutElementType' "TEXT_BOX"

pattern LayoutElementType_VISUAL :: LayoutElementType
pattern $bLayoutElementType_VISUAL :: LayoutElementType
$mLayoutElementType_VISUAL :: forall {r}. LayoutElementType -> ((# #) -> r) -> ((# #) -> r) -> r
LayoutElementType_VISUAL = LayoutElementType' "VISUAL"

{-# COMPLETE
  LayoutElementType_FILTER_CONTROL,
  LayoutElementType_PARAMETER_CONTROL,
  LayoutElementType_TEXT_BOX,
  LayoutElementType_VISUAL,
  LayoutElementType'
  #-}