{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

Represents a byte range as used in the Range header.

If /@end@/ is non-negative, then /@start@/ and /@end@/ represent the bounds
of of the range, counting from 0. (Eg, the first 500 bytes would be
represented as /@start@/ = 0 and /@end@/ = 499.)

If /@end@/ is -1 and /@start@/ is non-negative, then this represents a
range starting at /@start@/ and ending with the last byte of the
requested resource body. (Eg, all but the first 500 bytes would be
/@start@/ = 500, and /@end@/ = -1.)

If /@end@/ is -1 and /@start@/ is negative, then it represents a \"suffix
range\", referring to the last -/@start@/ bytes of the resource body.
(Eg, the last 500 bytes would be /@start@/ = -500 and /@end@/ = -1.)

/Since: 2.26/
-}

#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
       && !defined(__HADDOCK_VERSION__))

module GI.Soup.Structs.Range
    (

-- * Exported types
    Range(..)                               ,
    newZeroRange                            ,
    noRange                                 ,


 -- * Properties
-- ** end #attr:end#
{- | the end of the range
-}
    getRangeEnd                             ,
#if ENABLE_OVERLOADING
    range_end                               ,
#endif
    setRangeEnd                             ,


-- ** start #attr:start#
{- | the start of the range
-}
    getRangeStart                           ,
#if ENABLE_OVERLOADING
    range_start                             ,
#endif
    setRangeStart                           ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL


-- | Memory-managed wrapper type.
newtype Range = Range (ManagedPtr Range)
instance WrappedPtr Range where
    wrappedPtrCalloc = callocBytes 16
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 16 >=> wrapPtr Range)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `Range` struct initialized to zero.
newZeroRange :: MonadIO m => m Range
newZeroRange = liftIO $ wrappedPtrCalloc >>= wrapPtr Range

instance tag ~ 'AttrSet => Constructible Range tag where
    new _ attrs = do
        o <- newZeroRange
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `Range`.
noRange :: Maybe Range
noRange = Nothing

{- |
Get the value of the “@start@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' range #start
@
-}
getRangeStart :: MonadIO m => Range -> m Int64
getRangeStart s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int64
    return val

{- |
Set the value of the “@start@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' range [ #start 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRangeStart :: MonadIO m => Range -> Int64 -> m ()
setRangeStart s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Int64)

#if ENABLE_OVERLOADING
data RangeStartFieldInfo
instance AttrInfo RangeStartFieldInfo where
    type AttrAllowedOps RangeStartFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RangeStartFieldInfo = (~) Int64
    type AttrBaseTypeConstraint RangeStartFieldInfo = (~) Range
    type AttrGetType RangeStartFieldInfo = Int64
    type AttrLabel RangeStartFieldInfo = "start"
    type AttrOrigin RangeStartFieldInfo = Range
    attrGet _ = getRangeStart
    attrSet _ = setRangeStart
    attrConstruct = undefined
    attrClear _ = undefined

range_start :: AttrLabelProxy "start"
range_start = AttrLabelProxy

#endif


{- |
Get the value of the “@end@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' range #end
@
-}
getRangeEnd :: MonadIO m => Range -> m Int64
getRangeEnd s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Int64
    return val

{- |
Set the value of the “@end@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' range [ #end 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRangeEnd :: MonadIO m => Range -> Int64 -> m ()
setRangeEnd s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Int64)

#if ENABLE_OVERLOADING
data RangeEndFieldInfo
instance AttrInfo RangeEndFieldInfo where
    type AttrAllowedOps RangeEndFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RangeEndFieldInfo = (~) Int64
    type AttrBaseTypeConstraint RangeEndFieldInfo = (~) Range
    type AttrGetType RangeEndFieldInfo = Int64
    type AttrLabel RangeEndFieldInfo = "end"
    type AttrOrigin RangeEndFieldInfo = Range
    attrGet _ = getRangeEnd
    attrSet _ = setRangeEnd
    attrConstruct = undefined
    attrClear _ = undefined

range_end :: AttrLabelProxy "end"
range_end = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList Range
type instance O.AttributeList Range = RangeAttributeList
type RangeAttributeList = ('[ '("start", RangeStartFieldInfo), '("end", RangeEndFieldInfo)] :: [(Symbol, *)])
#endif

#if ENABLE_OVERLOADING
type family ResolveRangeMethod (t :: Symbol) (o :: *) :: * where
    ResolveRangeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveRangeMethod t Range, O.MethodInfo info Range p) => OL.IsLabel t (Range -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif

#endif