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

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

-- |
-- Module      : Amazonka.Omics.GetReferenceStore
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about a reference store.
module Amazonka.Omics.GetReferenceStore
  ( -- * Creating a Request
    GetReferenceStore (..),
    newGetReferenceStore,

    -- * Request Lenses
    getReferenceStore_id,

    -- * Destructuring the Response
    GetReferenceStoreResponse (..),
    newGetReferenceStoreResponse,

    -- * Response Lenses
    getReferenceStoreResponse_description,
    getReferenceStoreResponse_name,
    getReferenceStoreResponse_sseConfig,
    getReferenceStoreResponse_httpStatus,
    getReferenceStoreResponse_arn,
    getReferenceStoreResponse_creationTime,
    getReferenceStoreResponse_id,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Omics.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetReferenceStore' smart constructor.
data GetReferenceStore = GetReferenceStore'
  { -- | The store\'s ID.
    GetReferenceStore -> Text
id :: Prelude.Text
  }
  deriving (GetReferenceStore -> GetReferenceStore -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReferenceStore -> GetReferenceStore -> Bool
$c/= :: GetReferenceStore -> GetReferenceStore -> Bool
== :: GetReferenceStore -> GetReferenceStore -> Bool
$c== :: GetReferenceStore -> GetReferenceStore -> Bool
Prelude.Eq, ReadPrec [GetReferenceStore]
ReadPrec GetReferenceStore
Int -> ReadS GetReferenceStore
ReadS [GetReferenceStore]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReferenceStore]
$creadListPrec :: ReadPrec [GetReferenceStore]
readPrec :: ReadPrec GetReferenceStore
$creadPrec :: ReadPrec GetReferenceStore
readList :: ReadS [GetReferenceStore]
$creadList :: ReadS [GetReferenceStore]
readsPrec :: Int -> ReadS GetReferenceStore
$creadsPrec :: Int -> ReadS GetReferenceStore
Prelude.Read, Int -> GetReferenceStore -> ShowS
[GetReferenceStore] -> ShowS
GetReferenceStore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReferenceStore] -> ShowS
$cshowList :: [GetReferenceStore] -> ShowS
show :: GetReferenceStore -> String
$cshow :: GetReferenceStore -> String
showsPrec :: Int -> GetReferenceStore -> ShowS
$cshowsPrec :: Int -> GetReferenceStore -> ShowS
Prelude.Show, forall x. Rep GetReferenceStore x -> GetReferenceStore
forall x. GetReferenceStore -> Rep GetReferenceStore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetReferenceStore x -> GetReferenceStore
$cfrom :: forall x. GetReferenceStore -> Rep GetReferenceStore x
Prelude.Generic)

-- |
-- Create a value of 'GetReferenceStore' 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:
--
-- 'id', 'getReferenceStore_id' - The store\'s ID.
newGetReferenceStore ::
  -- | 'id'
  Prelude.Text ->
  GetReferenceStore
newGetReferenceStore :: Text -> GetReferenceStore
newGetReferenceStore Text
pId_ =
  GetReferenceStore' {$sel:id:GetReferenceStore' :: Text
id = Text
pId_}

-- | The store\'s ID.
getReferenceStore_id :: Lens.Lens' GetReferenceStore Prelude.Text
getReferenceStore_id :: Lens' GetReferenceStore Text
getReferenceStore_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStore' {Text
id :: Text
$sel:id:GetReferenceStore' :: GetReferenceStore -> Text
id} -> Text
id) (\s :: GetReferenceStore
s@GetReferenceStore' {} Text
a -> GetReferenceStore
s {$sel:id:GetReferenceStore' :: Text
id = Text
a} :: GetReferenceStore)

instance Core.AWSRequest GetReferenceStore where
  type
    AWSResponse GetReferenceStore =
      GetReferenceStoreResponse
  request :: (Service -> Service)
-> GetReferenceStore -> Request GetReferenceStore
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetReferenceStore
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetReferenceStore)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe SseConfig
-> Int
-> Text
-> ISO8601
-> Text
-> GetReferenceStoreResponse
GetReferenceStoreResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"sseConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"creationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"id")
      )

instance Prelude.Hashable GetReferenceStore where
  hashWithSalt :: Int -> GetReferenceStore -> Int
hashWithSalt Int
_salt GetReferenceStore' {Text
id :: Text
$sel:id:GetReferenceStore' :: GetReferenceStore -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData GetReferenceStore where
  rnf :: GetReferenceStore -> ()
rnf GetReferenceStore' {Text
id :: Text
$sel:id:GetReferenceStore' :: GetReferenceStore -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders GetReferenceStore where
  toHeaders :: GetReferenceStore -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetReferenceStore where
  toPath :: GetReferenceStore -> ByteString
toPath GetReferenceStore' {Text
id :: Text
$sel:id:GetReferenceStore' :: GetReferenceStore -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/referencestore/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

instance Data.ToQuery GetReferenceStore where
  toQuery :: GetReferenceStore -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetReferenceStoreResponse' smart constructor.
data GetReferenceStoreResponse = GetReferenceStoreResponse'
  { -- | The store\'s description.
    GetReferenceStoreResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The store\'s name.
    GetReferenceStoreResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The store\'s server-side encryption (SSE) settings.
    GetReferenceStoreResponse -> Maybe SseConfig
sseConfig :: Prelude.Maybe SseConfig,
    -- | The response's http status code.
    GetReferenceStoreResponse -> Int
httpStatus :: Prelude.Int,
    -- | The store\'s ARN.
    GetReferenceStoreResponse -> Text
arn :: Prelude.Text,
    -- | When the store was created.
    GetReferenceStoreResponse -> ISO8601
creationTime :: Data.ISO8601,
    -- | The store\'s ID.
    GetReferenceStoreResponse -> Text
id :: Prelude.Text
  }
  deriving (GetReferenceStoreResponse -> GetReferenceStoreResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReferenceStoreResponse -> GetReferenceStoreResponse -> Bool
$c/= :: GetReferenceStoreResponse -> GetReferenceStoreResponse -> Bool
== :: GetReferenceStoreResponse -> GetReferenceStoreResponse -> Bool
$c== :: GetReferenceStoreResponse -> GetReferenceStoreResponse -> Bool
Prelude.Eq, ReadPrec [GetReferenceStoreResponse]
ReadPrec GetReferenceStoreResponse
Int -> ReadS GetReferenceStoreResponse
ReadS [GetReferenceStoreResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReferenceStoreResponse]
$creadListPrec :: ReadPrec [GetReferenceStoreResponse]
readPrec :: ReadPrec GetReferenceStoreResponse
$creadPrec :: ReadPrec GetReferenceStoreResponse
readList :: ReadS [GetReferenceStoreResponse]
$creadList :: ReadS [GetReferenceStoreResponse]
readsPrec :: Int -> ReadS GetReferenceStoreResponse
$creadsPrec :: Int -> ReadS GetReferenceStoreResponse
Prelude.Read, Int -> GetReferenceStoreResponse -> ShowS
[GetReferenceStoreResponse] -> ShowS
GetReferenceStoreResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReferenceStoreResponse] -> ShowS
$cshowList :: [GetReferenceStoreResponse] -> ShowS
show :: GetReferenceStoreResponse -> String
$cshow :: GetReferenceStoreResponse -> String
showsPrec :: Int -> GetReferenceStoreResponse -> ShowS
$cshowsPrec :: Int -> GetReferenceStoreResponse -> ShowS
Prelude.Show, forall x.
Rep GetReferenceStoreResponse x -> GetReferenceStoreResponse
forall x.
GetReferenceStoreResponse -> Rep GetReferenceStoreResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetReferenceStoreResponse x -> GetReferenceStoreResponse
$cfrom :: forall x.
GetReferenceStoreResponse -> Rep GetReferenceStoreResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetReferenceStoreResponse' 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:
--
-- 'description', 'getReferenceStoreResponse_description' - The store\'s description.
--
-- 'name', 'getReferenceStoreResponse_name' - The store\'s name.
--
-- 'sseConfig', 'getReferenceStoreResponse_sseConfig' - The store\'s server-side encryption (SSE) settings.
--
-- 'httpStatus', 'getReferenceStoreResponse_httpStatus' - The response's http status code.
--
-- 'arn', 'getReferenceStoreResponse_arn' - The store\'s ARN.
--
-- 'creationTime', 'getReferenceStoreResponse_creationTime' - When the store was created.
--
-- 'id', 'getReferenceStoreResponse_id' - The store\'s ID.
newGetReferenceStoreResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'id'
  Prelude.Text ->
  GetReferenceStoreResponse
newGetReferenceStoreResponse :: Int -> Text -> UTCTime -> Text -> GetReferenceStoreResponse
newGetReferenceStoreResponse
  Int
pHttpStatus_
  Text
pArn_
  UTCTime
pCreationTime_
  Text
pId_ =
    GetReferenceStoreResponse'
      { $sel:description:GetReferenceStoreResponse' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:name:GetReferenceStoreResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:sseConfig:GetReferenceStoreResponse' :: Maybe SseConfig
sseConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetReferenceStoreResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:arn:GetReferenceStoreResponse' :: Text
arn = Text
pArn_,
        $sel:creationTime:GetReferenceStoreResponse' :: ISO8601
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:id:GetReferenceStoreResponse' :: Text
id = Text
pId_
      }

-- | The store\'s description.
getReferenceStoreResponse_description :: Lens.Lens' GetReferenceStoreResponse (Prelude.Maybe Prelude.Text)
getReferenceStoreResponse_description :: Lens' GetReferenceStoreResponse (Maybe Text)
getReferenceStoreResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} Maybe Text
a -> GetReferenceStoreResponse
s {$sel:description:GetReferenceStoreResponse' :: Maybe Text
description = Maybe Text
a} :: GetReferenceStoreResponse)

-- | The store\'s name.
getReferenceStoreResponse_name :: Lens.Lens' GetReferenceStoreResponse (Prelude.Maybe Prelude.Text)
getReferenceStoreResponse_name :: Lens' GetReferenceStoreResponse (Maybe Text)
getReferenceStoreResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} Maybe Text
a -> GetReferenceStoreResponse
s {$sel:name:GetReferenceStoreResponse' :: Maybe Text
name = Maybe Text
a} :: GetReferenceStoreResponse)

-- | The store\'s server-side encryption (SSE) settings.
getReferenceStoreResponse_sseConfig :: Lens.Lens' GetReferenceStoreResponse (Prelude.Maybe SseConfig)
getReferenceStoreResponse_sseConfig :: Lens' GetReferenceStoreResponse (Maybe SseConfig)
getReferenceStoreResponse_sseConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {Maybe SseConfig
sseConfig :: Maybe SseConfig
$sel:sseConfig:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Maybe SseConfig
sseConfig} -> Maybe SseConfig
sseConfig) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} Maybe SseConfig
a -> GetReferenceStoreResponse
s {$sel:sseConfig:GetReferenceStoreResponse' :: Maybe SseConfig
sseConfig = Maybe SseConfig
a} :: GetReferenceStoreResponse)

-- | The response's http status code.
getReferenceStoreResponse_httpStatus :: Lens.Lens' GetReferenceStoreResponse Prelude.Int
getReferenceStoreResponse_httpStatus :: Lens' GetReferenceStoreResponse Int
getReferenceStoreResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} Int
a -> GetReferenceStoreResponse
s {$sel:httpStatus:GetReferenceStoreResponse' :: Int
httpStatus = Int
a} :: GetReferenceStoreResponse)

-- | The store\'s ARN.
getReferenceStoreResponse_arn :: Lens.Lens' GetReferenceStoreResponse Prelude.Text
getReferenceStoreResponse_arn :: Lens' GetReferenceStoreResponse Text
getReferenceStoreResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {Text
arn :: Text
$sel:arn:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Text
arn} -> Text
arn) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} Text
a -> GetReferenceStoreResponse
s {$sel:arn:GetReferenceStoreResponse' :: Text
arn = Text
a} :: GetReferenceStoreResponse)

-- | When the store was created.
getReferenceStoreResponse_creationTime :: Lens.Lens' GetReferenceStoreResponse Prelude.UTCTime
getReferenceStoreResponse_creationTime :: Lens' GetReferenceStoreResponse UTCTime
getReferenceStoreResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {ISO8601
creationTime :: ISO8601
$sel:creationTime:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> ISO8601
creationTime} -> ISO8601
creationTime) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} ISO8601
a -> GetReferenceStoreResponse
s {$sel:creationTime:GetReferenceStoreResponse' :: ISO8601
creationTime = ISO8601
a} :: GetReferenceStoreResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The store\'s ID.
getReferenceStoreResponse_id :: Lens.Lens' GetReferenceStoreResponse Prelude.Text
getReferenceStoreResponse_id :: Lens' GetReferenceStoreResponse Text
getReferenceStoreResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReferenceStoreResponse' {Text
id :: Text
$sel:id:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Text
id} -> Text
id) (\s :: GetReferenceStoreResponse
s@GetReferenceStoreResponse' {} Text
a -> GetReferenceStoreResponse
s {$sel:id:GetReferenceStoreResponse' :: Text
id = Text
a} :: GetReferenceStoreResponse)

instance Prelude.NFData GetReferenceStoreResponse where
  rnf :: GetReferenceStoreResponse -> ()
rnf GetReferenceStoreResponse' {Int
Maybe Text
Maybe SseConfig
Text
ISO8601
id :: Text
creationTime :: ISO8601
arn :: Text
httpStatus :: Int
sseConfig :: Maybe SseConfig
name :: Maybe Text
description :: Maybe Text
$sel:id:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Text
$sel:creationTime:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> ISO8601
$sel:arn:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Text
$sel:httpStatus:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Int
$sel:sseConfig:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Maybe SseConfig
$sel:name:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Maybe Text
$sel:description:GetReferenceStoreResponse' :: GetReferenceStoreResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SseConfig
sseConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id