{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Vector.Algorithms.Quicksort.Predefined.Pair
( TestPair(..)
, toTuple
) where
import Data.Vector.Generic qualified as G
import Data.Vector.Generic.Mutable qualified as GM
import Data.Vector.Unboxed qualified as U
data TestPair a b = TestPair a b
deriving (Int -> TestPair a b -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> TestPair a b -> ShowS
forall a b. (Show a, Show b) => [TestPair a b] -> ShowS
forall a b. (Show a, Show b) => TestPair a b -> String
showList :: [TestPair a b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [TestPair a b] -> ShowS
show :: TestPair a b -> String
$cshow :: forall a b. (Show a, Show b) => TestPair a b -> String
showsPrec :: Int -> TestPair a b -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> TestPair a b -> ShowS
Show)
{-# INLINE toTuple #-}
toTuple :: TestPair a b -> (a, b)
toTuple :: forall a b. TestPair a b -> (a, b)
toTuple (TestPair a
a b
b) = (a
a, b
b)
instance U.IsoUnbox (TestPair a b) (a, b) where
{-# INLINE toURepr #-}
{-# INLINE fromURepr #-}
toURepr :: TestPair a b -> (a, b)
toURepr = forall a b. TestPair a b -> (a, b)
toTuple
fromURepr :: (a, b) -> TestPair a b
fromURepr (a
a, b
b) = forall a b. a -> b -> TestPair a b
TestPair a
a b
b
newtype instance U.MVector s (TestPair a b) = MV_TestPair (U.MVector s (a, b))
newtype instance U.Vector (TestPair a b) = V_TestPair (U.Vector (a, b))
deriving via (TestPair a b `U.As` (a, b)) instance (U.Unbox a, U.Unbox b) => GM.MVector U.MVector (TestPair a b)
deriving via (TestPair a b `U.As` (a, b)) instance (U.Unbox a, U.Unbox b) => G.Vector U.Vector (TestPair a b)
instance (U.Unbox a, U.Unbox b) => U.Unbox (TestPair a b)
instance Eq a => Eq (TestPair a b) where
TestPair a
x b
_ == :: TestPair a b -> TestPair a b -> Bool
== TestPair a
x' b
_ = a
x forall a. Eq a => a -> a -> Bool
== a
x'
instance Ord a => Ord (TestPair a b) where
TestPair a
x b
_ compare :: TestPair a b -> TestPair a b -> Ordering
`compare` TestPair a
x' b
_ = a
x forall a. Ord a => a -> a -> Ordering
`compare` a
x'