{-# 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.GetSequenceStore
-- 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 sequence store.
module Amazonka.Omics.GetSequenceStore
  ( -- * Creating a Request
    GetSequenceStore (..),
    newGetSequenceStore,

    -- * Request Lenses
    getSequenceStore_id,

    -- * Destructuring the Response
    GetSequenceStoreResponse (..),
    newGetSequenceStoreResponse,

    -- * Response Lenses
    getSequenceStoreResponse_description,
    getSequenceStoreResponse_name,
    getSequenceStoreResponse_sseConfig,
    getSequenceStoreResponse_httpStatus,
    getSequenceStoreResponse_arn,
    getSequenceStoreResponse_creationTime,
    getSequenceStoreResponse_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:/ 'newGetSequenceStore' smart constructor.
data GetSequenceStore = GetSequenceStore'
  { -- | The store\'s ID.
    GetSequenceStore -> Text
id :: Prelude.Text
  }
  deriving (GetSequenceStore -> GetSequenceStore -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSequenceStore -> GetSequenceStore -> Bool
$c/= :: GetSequenceStore -> GetSequenceStore -> Bool
== :: GetSequenceStore -> GetSequenceStore -> Bool
$c== :: GetSequenceStore -> GetSequenceStore -> Bool
Prelude.Eq, ReadPrec [GetSequenceStore]
ReadPrec GetSequenceStore
Int -> ReadS GetSequenceStore
ReadS [GetSequenceStore]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSequenceStore]
$creadListPrec :: ReadPrec [GetSequenceStore]
readPrec :: ReadPrec GetSequenceStore
$creadPrec :: ReadPrec GetSequenceStore
readList :: ReadS [GetSequenceStore]
$creadList :: ReadS [GetSequenceStore]
readsPrec :: Int -> ReadS GetSequenceStore
$creadsPrec :: Int -> ReadS GetSequenceStore
Prelude.Read, Int -> GetSequenceStore -> ShowS
[GetSequenceStore] -> ShowS
GetSequenceStore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSequenceStore] -> ShowS
$cshowList :: [GetSequenceStore] -> ShowS
show :: GetSequenceStore -> String
$cshow :: GetSequenceStore -> String
showsPrec :: Int -> GetSequenceStore -> ShowS
$cshowsPrec :: Int -> GetSequenceStore -> ShowS
Prelude.Show, forall x. Rep GetSequenceStore x -> GetSequenceStore
forall x. GetSequenceStore -> Rep GetSequenceStore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSequenceStore x -> GetSequenceStore
$cfrom :: forall x. GetSequenceStore -> Rep GetSequenceStore x
Prelude.Generic)

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

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

instance Core.AWSRequest GetSequenceStore where
  type
    AWSResponse GetSequenceStore =
      GetSequenceStoreResponse
  request :: (Service -> Service)
-> GetSequenceStore -> Request GetSequenceStore
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 GetSequenceStore
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSequenceStore)))
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
-> GetSequenceStoreResponse
GetSequenceStoreResponse'
            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 GetSequenceStore where
  hashWithSalt :: Int -> GetSequenceStore -> Int
hashWithSalt Int
_salt GetSequenceStore' {Text
id :: Text
$sel:id:GetSequenceStore' :: GetSequenceStore -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

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

instance Data.ToHeaders GetSequenceStore where
  toHeaders :: GetSequenceStore -> 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 GetSequenceStore where
  toPath :: GetSequenceStore -> ByteString
toPath GetSequenceStore' {Text
id :: Text
$sel:id:GetSequenceStore' :: GetSequenceStore -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/sequencestore/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

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

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

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

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

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

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

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

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

instance Prelude.NFData GetSequenceStoreResponse where
  rnf :: GetSequenceStoreResponse -> ()
rnf GetSequenceStoreResponse' {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:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> Text
$sel:creationTime:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> ISO8601
$sel:arn:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> Text
$sel:httpStatus:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> Int
$sel:sseConfig:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> Maybe SseConfig
$sel:name:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> Maybe Text
$sel:description:GetSequenceStoreResponse' :: GetSequenceStoreResponse -> 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