module Data.PrimitiveArray.Index.EdgeBoundary where
import Control.Applicative ((<$>))
import Control.DeepSeq (NFData(..))
import Control.Monad (filterM, guard)
import Data.Aeson (FromJSON,FromJSONKey,ToJSON,ToJSONKey)
import Data.Binary (Binary)
import Data.Hashable (Hashable)
import Data.Serialize (Serialize)
import Data.Vector.Fusion.Stream.Monadic (Step(..), map)
import Data.Vector.Unboxed.Deriving
import Debug.Trace
import GHC.Generics (Generic)
import Prelude hiding (map)
import Test.QuickCheck (Arbitrary(..), choose)
import Test.SmallCheck.Series as TS
import Data.PrimitiveArray.Index.Class
import Data.PrimitiveArray.Index.IOC
import Data.PrimitiveArray.Vector.Compat
data EdgeBoundary t = !Int :-> !Int
deriving (Eq,Ord,Show,Generic,Read)
fromEdgeBoundaryFst :: EdgeBoundary t -> Int
fromEdgeBoundaryFst (i :-> _) = i
fromEdgeBoundarySnd :: EdgeBoundary t -> Int
fromEdgeBoundarySnd (_ :-> j) = j
derivingUnbox "EdgeBoundary"
[t| forall t . EdgeBoundary t -> (Int,Int) |]
[| \ (f :-> t) -> (f,t) |]
[| \ (f,t) -> (f :-> t) |]
instance Binary (EdgeBoundary t)
instance Serialize (EdgeBoundary t)
instance FromJSON (EdgeBoundary t)
instance FromJSONKey (EdgeBoundary t)
instance ToJSON (EdgeBoundary t)
instance ToJSONKey (EdgeBoundary t)
instance Hashable (EdgeBoundary t)
instance NFData (EdgeBoundary t) where
rnf (f :-> t) = f `seq` rnf t
instance Index (EdgeBoundary t) where
linearIndex (f :-> _) (_ :-> t) (i :-> j) = i * (t+1) + j
smallestLinearIndex _ = error "still needed?"
largestLinearIndex (_ :-> t) = (t+1) * (t+1) 1
size _ (_ :-> t) = (t+1) * (t+1)
inBounds _ (_ :-> t) (i :-> j) = 0<=i && i <= t && 0 <= j && j<=t
instance IndexStream z => IndexStream (z:.EdgeBoundary I) where
streamUp (ls:.(l:->_)) (hs:.(_:->h)) = flatten (streamUpMk l) (streamUpStep l h) $ streamUp ls hs
streamDown (ls:.(l:->_)) (hs:.(_:->h)) = flatten (streamDownMk h) (streamDownStep l h) $ streamDown ls hs
instance IndexStream z => IndexStream (z:.EdgeBoundary O) where
streamUp (ls:.(l:->_)) (hs:.(_:->h)) = flatten (streamDownMk h) (streamDownStep l h) $ streamUp ls hs
streamDown (ls:.(l:->_)) (hs:.(_:->h)) = flatten (streamUpMk l) (streamUpStep l h) $ streamDown ls hs
instance IndexStream z => IndexStream (z:.EdgeBoundary C) where
streamUp (ls:.(l:->_)) (hs:.(_:->h)) = flatten (streamUpMk l) (streamUpStep l h) $ streamUp ls hs
streamDown (ls:.(l:->_)) (hs:.(_:->h)) = flatten (streamDownMk h) (streamDownStep l h) $ streamDown ls hs
streamUpMk l z = return (z,l,l)
streamUpStep l h (z,i,j)
| i > h = return $ Done
| j > h = return $ Skip (z,i+1,l)
| otherwise = return $ Yield (z:.(i:->j)) (z,i,j+1)
streamDownMk h z = return (z,h,h)
streamDownStep l h (z,i,j)
| i < l = return $ Done
| j < l = return $ Skip (z,i1,h)
| otherwise = return $ Yield (z:.(i:->j)) (z,i,j1)
instance (IndexStream (Z:.EdgeBoundary t)) => IndexStream (EdgeBoundary t)
instance Arbitrary (EdgeBoundary t) where
arbitrary = do
a <- choose (0,14)
b <- choose (0,14)
return $ a :-> b
shrink (i:->j) = Prelude.fmap (\(k,l) -> k :-> l) $ shrink (i,j)
instance Monad m => Serial m (EdgeBoundary t) where
series = do
i <- TS.getNonNegative <$> series
j <- TS.getNonNegative <$> series
return $ i :-> j