module Data.PrimitiveArray.Index.Outside where
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Data.Aeson
import Data.Binary
import Data.Serialize
import Data.Vector.Unboxed.Deriving
import Data.Vector.Unboxed (Unbox(..))
import GHC.Generics
import Test.QuickCheck
import Data.PrimitiveArray.Index.Class
newtype Outside z = O { unO :: z }
  deriving (Eq,Ord,Read,Show,Generic)
derivingUnbox "Outside"
  [t| forall z . Unbox z => Outside z -> z |]
  [| unO |]
  [| O   |]
instance Binary    z => Binary    (Outside z)
instance Serialize z => Serialize (Outside z)
instance ToJSON    z => ToJSON    (Outside z)
instance FromJSON  z => FromJSON  (Outside z)
instance NFData z => NFData (Outside z) where
  rnf (O z) = rnf z
  
instance Index i => Index (Outside i) where
  linearIndex (O l) (O h) (O i) = linearIndex l h i
  
  smallestLinearIndex (O i) = smallestLinearIndex i
  
  largestLinearIndex (O i) = largestLinearIndex i
  
  size (O l) (O h) = size l h
  
  inBounds (O l) (O h) (O z) = inBounds l h z
  
instance IndexStream i => IndexStream (Outside i) where
  streamUp (O l) (O h) = fmap O $ streamDown l h
  
  streamDown (O l) (O h) = fmap O $ streamUp l h
  
instance Arbitrary z => Arbitrary (Outside z) where
  arbitrary = O <$> arbitrary
  shrink (O z) = O <$> shrink z