{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

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

-- |
-- Module      : Amazonka.HoneyCode.Types.Cell
-- 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.HoneyCode.Types.Cell where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.HoneyCode.Types.Format
import qualified Amazonka.Prelude as Prelude

-- | An object that represents a single cell in a table.
--
-- /See:/ 'newCell' smart constructor.
data Cell = Cell'
  { -- | The format of the cell. If this field is empty, then the format is
    -- either not specified in the workbook or the format is set to AUTO.
    Cell -> Maybe Format
format :: Prelude.Maybe Format,
    -- | The formatted value of the cell. This is the value that you see
    -- displayed in the cell in the UI.
    --
    -- Note that the formatted value of a cell is always represented as a
    -- string irrespective of the data that is stored in the cell. For example,
    -- if a cell contains a date, the formatted value of the cell is the string
    -- representation of the formatted date being shown in the cell in the UI.
    -- See details in the rawValue field below for how cells of different
    -- formats will have different raw and formatted values.
    Cell -> Maybe Text
formattedValue :: Prelude.Maybe Prelude.Text,
    -- | A list of formatted values of the cell. This field is only returned when
    -- the cell is ROWSET format (aka multi-select or multi-record picklist).
    -- Values in the list are always represented as strings. The formattedValue
    -- field will be empty if this field is returned.
    Cell -> Maybe [Text]
formattedValues :: Prelude.Maybe [Prelude.Text],
    -- | The formula contained in the cell. This field is empty if a cell does
    -- not have a formula.
    Cell -> Maybe (Sensitive Text)
formula :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The raw value of the data contained in the cell. The raw value depends
    -- on the format of the data in the cell. However the attribute in the API
    -- return value is always a string containing the raw value.
    --
    -- Cells with format DATE, DATE_TIME or TIME have the raw value as a
    -- floating point number where the whole number represents the number of
    -- days since 1\/1\/1900 and the fractional part represents the fraction of
    -- the day since midnight. For example, a cell with date 11\/3\/2020 has
    -- the raw value \"44138\". A cell with the time 9:00 AM has the raw value
    -- \"0.375\" and a cell with date\/time value of 11\/3\/2020 9:00 AM has
    -- the raw value \"44138.375\". Notice that even though the raw value is a
    -- number in all three cases, it is still represented as a string.
    --
    -- Cells with format NUMBER, CURRENCY, PERCENTAGE and ACCOUNTING have the
    -- raw value of the data as the number representing the data being
    -- displayed. For example, the number 1.325 with two decimal places in the
    -- format will have it\'s raw value as \"1.325\" and formatted value as
    -- \"1.33\". A currency value for $10 will have the raw value as \"10\" and
    -- formatted value as \"$10.00\". A value representing 20% with two decimal
    -- places in the format will have its raw value as \"0.2\" and the
    -- formatted value as \"20.00%\". An accounting value of -$25 will have
    -- \"-25\" as the raw value and \"$ (25.00)\" as the formatted value.
    --
    -- Cells with format TEXT will have the raw text as the raw value. For
    -- example, a cell with text \"John Smith\" will have \"John Smith\" as
    -- both the raw value and the formatted value.
    --
    -- Cells with format CONTACT will have the name of the contact as a
    -- formatted value and the email address of the contact as the raw value.
    -- For example, a contact for John Smith will have \"John Smith\" as the
    -- formatted value and \"john.smith\@example.com\" as the raw value.
    --
    -- Cells with format ROWLINK (aka picklist) will have the first column of
    -- the linked row as the formatted value and the row id of the linked row
    -- as the raw value. For example, a cell containing a picklist to a table
    -- that displays task status might have \"Completed\" as the formatted
    -- value and
    -- \"row:dfcefaee-5b37-4355-8f28-40c3e4ff5dd4\/ca432b2f-b8eb-431d-9fb5-cbe0342f9f03\"
    -- as the raw value.
    --
    -- Cells with format ROWSET (aka multi-select or multi-record picklist)
    -- will by default have the first column of each of the linked rows as the
    -- formatted value in the list, and the rowset id of the linked rows as the
    -- raw value. For example, a cell containing a multi-select picklist to a
    -- table that contains items might have \"Item A\", \"Item B\" in the
    -- formatted value list and \"rows:b742c1f4-6cb0-4650-a845-35eb86fcc2bb\/
    -- [fdea123b-8f68-474a-aa8a-5ff87aa333af,6daf41f0-a138-4eee-89da-123086d36ecf]\"
    -- as the raw value.
    --
    -- Cells with format ATTACHMENT will have the name of the attachment as the
    -- formatted value and the attachment id as the raw value. For example, a
    -- cell containing an attachment named \"image.jpeg\" will have
    -- \"image.jpeg\" as the formatted value and
    -- \"attachment:ca432b2f-b8eb-431d-9fb5-cbe0342f9f03\" as the raw value.
    --
    -- Cells with format AUTO or cells without any format that are
    -- auto-detected as one of the formats above will contain the raw and
    -- formatted values as mentioned above, based on the auto-detected formats.
    -- If there is no auto-detected format, the raw and formatted values will
    -- be the same as the data in the cell.
    Cell -> Maybe Text
rawValue :: Prelude.Maybe Prelude.Text
  }
  deriving (Cell -> Cell -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cell -> Cell -> Bool
$c/= :: Cell -> Cell -> Bool
== :: Cell -> Cell -> Bool
$c== :: Cell -> Cell -> Bool
Prelude.Eq, Int -> Cell -> ShowS
[Cell] -> ShowS
Cell -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cell] -> ShowS
$cshowList :: [Cell] -> ShowS
show :: Cell -> String
$cshow :: Cell -> String
showsPrec :: Int -> Cell -> ShowS
$cshowsPrec :: Int -> Cell -> ShowS
Prelude.Show, forall x. Rep Cell x -> Cell
forall x. Cell -> Rep Cell x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Cell x -> Cell
$cfrom :: forall x. Cell -> Rep Cell x
Prelude.Generic)

-- |
-- Create a value of 'Cell' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'format', 'cell_format' - The format of the cell. If this field is empty, then the format is
-- either not specified in the workbook or the format is set to AUTO.
--
-- 'formattedValue', 'cell_formattedValue' - The formatted value of the cell. This is the value that you see
-- displayed in the cell in the UI.
--
-- Note that the formatted value of a cell is always represented as a
-- string irrespective of the data that is stored in the cell. For example,
-- if a cell contains a date, the formatted value of the cell is the string
-- representation of the formatted date being shown in the cell in the UI.
-- See details in the rawValue field below for how cells of different
-- formats will have different raw and formatted values.
--
-- 'formattedValues', 'cell_formattedValues' - A list of formatted values of the cell. This field is only returned when
-- the cell is ROWSET format (aka multi-select or multi-record picklist).
-- Values in the list are always represented as strings. The formattedValue
-- field will be empty if this field is returned.
--
-- 'formula', 'cell_formula' - The formula contained in the cell. This field is empty if a cell does
-- not have a formula.
--
-- 'rawValue', 'cell_rawValue' - The raw value of the data contained in the cell. The raw value depends
-- on the format of the data in the cell. However the attribute in the API
-- return value is always a string containing the raw value.
--
-- Cells with format DATE, DATE_TIME or TIME have the raw value as a
-- floating point number where the whole number represents the number of
-- days since 1\/1\/1900 and the fractional part represents the fraction of
-- the day since midnight. For example, a cell with date 11\/3\/2020 has
-- the raw value \"44138\". A cell with the time 9:00 AM has the raw value
-- \"0.375\" and a cell with date\/time value of 11\/3\/2020 9:00 AM has
-- the raw value \"44138.375\". Notice that even though the raw value is a
-- number in all three cases, it is still represented as a string.
--
-- Cells with format NUMBER, CURRENCY, PERCENTAGE and ACCOUNTING have the
-- raw value of the data as the number representing the data being
-- displayed. For example, the number 1.325 with two decimal places in the
-- format will have it\'s raw value as \"1.325\" and formatted value as
-- \"1.33\". A currency value for $10 will have the raw value as \"10\" and
-- formatted value as \"$10.00\". A value representing 20% with two decimal
-- places in the format will have its raw value as \"0.2\" and the
-- formatted value as \"20.00%\". An accounting value of -$25 will have
-- \"-25\" as the raw value and \"$ (25.00)\" as the formatted value.
--
-- Cells with format TEXT will have the raw text as the raw value. For
-- example, a cell with text \"John Smith\" will have \"John Smith\" as
-- both the raw value and the formatted value.
--
-- Cells with format CONTACT will have the name of the contact as a
-- formatted value and the email address of the contact as the raw value.
-- For example, a contact for John Smith will have \"John Smith\" as the
-- formatted value and \"john.smith\@example.com\" as the raw value.
--
-- Cells with format ROWLINK (aka picklist) will have the first column of
-- the linked row as the formatted value and the row id of the linked row
-- as the raw value. For example, a cell containing a picklist to a table
-- that displays task status might have \"Completed\" as the formatted
-- value and
-- \"row:dfcefaee-5b37-4355-8f28-40c3e4ff5dd4\/ca432b2f-b8eb-431d-9fb5-cbe0342f9f03\"
-- as the raw value.
--
-- Cells with format ROWSET (aka multi-select or multi-record picklist)
-- will by default have the first column of each of the linked rows as the
-- formatted value in the list, and the rowset id of the linked rows as the
-- raw value. For example, a cell containing a multi-select picklist to a
-- table that contains items might have \"Item A\", \"Item B\" in the
-- formatted value list and \"rows:b742c1f4-6cb0-4650-a845-35eb86fcc2bb\/
-- [fdea123b-8f68-474a-aa8a-5ff87aa333af,6daf41f0-a138-4eee-89da-123086d36ecf]\"
-- as the raw value.
--
-- Cells with format ATTACHMENT will have the name of the attachment as the
-- formatted value and the attachment id as the raw value. For example, a
-- cell containing an attachment named \"image.jpeg\" will have
-- \"image.jpeg\" as the formatted value and
-- \"attachment:ca432b2f-b8eb-431d-9fb5-cbe0342f9f03\" as the raw value.
--
-- Cells with format AUTO or cells without any format that are
-- auto-detected as one of the formats above will contain the raw and
-- formatted values as mentioned above, based on the auto-detected formats.
-- If there is no auto-detected format, the raw and formatted values will
-- be the same as the data in the cell.
newCell ::
  Cell
newCell :: Cell
newCell =
  Cell'
    { $sel:format:Cell' :: Maybe Format
format = forall a. Maybe a
Prelude.Nothing,
      $sel:formattedValue:Cell' :: Maybe Text
formattedValue = forall a. Maybe a
Prelude.Nothing,
      $sel:formattedValues:Cell' :: Maybe [Text]
formattedValues = forall a. Maybe a
Prelude.Nothing,
      $sel:formula:Cell' :: Maybe (Sensitive Text)
formula = forall a. Maybe a
Prelude.Nothing,
      $sel:rawValue:Cell' :: Maybe Text
rawValue = forall a. Maybe a
Prelude.Nothing
    }

-- | The format of the cell. If this field is empty, then the format is
-- either not specified in the workbook or the format is set to AUTO.
cell_format :: Lens.Lens' Cell (Prelude.Maybe Format)
cell_format :: Lens' Cell (Maybe Format)
cell_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cell' {Maybe Format
format :: Maybe Format
$sel:format:Cell' :: Cell -> Maybe Format
format} -> Maybe Format
format) (\s :: Cell
s@Cell' {} Maybe Format
a -> Cell
s {$sel:format:Cell' :: Maybe Format
format = Maybe Format
a} :: Cell)

-- | The formatted value of the cell. This is the value that you see
-- displayed in the cell in the UI.
--
-- Note that the formatted value of a cell is always represented as a
-- string irrespective of the data that is stored in the cell. For example,
-- if a cell contains a date, the formatted value of the cell is the string
-- representation of the formatted date being shown in the cell in the UI.
-- See details in the rawValue field below for how cells of different
-- formats will have different raw and formatted values.
cell_formattedValue :: Lens.Lens' Cell (Prelude.Maybe Prelude.Text)
cell_formattedValue :: Lens' Cell (Maybe Text)
cell_formattedValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cell' {Maybe Text
formattedValue :: Maybe Text
$sel:formattedValue:Cell' :: Cell -> Maybe Text
formattedValue} -> Maybe Text
formattedValue) (\s :: Cell
s@Cell' {} Maybe Text
a -> Cell
s {$sel:formattedValue:Cell' :: Maybe Text
formattedValue = Maybe Text
a} :: Cell)

-- | A list of formatted values of the cell. This field is only returned when
-- the cell is ROWSET format (aka multi-select or multi-record picklist).
-- Values in the list are always represented as strings. The formattedValue
-- field will be empty if this field is returned.
cell_formattedValues :: Lens.Lens' Cell (Prelude.Maybe [Prelude.Text])
cell_formattedValues :: Lens' Cell (Maybe [Text])
cell_formattedValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cell' {Maybe [Text]
formattedValues :: Maybe [Text]
$sel:formattedValues:Cell' :: Cell -> Maybe [Text]
formattedValues} -> Maybe [Text]
formattedValues) (\s :: Cell
s@Cell' {} Maybe [Text]
a -> Cell
s {$sel:formattedValues:Cell' :: Maybe [Text]
formattedValues = Maybe [Text]
a} :: Cell) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The formula contained in the cell. This field is empty if a cell does
-- not have a formula.
cell_formula :: Lens.Lens' Cell (Prelude.Maybe Prelude.Text)
cell_formula :: Lens' Cell (Maybe Text)
cell_formula = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cell' {Maybe (Sensitive Text)
formula :: Maybe (Sensitive Text)
$sel:formula:Cell' :: Cell -> Maybe (Sensitive Text)
formula} -> Maybe (Sensitive Text)
formula) (\s :: Cell
s@Cell' {} Maybe (Sensitive Text)
a -> Cell
s {$sel:formula:Cell' :: Maybe (Sensitive Text)
formula = Maybe (Sensitive Text)
a} :: Cell) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The raw value of the data contained in the cell. The raw value depends
-- on the format of the data in the cell. However the attribute in the API
-- return value is always a string containing the raw value.
--
-- Cells with format DATE, DATE_TIME or TIME have the raw value as a
-- floating point number where the whole number represents the number of
-- days since 1\/1\/1900 and the fractional part represents the fraction of
-- the day since midnight. For example, a cell with date 11\/3\/2020 has
-- the raw value \"44138\". A cell with the time 9:00 AM has the raw value
-- \"0.375\" and a cell with date\/time value of 11\/3\/2020 9:00 AM has
-- the raw value \"44138.375\". Notice that even though the raw value is a
-- number in all three cases, it is still represented as a string.
--
-- Cells with format NUMBER, CURRENCY, PERCENTAGE and ACCOUNTING have the
-- raw value of the data as the number representing the data being
-- displayed. For example, the number 1.325 with two decimal places in the
-- format will have it\'s raw value as \"1.325\" and formatted value as
-- \"1.33\". A currency value for $10 will have the raw value as \"10\" and
-- formatted value as \"$10.00\". A value representing 20% with two decimal
-- places in the format will have its raw value as \"0.2\" and the
-- formatted value as \"20.00%\". An accounting value of -$25 will have
-- \"-25\" as the raw value and \"$ (25.00)\" as the formatted value.
--
-- Cells with format TEXT will have the raw text as the raw value. For
-- example, a cell with text \"John Smith\" will have \"John Smith\" as
-- both the raw value and the formatted value.
--
-- Cells with format CONTACT will have the name of the contact as a
-- formatted value and the email address of the contact as the raw value.
-- For example, a contact for John Smith will have \"John Smith\" as the
-- formatted value and \"john.smith\@example.com\" as the raw value.
--
-- Cells with format ROWLINK (aka picklist) will have the first column of
-- the linked row as the formatted value and the row id of the linked row
-- as the raw value. For example, a cell containing a picklist to a table
-- that displays task status might have \"Completed\" as the formatted
-- value and
-- \"row:dfcefaee-5b37-4355-8f28-40c3e4ff5dd4\/ca432b2f-b8eb-431d-9fb5-cbe0342f9f03\"
-- as the raw value.
--
-- Cells with format ROWSET (aka multi-select or multi-record picklist)
-- will by default have the first column of each of the linked rows as the
-- formatted value in the list, and the rowset id of the linked rows as the
-- raw value. For example, a cell containing a multi-select picklist to a
-- table that contains items might have \"Item A\", \"Item B\" in the
-- formatted value list and \"rows:b742c1f4-6cb0-4650-a845-35eb86fcc2bb\/
-- [fdea123b-8f68-474a-aa8a-5ff87aa333af,6daf41f0-a138-4eee-89da-123086d36ecf]\"
-- as the raw value.
--
-- Cells with format ATTACHMENT will have the name of the attachment as the
-- formatted value and the attachment id as the raw value. For example, a
-- cell containing an attachment named \"image.jpeg\" will have
-- \"image.jpeg\" as the formatted value and
-- \"attachment:ca432b2f-b8eb-431d-9fb5-cbe0342f9f03\" as the raw value.
--
-- Cells with format AUTO or cells without any format that are
-- auto-detected as one of the formats above will contain the raw and
-- formatted values as mentioned above, based on the auto-detected formats.
-- If there is no auto-detected format, the raw and formatted values will
-- be the same as the data in the cell.
cell_rawValue :: Lens.Lens' Cell (Prelude.Maybe Prelude.Text)
cell_rawValue :: Lens' Cell (Maybe Text)
cell_rawValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cell' {Maybe Text
rawValue :: Maybe Text
$sel:rawValue:Cell' :: Cell -> Maybe Text
rawValue} -> Maybe Text
rawValue) (\s :: Cell
s@Cell' {} Maybe Text
a -> Cell
s {$sel:rawValue:Cell' :: Maybe Text
rawValue = Maybe Text
a} :: Cell)

instance Data.FromJSON Cell where
  parseJSON :: Value -> Parser Cell
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Cell"
      ( \Object
x ->
          Maybe Format
-> Maybe Text
-> Maybe [Text]
-> Maybe (Sensitive Text)
-> Maybe Text
-> Cell
Cell'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"format")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"formattedValue")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"formattedValues"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"formula")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"rawValue")
      )

instance Prelude.Hashable Cell where
  hashWithSalt :: Int -> Cell -> Int
hashWithSalt Int
_salt Cell' {Maybe [Text]
Maybe Text
Maybe (Sensitive Text)
Maybe Format
rawValue :: Maybe Text
formula :: Maybe (Sensitive Text)
formattedValues :: Maybe [Text]
formattedValue :: Maybe Text
format :: Maybe Format
$sel:rawValue:Cell' :: Cell -> Maybe Text
$sel:formula:Cell' :: Cell -> Maybe (Sensitive Text)
$sel:formattedValues:Cell' :: Cell -> Maybe [Text]
$sel:formattedValue:Cell' :: Cell -> Maybe Text
$sel:format:Cell' :: Cell -> Maybe Format
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Format
format
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
formattedValue
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
formattedValues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
formula
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
rawValue

instance Prelude.NFData Cell where
  rnf :: Cell -> ()
rnf Cell' {Maybe [Text]
Maybe Text
Maybe (Sensitive Text)
Maybe Format
rawValue :: Maybe Text
formula :: Maybe (Sensitive Text)
formattedValues :: Maybe [Text]
formattedValue :: Maybe Text
format :: Maybe Format
$sel:rawValue:Cell' :: Cell -> Maybe Text
$sel:formula:Cell' :: Cell -> Maybe (Sensitive Text)
$sel:formattedValues:Cell' :: Cell -> Maybe [Text]
$sel:formattedValue:Cell' :: Cell -> Maybe Text
$sel:format:Cell' :: Cell -> Maybe Format
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Format
format
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
formattedValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
formattedValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
formula
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
rawValue