{-# 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.Omics.Types.TsvStoreOptions
-- 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.Omics.Types.TsvStoreOptions 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.AnnotationType
import Amazonka.Omics.Types.FormatToHeaderKey
import Amazonka.Omics.Types.SchemaValueType
import qualified Amazonka.Prelude as Prelude

-- | File settings for a TSV store.
--
-- /See:/ 'newTsvStoreOptions' smart constructor.
data TsvStoreOptions = TsvStoreOptions'
  { -- | The store\'s annotation type.
    TsvStoreOptions -> Maybe AnnotationType
annotationType :: Prelude.Maybe AnnotationType,
    -- | The store\'s header key to column name mapping.
    TsvStoreOptions -> Maybe (HashMap FormatToHeaderKey Text)
formatToHeader :: Prelude.Maybe (Prelude.HashMap FormatToHeaderKey Prelude.Text),
    -- | The store\'s schema.
    TsvStoreOptions -> Maybe (NonEmpty (HashMap Text SchemaValueType))
schema :: Prelude.Maybe (Prelude.NonEmpty (Prelude.HashMap Prelude.Text SchemaValueType))
  }
  deriving (TsvStoreOptions -> TsvStoreOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TsvStoreOptions -> TsvStoreOptions -> Bool
$c/= :: TsvStoreOptions -> TsvStoreOptions -> Bool
== :: TsvStoreOptions -> TsvStoreOptions -> Bool
$c== :: TsvStoreOptions -> TsvStoreOptions -> Bool
Prelude.Eq, ReadPrec [TsvStoreOptions]
ReadPrec TsvStoreOptions
Int -> ReadS TsvStoreOptions
ReadS [TsvStoreOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TsvStoreOptions]
$creadListPrec :: ReadPrec [TsvStoreOptions]
readPrec :: ReadPrec TsvStoreOptions
$creadPrec :: ReadPrec TsvStoreOptions
readList :: ReadS [TsvStoreOptions]
$creadList :: ReadS [TsvStoreOptions]
readsPrec :: Int -> ReadS TsvStoreOptions
$creadsPrec :: Int -> ReadS TsvStoreOptions
Prelude.Read, Int -> TsvStoreOptions -> ShowS
[TsvStoreOptions] -> ShowS
TsvStoreOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TsvStoreOptions] -> ShowS
$cshowList :: [TsvStoreOptions] -> ShowS
show :: TsvStoreOptions -> String
$cshow :: TsvStoreOptions -> String
showsPrec :: Int -> TsvStoreOptions -> ShowS
$cshowsPrec :: Int -> TsvStoreOptions -> ShowS
Prelude.Show, forall x. Rep TsvStoreOptions x -> TsvStoreOptions
forall x. TsvStoreOptions -> Rep TsvStoreOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TsvStoreOptions x -> TsvStoreOptions
$cfrom :: forall x. TsvStoreOptions -> Rep TsvStoreOptions x
Prelude.Generic)

-- |
-- Create a value of 'TsvStoreOptions' 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:
--
-- 'annotationType', 'tsvStoreOptions_annotationType' - The store\'s annotation type.
--
-- 'formatToHeader', 'tsvStoreOptions_formatToHeader' - The store\'s header key to column name mapping.
--
-- 'schema', 'tsvStoreOptions_schema' - The store\'s schema.
newTsvStoreOptions ::
  TsvStoreOptions
newTsvStoreOptions :: TsvStoreOptions
newTsvStoreOptions =
  TsvStoreOptions'
    { $sel:annotationType:TsvStoreOptions' :: Maybe AnnotationType
annotationType = forall a. Maybe a
Prelude.Nothing,
      $sel:formatToHeader:TsvStoreOptions' :: Maybe (HashMap FormatToHeaderKey Text)
formatToHeader = forall a. Maybe a
Prelude.Nothing,
      $sel:schema:TsvStoreOptions' :: Maybe (NonEmpty (HashMap Text SchemaValueType))
schema = forall a. Maybe a
Prelude.Nothing
    }

-- | The store\'s annotation type.
tsvStoreOptions_annotationType :: Lens.Lens' TsvStoreOptions (Prelude.Maybe AnnotationType)
tsvStoreOptions_annotationType :: Lens' TsvStoreOptions (Maybe AnnotationType)
tsvStoreOptions_annotationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TsvStoreOptions' {Maybe AnnotationType
annotationType :: Maybe AnnotationType
$sel:annotationType:TsvStoreOptions' :: TsvStoreOptions -> Maybe AnnotationType
annotationType} -> Maybe AnnotationType
annotationType) (\s :: TsvStoreOptions
s@TsvStoreOptions' {} Maybe AnnotationType
a -> TsvStoreOptions
s {$sel:annotationType:TsvStoreOptions' :: Maybe AnnotationType
annotationType = Maybe AnnotationType
a} :: TsvStoreOptions)

-- | The store\'s header key to column name mapping.
tsvStoreOptions_formatToHeader :: Lens.Lens' TsvStoreOptions (Prelude.Maybe (Prelude.HashMap FormatToHeaderKey Prelude.Text))
tsvStoreOptions_formatToHeader :: Lens' TsvStoreOptions (Maybe (HashMap FormatToHeaderKey Text))
tsvStoreOptions_formatToHeader = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TsvStoreOptions' {Maybe (HashMap FormatToHeaderKey Text)
formatToHeader :: Maybe (HashMap FormatToHeaderKey Text)
$sel:formatToHeader:TsvStoreOptions' :: TsvStoreOptions -> Maybe (HashMap FormatToHeaderKey Text)
formatToHeader} -> Maybe (HashMap FormatToHeaderKey Text)
formatToHeader) (\s :: TsvStoreOptions
s@TsvStoreOptions' {} Maybe (HashMap FormatToHeaderKey Text)
a -> TsvStoreOptions
s {$sel:formatToHeader:TsvStoreOptions' :: Maybe (HashMap FormatToHeaderKey Text)
formatToHeader = Maybe (HashMap FormatToHeaderKey Text)
a} :: TsvStoreOptions) 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 store\'s schema.
tsvStoreOptions_schema :: Lens.Lens' TsvStoreOptions (Prelude.Maybe (Prelude.NonEmpty (Prelude.HashMap Prelude.Text SchemaValueType)))
tsvStoreOptions_schema :: Lens'
  TsvStoreOptions (Maybe (NonEmpty (HashMap Text SchemaValueType)))
tsvStoreOptions_schema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TsvStoreOptions' {Maybe (NonEmpty (HashMap Text SchemaValueType))
schema :: Maybe (NonEmpty (HashMap Text SchemaValueType))
$sel:schema:TsvStoreOptions' :: TsvStoreOptions -> Maybe (NonEmpty (HashMap Text SchemaValueType))
schema} -> Maybe (NonEmpty (HashMap Text SchemaValueType))
schema) (\s :: TsvStoreOptions
s@TsvStoreOptions' {} Maybe (NonEmpty (HashMap Text SchemaValueType))
a -> TsvStoreOptions
s {$sel:schema:TsvStoreOptions' :: Maybe (NonEmpty (HashMap Text SchemaValueType))
schema = Maybe (NonEmpty (HashMap Text SchemaValueType))
a} :: TsvStoreOptions) 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

instance Data.FromJSON TsvStoreOptions where
  parseJSON :: Value -> Parser TsvStoreOptions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TsvStoreOptions"
      ( \Object
x ->
          Maybe AnnotationType
-> Maybe (HashMap FormatToHeaderKey Text)
-> Maybe (NonEmpty (HashMap Text SchemaValueType))
-> TsvStoreOptions
TsvStoreOptions'
            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
"annotationType")
            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
"formatToHeader" 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
"schema")
      )

instance Prelude.Hashable TsvStoreOptions where
  hashWithSalt :: Int -> TsvStoreOptions -> Int
hashWithSalt Int
_salt TsvStoreOptions' {Maybe (NonEmpty (HashMap Text SchemaValueType))
Maybe (HashMap FormatToHeaderKey Text)
Maybe AnnotationType
schema :: Maybe (NonEmpty (HashMap Text SchemaValueType))
formatToHeader :: Maybe (HashMap FormatToHeaderKey Text)
annotationType :: Maybe AnnotationType
$sel:schema:TsvStoreOptions' :: TsvStoreOptions -> Maybe (NonEmpty (HashMap Text SchemaValueType))
$sel:formatToHeader:TsvStoreOptions' :: TsvStoreOptions -> Maybe (HashMap FormatToHeaderKey Text)
$sel:annotationType:TsvStoreOptions' :: TsvStoreOptions -> Maybe AnnotationType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnnotationType
annotationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap FormatToHeaderKey Text)
formatToHeader
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty (HashMap Text SchemaValueType))
schema

instance Prelude.NFData TsvStoreOptions where
  rnf :: TsvStoreOptions -> ()
rnf TsvStoreOptions' {Maybe (NonEmpty (HashMap Text SchemaValueType))
Maybe (HashMap FormatToHeaderKey Text)
Maybe AnnotationType
schema :: Maybe (NonEmpty (HashMap Text SchemaValueType))
formatToHeader :: Maybe (HashMap FormatToHeaderKey Text)
annotationType :: Maybe AnnotationType
$sel:schema:TsvStoreOptions' :: TsvStoreOptions -> Maybe (NonEmpty (HashMap Text SchemaValueType))
$sel:formatToHeader:TsvStoreOptions' :: TsvStoreOptions -> Maybe (HashMap FormatToHeaderKey Text)
$sel:annotationType:TsvStoreOptions' :: TsvStoreOptions -> Maybe AnnotationType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AnnotationType
annotationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap FormatToHeaderKey Text)
formatToHeader
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty (HashMap Text SchemaValueType))
schema

instance Data.ToJSON TsvStoreOptions where
  toJSON :: TsvStoreOptions -> Value
toJSON TsvStoreOptions' {Maybe (NonEmpty (HashMap Text SchemaValueType))
Maybe (HashMap FormatToHeaderKey Text)
Maybe AnnotationType
schema :: Maybe (NonEmpty (HashMap Text SchemaValueType))
formatToHeader :: Maybe (HashMap FormatToHeaderKey Text)
annotationType :: Maybe AnnotationType
$sel:schema:TsvStoreOptions' :: TsvStoreOptions -> Maybe (NonEmpty (HashMap Text SchemaValueType))
$sel:formatToHeader:TsvStoreOptions' :: TsvStoreOptions -> Maybe (HashMap FormatToHeaderKey Text)
$sel:annotationType:TsvStoreOptions' :: TsvStoreOptions -> Maybe AnnotationType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"annotationType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AnnotationType
annotationType,
            (Key
"formatToHeader" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap FormatToHeaderKey Text)
formatToHeader,
            (Key
"schema" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty (HashMap Text SchemaValueType))
schema
          ]
      )