{-# 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.S3.Types.ScanRange
-- 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.S3.Types.ScanRange where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.S3.Internal

-- | Specifies the byte range of the object to get the records from. A record
-- is processed when its first byte is contained by the range. This
-- parameter is optional, but when specified, it must not be empty. See RFC
-- 2616, Section 14.35.1 about how to specify the start and end of the
-- range.
--
-- /See:/ 'newScanRange' smart constructor.
data ScanRange = ScanRange'
  { -- | Specifies the end of the byte range. This parameter is optional. Valid
    -- values: non-negative integers. The default value is one less than the
    -- size of the object being queried. If only the End parameter is supplied,
    -- it is interpreted to mean scan the last N bytes of the file. For
    -- example, @\<scanrange>\<end>50\<\/end>\<\/scanrange>@ means scan the
    -- last 50 bytes.
    ScanRange -> Maybe Integer
end :: Prelude.Maybe Prelude.Integer,
    -- | Specifies the start of the byte range. This parameter is optional. Valid
    -- values: non-negative integers. The default value is 0. If only @start@
    -- is supplied, it means scan from that point to the end of the file. For
    -- example, @\<scanrange>\<start>50\<\/start>\<\/scanrange>@ means scan
    -- from byte 50 until the end of the file.
    ScanRange -> Maybe Integer
start :: Prelude.Maybe Prelude.Integer
  }
  deriving (ScanRange -> ScanRange -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScanRange -> ScanRange -> Bool
$c/= :: ScanRange -> ScanRange -> Bool
== :: ScanRange -> ScanRange -> Bool
$c== :: ScanRange -> ScanRange -> Bool
Prelude.Eq, ReadPrec [ScanRange]
ReadPrec ScanRange
Int -> ReadS ScanRange
ReadS [ScanRange]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScanRange]
$creadListPrec :: ReadPrec [ScanRange]
readPrec :: ReadPrec ScanRange
$creadPrec :: ReadPrec ScanRange
readList :: ReadS [ScanRange]
$creadList :: ReadS [ScanRange]
readsPrec :: Int -> ReadS ScanRange
$creadsPrec :: Int -> ReadS ScanRange
Prelude.Read, Int -> ScanRange -> ShowS
[ScanRange] -> ShowS
ScanRange -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScanRange] -> ShowS
$cshowList :: [ScanRange] -> ShowS
show :: ScanRange -> String
$cshow :: ScanRange -> String
showsPrec :: Int -> ScanRange -> ShowS
$cshowsPrec :: Int -> ScanRange -> ShowS
Prelude.Show, forall x. Rep ScanRange x -> ScanRange
forall x. ScanRange -> Rep ScanRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScanRange x -> ScanRange
$cfrom :: forall x. ScanRange -> Rep ScanRange x
Prelude.Generic)

-- |
-- Create a value of 'ScanRange' 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:
--
-- 'end', 'scanRange_end' - Specifies the end of the byte range. This parameter is optional. Valid
-- values: non-negative integers. The default value is one less than the
-- size of the object being queried. If only the End parameter is supplied,
-- it is interpreted to mean scan the last N bytes of the file. For
-- example, @\<scanrange>\<end>50\<\/end>\<\/scanrange>@ means scan the
-- last 50 bytes.
--
-- 'start', 'scanRange_start' - Specifies the start of the byte range. This parameter is optional. Valid
-- values: non-negative integers. The default value is 0. If only @start@
-- is supplied, it means scan from that point to the end of the file. For
-- example, @\<scanrange>\<start>50\<\/start>\<\/scanrange>@ means scan
-- from byte 50 until the end of the file.
newScanRange ::
  ScanRange
newScanRange :: ScanRange
newScanRange =
  ScanRange'
    { $sel:end:ScanRange' :: Maybe Integer
end = forall a. Maybe a
Prelude.Nothing,
      $sel:start:ScanRange' :: Maybe Integer
start = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies the end of the byte range. This parameter is optional. Valid
-- values: non-negative integers. The default value is one less than the
-- size of the object being queried. If only the End parameter is supplied,
-- it is interpreted to mean scan the last N bytes of the file. For
-- example, @\<scanrange>\<end>50\<\/end>\<\/scanrange>@ means scan the
-- last 50 bytes.
scanRange_end :: Lens.Lens' ScanRange (Prelude.Maybe Prelude.Integer)
scanRange_end :: Lens' ScanRange (Maybe Integer)
scanRange_end = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScanRange' {Maybe Integer
end :: Maybe Integer
$sel:end:ScanRange' :: ScanRange -> Maybe Integer
end} -> Maybe Integer
end) (\s :: ScanRange
s@ScanRange' {} Maybe Integer
a -> ScanRange
s {$sel:end:ScanRange' :: Maybe Integer
end = Maybe Integer
a} :: ScanRange)

-- | Specifies the start of the byte range. This parameter is optional. Valid
-- values: non-negative integers. The default value is 0. If only @start@
-- is supplied, it means scan from that point to the end of the file. For
-- example, @\<scanrange>\<start>50\<\/start>\<\/scanrange>@ means scan
-- from byte 50 until the end of the file.
scanRange_start :: Lens.Lens' ScanRange (Prelude.Maybe Prelude.Integer)
scanRange_start :: Lens' ScanRange (Maybe Integer)
scanRange_start = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScanRange' {Maybe Integer
start :: Maybe Integer
$sel:start:ScanRange' :: ScanRange -> Maybe Integer
start} -> Maybe Integer
start) (\s :: ScanRange
s@ScanRange' {} Maybe Integer
a -> ScanRange
s {$sel:start:ScanRange' :: Maybe Integer
start = Maybe Integer
a} :: ScanRange)

instance Prelude.Hashable ScanRange where
  hashWithSalt :: Int -> ScanRange -> Int
hashWithSalt Int
_salt ScanRange' {Maybe Integer
start :: Maybe Integer
end :: Maybe Integer
$sel:start:ScanRange' :: ScanRange -> Maybe Integer
$sel:end:ScanRange' :: ScanRange -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
end
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
start

instance Prelude.NFData ScanRange where
  rnf :: ScanRange -> ()
rnf ScanRange' {Maybe Integer
start :: Maybe Integer
end :: Maybe Integer
$sel:start:ScanRange' :: ScanRange -> Maybe Integer
$sel:end:ScanRange' :: ScanRange -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
end seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
start

instance Data.ToXML ScanRange where
  toXML :: ScanRange -> XML
toXML ScanRange' {Maybe Integer
start :: Maybe Integer
end :: Maybe Integer
$sel:start:ScanRange' :: ScanRange -> Maybe Integer
$sel:end:ScanRange' :: ScanRange -> Maybe Integer
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [Name
"End" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Integer
end, Name
"Start" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Integer
start]