{-# LANGUAGE OverloadedStrings, FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, CPP #-}
module Network.HTTP.Types.Header
(
  -- ** Types
  Header
, HeaderName
, RequestHeaders
, ResponseHeaders
  -- ** Common headers
, hAccept
, hAcceptCharset
, hAcceptEncoding
, hAcceptLanguage
, hAcceptRanges
, hAge
, hAllow
, hAuthorization
, hCacheControl
, hConnection
, hContentEncoding
, hContentLanguage
, hContentLength
, hContentLocation
, hContentMD5
, hContentRange
, hContentType
, hDate
, hETag
, hExpect
, hExpires
, hFrom
, hHost
, hIfMatch
, hIfModifiedSince
, hIfNoneMatch
, hIfRange
, hIfUnmodifiedSince
, hLastModified
, hLocation
, hMaxForwards
, hOrigin
, hPragma
, hPrefer
, hPreferenceApplied
, hProxyAuthenticate
, hProxyAuthorization
, hRange
, hReferer
, hRetryAfter
, hServer
, hTE
, hTrailer
, hTransferEncoding
, hUpgrade
, hUserAgent
, hVary
, hVia
, hWWWAuthenticate
, hWarning
, hContentDisposition
, hMIMEVersion
, hCookie
, hSetCookie
  -- ** Byte ranges
, ByteRange(..)
, renderByteRangeBuilder
, renderByteRange
, ByteRanges
, renderByteRangesBuilder
, renderByteRanges
, parseByteRanges
)
where

import           Data.List
#if __GLASGOW_HASKELL__ < 710
import           Data.Monoid
#endif
import qualified Data.ByteString                as B
import qualified Data.ByteString.Char8          as B8
import qualified Data.ByteString.Builder        as B
import qualified Data.ByteString.Lazy           as BL
import qualified Data.CaseInsensitive           as CI
import           Data.ByteString.Char8          () {-IsString-}
import           Data.Typeable                  (Typeable)
import           Data.Data                      (Data)

-- | Header
type Header = (HeaderName, B.ByteString)

-- | Header name
type HeaderName = CI.CI B.ByteString

-- | Request Headers
type RequestHeaders = [Header]

-- | Response Headers
type ResponseHeaders = [Header]

-- | HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAccept, hAcceptCharset, hAcceptEncoding, hAcceptLanguage, hAcceptRanges, hAge, hAllow, hAuthorization, hCacheControl, hConnection, hContentEncoding, hContentLanguage, hContentLength, hContentLocation, hContentMD5, hContentRange, hContentType, hDate, hETag, hExpect, hExpires, hFrom, hHost, hIfMatch, hIfModifiedSince, hIfNoneMatch, hIfRange, hIfUnmodifiedSince, hLastModified, hLocation, hMaxForwards, hPragma, hProxyAuthenticate, hProxyAuthorization, hRange, hReferer, hRetryAfter, hServer, hTE, hTrailer, hTransferEncoding, hUpgrade, hUserAgent, hVary, hVia, hWWWAuthenticate, hWarning :: HeaderName
hAccept :: HeaderName
hAccept             = HeaderName
"Accept"
hAcceptCharset :: HeaderName
hAcceptCharset      = HeaderName
"Accept-Charset"
hAcceptEncoding :: HeaderName
hAcceptEncoding     = HeaderName
"Accept-Encoding"
hAcceptLanguage :: HeaderName
hAcceptLanguage     = HeaderName
"Accept-Language"
hAcceptRanges :: HeaderName
hAcceptRanges       = HeaderName
"Accept-Ranges"
hAge :: HeaderName
hAge                = HeaderName
"Age"
hAllow :: HeaderName
hAllow              = HeaderName
"Allow"
hAuthorization :: HeaderName
hAuthorization      = HeaderName
"Authorization"
hCacheControl :: HeaderName
hCacheControl       = HeaderName
"Cache-Control"
hConnection :: HeaderName
hConnection         = HeaderName
"Connection"
hContentEncoding :: HeaderName
hContentEncoding    = HeaderName
"Content-Encoding"
hContentLanguage :: HeaderName
hContentLanguage    = HeaderName
"Content-Language"
hContentLength :: HeaderName
hContentLength      = HeaderName
"Content-Length"
hContentLocation :: HeaderName
hContentLocation    = HeaderName
"Content-Location"
hContentMD5 :: HeaderName
hContentMD5         = HeaderName
"Content-MD5"
hContentRange :: HeaderName
hContentRange       = HeaderName
"Content-Range"
hContentType :: HeaderName
hContentType        = HeaderName
"Content-Type"
hDate :: HeaderName
hDate               = HeaderName
"Date"
hETag :: HeaderName
hETag               = HeaderName
"ETag"
hExpect :: HeaderName
hExpect             = HeaderName
"Expect"
hExpires :: HeaderName
hExpires            = HeaderName
"Expires"
hFrom :: HeaderName
hFrom               = HeaderName
"From"
hHost :: HeaderName
hHost               = HeaderName
"Host"
hIfMatch :: HeaderName
hIfMatch            = HeaderName
"If-Match"
hIfModifiedSince :: HeaderName
hIfModifiedSince    = HeaderName
"If-Modified-Since"
hIfNoneMatch :: HeaderName
hIfNoneMatch        = HeaderName
"If-None-Match"
hIfRange :: HeaderName
hIfRange            = HeaderName
"If-Range"
hIfUnmodifiedSince :: HeaderName
hIfUnmodifiedSince  = HeaderName
"If-Unmodified-Since"
hLastModified :: HeaderName
hLastModified       = HeaderName
"Last-Modified"
hLocation :: HeaderName
hLocation           = HeaderName
"Location"
hMaxForwards :: HeaderName
hMaxForwards        = HeaderName
"Max-Forwards"
hPragma :: HeaderName
hPragma             = HeaderName
"Pragma"
hProxyAuthenticate :: HeaderName
hProxyAuthenticate  = HeaderName
"Proxy-Authenticate"
hProxyAuthorization :: HeaderName
hProxyAuthorization = HeaderName
"Proxy-Authorization"
hRange :: HeaderName
hRange              = HeaderName
"Range"
hReferer :: HeaderName
hReferer            = HeaderName
"Referer"
hRetryAfter :: HeaderName
hRetryAfter         = HeaderName
"Retry-After"
hServer :: HeaderName
hServer             = HeaderName
"Server"
hTE :: HeaderName
hTE                 = HeaderName
"TE"
hTrailer :: HeaderName
hTrailer            = HeaderName
"Trailer"
hTransferEncoding :: HeaderName
hTransferEncoding   = HeaderName
"Transfer-Encoding"
hUpgrade :: HeaderName
hUpgrade            = HeaderName
"Upgrade"
hUserAgent :: HeaderName
hUserAgent          = HeaderName
"User-Agent"
hVary :: HeaderName
hVary               = HeaderName
"Vary"
hVia :: HeaderName
hVia                = HeaderName
"Via"
hWWWAuthenticate :: HeaderName
hWWWAuthenticate    = HeaderName
"WWW-Authenticate"
hWarning :: HeaderName
hWarning            = HeaderName
"Warning"

-- | HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec19.html
hContentDisposition, hMIMEVersion :: HeaderName
hContentDisposition :: HeaderName
hContentDisposition = HeaderName
"Content-Disposition"
hMIMEVersion :: HeaderName
hMIMEVersion        = HeaderName
"MIME-Version"

-- | HTTP Header names according to https://tools.ietf.org/html/rfc6265#section-4
hCookie, hSetCookie :: HeaderName
hCookie :: HeaderName
hCookie             = HeaderName
"Cookie"
hSetCookie :: HeaderName
hSetCookie          = HeaderName
"Set-Cookie"

-- | HTTP Header names according to https://tools.ietf.org/html/rfc6454
hOrigin :: HeaderName
hOrigin :: HeaderName
hOrigin = HeaderName
"Origin"

-- | HTTP Header names according to https://tools.ietf.org/html/rfc7240
hPrefer, hPreferenceApplied :: HeaderName
hPrefer :: HeaderName
hPrefer = HeaderName
"Prefer"
hPreferenceApplied :: HeaderName
hPreferenceApplied = HeaderName
"Preference-Applied"

-- | RFC 2616 Byte range (individual).
--
-- Negative indices are not allowed!
data ByteRange
  = ByteRangeFrom !Integer
  | ByteRangeFromTo !Integer !Integer
  | ByteRangeSuffix !Integer
  deriving (Int -> ByteRange -> ShowS
[ByteRange] -> ShowS
ByteRange -> String
(Int -> ByteRange -> ShowS)
-> (ByteRange -> String)
-> ([ByteRange] -> ShowS)
-> Show ByteRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ByteRange -> ShowS
showsPrec :: Int -> ByteRange -> ShowS
$cshow :: ByteRange -> String
show :: ByteRange -> String
$cshowList :: [ByteRange] -> ShowS
showList :: [ByteRange] -> ShowS
Show, ByteRange -> ByteRange -> Bool
(ByteRange -> ByteRange -> Bool)
-> (ByteRange -> ByteRange -> Bool) -> Eq ByteRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ByteRange -> ByteRange -> Bool
== :: ByteRange -> ByteRange -> Bool
$c/= :: ByteRange -> ByteRange -> Bool
/= :: ByteRange -> ByteRange -> Bool
Eq, Eq ByteRange
Eq ByteRange
-> (ByteRange -> ByteRange -> Ordering)
-> (ByteRange -> ByteRange -> Bool)
-> (ByteRange -> ByteRange -> Bool)
-> (ByteRange -> ByteRange -> Bool)
-> (ByteRange -> ByteRange -> Bool)
-> (ByteRange -> ByteRange -> ByteRange)
-> (ByteRange -> ByteRange -> ByteRange)
-> Ord ByteRange
ByteRange -> ByteRange -> Bool
ByteRange -> ByteRange -> Ordering
ByteRange -> ByteRange -> ByteRange
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ByteRange -> ByteRange -> Ordering
compare :: ByteRange -> ByteRange -> Ordering
$c< :: ByteRange -> ByteRange -> Bool
< :: ByteRange -> ByteRange -> Bool
$c<= :: ByteRange -> ByteRange -> Bool
<= :: ByteRange -> ByteRange -> Bool
$c> :: ByteRange -> ByteRange -> Bool
> :: ByteRange -> ByteRange -> Bool
$c>= :: ByteRange -> ByteRange -> Bool
>= :: ByteRange -> ByteRange -> Bool
$cmax :: ByteRange -> ByteRange -> ByteRange
max :: ByteRange -> ByteRange -> ByteRange
$cmin :: ByteRange -> ByteRange -> ByteRange
min :: ByteRange -> ByteRange -> ByteRange
Ord, Typeable, Typeable ByteRange
Typeable ByteRange
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ByteRange -> c ByteRange)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ByteRange)
-> (ByteRange -> Constr)
-> (ByteRange -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ByteRange))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange))
-> ((forall b. Data b => b -> b) -> ByteRange -> ByteRange)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ByteRange -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ByteRange -> r)
-> (forall u. (forall d. Data d => d -> u) -> ByteRange -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ByteRange -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange)
-> Data ByteRange
ByteRange -> Constr
ByteRange -> DataType
(forall b. Data b => b -> b) -> ByteRange -> ByteRange
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ByteRange -> u
forall u. (forall d. Data d => d -> u) -> ByteRange -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteRange -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteRange -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteRange
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteRange -> c ByteRange
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteRange)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteRange -> c ByteRange
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteRange -> c ByteRange
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteRange
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteRange
$ctoConstr :: ByteRange -> Constr
toConstr :: ByteRange -> Constr
$cdataTypeOf :: ByteRange -> DataType
dataTypeOf :: ByteRange -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteRange)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteRange)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange)
$cgmapT :: (forall b. Data b => b -> b) -> ByteRange -> ByteRange
gmapT :: (forall b. Data b => b -> b) -> ByteRange -> ByteRange
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteRange -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteRange -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteRange -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteRange -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ByteRange -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ByteRange -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteRange -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteRange -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteRange -> m ByteRange
Data)

renderByteRangeBuilder :: ByteRange -> B.Builder
renderByteRangeBuilder :: ByteRange -> Builder
renderByteRangeBuilder (ByteRangeFrom Integer
from) = Integer -> Builder
B.integerDec Integer
from Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend` Char -> Builder
B.char7 Char
'-'
renderByteRangeBuilder (ByteRangeFromTo Integer
from Integer
to) = Integer -> Builder
B.integerDec Integer
from Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend` Char -> Builder
B.char7 Char
'-' Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend` Integer -> Builder
B.integerDec Integer
to
renderByteRangeBuilder (ByteRangeSuffix Integer
suffix) = Char -> Builder
B.char7 Char
'-' Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend` Integer -> Builder
B.integerDec Integer
suffix

renderByteRange :: ByteRange -> B.ByteString
renderByteRange :: ByteRange -> ByteString
renderByteRange = ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (ByteRange -> ByteString) -> ByteRange -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
B.toLazyByteString (Builder -> ByteString)
-> (ByteRange -> Builder) -> ByteRange -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteRange -> Builder
renderByteRangeBuilder

-- | RFC 2616 Byte ranges (set).
type ByteRanges = [ByteRange]

renderByteRangesBuilder :: ByteRanges -> B.Builder
renderByteRangesBuilder :: [ByteRange] -> Builder
renderByteRangesBuilder [ByteRange]
xs = ByteString -> Builder
B.byteString ByteString
"bytes=" Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend`
                             [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat (Builder -> [Builder] -> [Builder]
forall a. a -> [a] -> [a]
intersperse (Char -> Builder
B.char7 Char
',') ((ByteRange -> Builder) -> [ByteRange] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map ByteRange -> Builder
renderByteRangeBuilder [ByteRange]
xs))

renderByteRanges :: ByteRanges -> B.ByteString
renderByteRanges :: [ByteRange] -> ByteString
renderByteRanges = ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> ([ByteRange] -> ByteString) -> [ByteRange] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
B.toLazyByteString (Builder -> ByteString)
-> ([ByteRange] -> Builder) -> [ByteRange] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteRange] -> Builder
renderByteRangesBuilder

-- | Parse the value of a Range header into a 'ByteRanges'.
--
-- >>> parseByteRanges "error"
-- Nothing
-- >>> parseByteRanges "bytes=0-499"
-- Just [ByteRangeFromTo 0 499]
-- >>> parseByteRanges "bytes=500-999"
-- Just [ByteRangeFromTo 500 999]
-- >>> parseByteRanges "bytes=-500"
-- Just [ByteRangeSuffix 500]
-- >>> parseByteRanges "bytes=9500-"
-- Just [ByteRangeFrom 9500]
-- >>> parseByteRanges "bytes=0-0,-1"
-- Just [ByteRangeFromTo 0 0,ByteRangeSuffix 1]
-- >>> parseByteRanges "bytes=500-600,601-999"
-- Just [ByteRangeFromTo 500 600,ByteRangeFromTo 601 999]
-- >>> parseByteRanges "bytes=500-700,601-999"
-- Just [ByteRangeFromTo 500 700,ByteRangeFromTo 601 999]
parseByteRanges :: B.ByteString -> Maybe ByteRanges
parseByteRanges :: ByteString -> Maybe [ByteRange]
parseByteRanges ByteString
bs1 = do
    ByteString
bs2 <- ByteString -> ByteString -> Maybe ByteString
stripPrefixB ByteString
"bytes=" ByteString
bs1
    (ByteRange
r, ByteString
bs3) <- ByteString -> Maybe (ByteRange, ByteString)
range ByteString
bs2
    ([ByteRange] -> [ByteRange]) -> ByteString -> Maybe [ByteRange]
forall {c}. ([ByteRange] -> c) -> ByteString -> Maybe c
ranges (ByteRange
rByteRange -> [ByteRange] -> [ByteRange]
forall a. a -> [a] -> [a]
:) ByteString
bs3
  where
    range :: ByteString -> Maybe (ByteRange, ByteString)
range ByteString
bs2 = do
        (Integer
i, ByteString
bs3) <- ByteString -> Maybe (Integer, ByteString)
B8.readInteger ByteString
bs2
        if Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 -- has prefix "-" ("-0" is not valid, but here treated as "0-")
            then (ByteRange, ByteString) -> Maybe (ByteRange, ByteString)
forall a. a -> Maybe a
Just (Integer -> ByteRange
ByteRangeSuffix (Integer -> Integer
forall a. Num a => a -> a
negate Integer
i), ByteString
bs3)
            else do
                ByteString
bs4 <- ByteString -> ByteString -> Maybe ByteString
stripPrefixB ByteString
"-" ByteString
bs3
                case ByteString -> Maybe (Integer, ByteString)
B8.readInteger ByteString
bs4 of
                    Just (Integer
j, ByteString
bs5) | Integer
j Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
i -> (ByteRange, ByteString) -> Maybe (ByteRange, ByteString)
forall a. a -> Maybe a
Just (Integer -> Integer -> ByteRange
ByteRangeFromTo Integer
i Integer
j, ByteString
bs5)
                    Maybe (Integer, ByteString)
_ -> (ByteRange, ByteString) -> Maybe (ByteRange, ByteString)
forall a. a -> Maybe a
Just (Integer -> ByteRange
ByteRangeFrom Integer
i, ByteString
bs4)
    ranges :: ([ByteRange] -> c) -> ByteString -> Maybe c
ranges [ByteRange] -> c
front ByteString
bs3
        | ByteString -> Bool
B.null ByteString
bs3 = c -> Maybe c
forall a. a -> Maybe a
Just ([ByteRange] -> c
front [])
        | Bool
otherwise = do
            ByteString
bs4 <- ByteString -> ByteString -> Maybe ByteString
stripPrefixB ByteString
"," ByteString
bs3
            (ByteRange
r, ByteString
bs5) <- ByteString -> Maybe (ByteRange, ByteString)
range ByteString
bs4
            ([ByteRange] -> c) -> ByteString -> Maybe c
ranges ([ByteRange] -> c
front ([ByteRange] -> c)
-> ([ByteRange] -> [ByteRange]) -> [ByteRange] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteRange
rByteRange -> [ByteRange] -> [ByteRange]
forall a. a -> [a] -> [a]
:)) ByteString
bs5

    stripPrefixB :: ByteString -> ByteString -> Maybe ByteString
stripPrefixB ByteString
x ByteString
y
        | ByteString
x ByteString -> ByteString -> Bool
`B.isPrefixOf` ByteString
y = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Int -> ByteString -> ByteString
B.drop (ByteString -> Int
B.length ByteString
x) ByteString
y)
        | Bool
otherwise = Maybe ByteString
forall a. Maybe a
Nothing