module Data.PrimitiveArray.Index.Point where
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Data.Aeson
import Data.Binary
import Data.Bits
import Data.Bits.Extras (Ranked)
import Data.Hashable (Hashable)
import Data.Serialize
import Data.Vector.Unboxed.Deriving
import Data.Vector.Unboxed (Unbox(..))
import GHC.Exts
import GHC.Generics (Generic)
import qualified Data.Vector.Fusion.Stream.Monadic as SM
import qualified Data.Vector.Unboxed as VU
import Test.QuickCheck as TQ
import Test.SmallCheck.Series as TS
import Data.PrimitiveArray.Index.Class
import Data.PrimitiveArray.Index.IOC
import Data.PrimitiveArray.Vector.Compat
newtype PointL t = PointL {fromPointL :: Int}
deriving (Eq,Ord,Read,Show,Generic)
pointLI :: Int -> PointL I
pointLI = PointL
pointLO :: Int -> PointL O
pointLO = PointL
pointLC :: Int -> PointL C
pointLC = PointL
newtype PointR t = PointR {fromPointR :: Int}
deriving (Eq,Ord,Read,Show,Generic)
derivingUnbox "PointL"
[t| forall t . PointL t -> Int |]
[| \ (PointL i) -> i |]
[| \ i -> PointL i |]
instance Binary (PointL t)
instance Serialize (PointL t)
instance FromJSON (PointL t)
instance ToJSON (PointL t)
instance Hashable (PointL t)
instance NFData (PointL t) where
rnf (PointL l) = rnf l
instance Index (PointL t) where
linearIndex _ _ (PointL z) = z
smallestLinearIndex (PointL l) = error "still needed?"
largestLinearIndex (PointL h) = h
size (_) (PointL h) = h + 1
inBounds (_) (PointL h) (PointL x) = 0<=x && x<=h
instance IndexStream z => IndexStream (z:.PointL I) where
streamUp (ls:.PointL lf) (hs:.PointL ht) = flatten (streamUpMk lf) (streamUpStep ht) $ streamUp ls hs
streamDown (ls:.PointL lf) (hs:.PointL ht) = flatten (streamDownMk ht) (streamDownStep lf) $ streamDown ls hs
instance IndexStream z => IndexStream (z:.PointL O) where
streamUp (ls:.PointL lf) (hs:.PointL ht) = flatten (streamDownMk ht) (streamDownStep lf) $ streamUp ls hs
streamDown (ls:.PointL lf) (hs:.PointL ht) = flatten (streamUpMk lf) (streamUpStep ht) $ streamDown ls hs
instance IndexStream z => IndexStream (z:.PointL C) where
streamUp (ls:.PointL lf) (hs:.PointL ht) = flatten (streamUpMk lf) (streamUpStep ht) $ streamUp ls hs
streamDown (ls:.PointL lf) (hs:.PointL ht) = flatten (streamDownMk ht) (streamDownStep lf) $ streamDown ls hs
data SP z = SP !z !Int#
streamUpMk (I# lf) z = return $ SP z lf
streamUpStep (I# ht) (SP z k)
| 1# <- k ># ht = return $ SM.Done
| otherwise = return $ SM.Yield (z:.PointL (I# k)) (SP z (k +# 1#))
streamDownMk (I# ht) z = return $ SP z ht
streamDownStep (I# lf) (SP z k)
| 1# <- k <# lf = return $ SM.Done
| otherwise = return $ SM.Yield (z:.PointL (I# k)) (SP z (k -# 1#))
instance IndexStream (Z:.PointL t) => IndexStream (PointL t)
instance Arbitrary (PointL t) where
arbitrary = do
b <- choose (0,100)
return $ PointL b
shrink (PointL j)
| 0<j = [PointL $ j1]
| otherwise = []
instance Monad m => Serial m (PointL t) where
series = PointL . TS.getNonNegative <$> series
derivingUnbox "PointR"
[t| forall t . PointR t -> Int |]
[| \ (PointR i) -> i |]
[| \ i -> PointR i |]
instance Binary (PointR t)
instance Serialize (PointR t)
instance FromJSON (PointR t)
instance ToJSON (PointR t)
instance Hashable (PointR t)
instance NFData (PointR t) where
rnf (PointR l) = rnf l
instance Index (PointR t) where
linearIndex l _ (PointR z) = undefined
smallestLinearIndex = undefined
largestLinearIndex = undefined
size = undefined