module AtCoder.Extra.Semigroup.Permutation
(
Permutation (..),
new,
unsafeNew,
ident,
zero,
act,
length,
)
where
import AtCoder.Internal.Assert qualified as ACIA
import Data.Vector.Generic qualified as VG
import Data.Vector.Unboxed qualified as VU
import GHC.Stack (HasCallStack)
import Prelude hiding (length)
newtype Permutation = Permutation
{ Permutation -> Vector Int
unPermutation :: VU.Vector Int
}
deriving newtype
(
Permutation -> Permutation -> Bool
(Permutation -> Permutation -> Bool)
-> (Permutation -> Permutation -> Bool) -> Eq Permutation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Permutation -> Permutation -> Bool
== :: Permutation -> Permutation -> Bool
$c/= :: Permutation -> Permutation -> Bool
/= :: Permutation -> Permutation -> Bool
Eq,
Int -> Permutation -> ShowS
[Permutation] -> ShowS
Permutation -> String
(Int -> Permutation -> ShowS)
-> (Permutation -> String)
-> ([Permutation] -> ShowS)
-> Show Permutation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Permutation -> ShowS
showsPrec :: Int -> Permutation -> ShowS
$cshow :: Permutation -> String
show :: Permutation -> String
$cshowList :: [Permutation] -> ShowS
showList :: [Permutation] -> ShowS
Show
)
{-# INLINE new #-}
new :: (HasCallStack) => VU.Vector Int -> Permutation
new :: HasCallStack => Vector Int -> Permutation
new Vector Int
xs = Vector Int -> Permutation
Permutation Vector Int
xs
where
n :: Int
n = Vector Int -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector Int
xs
!()
_ = (() -> Int -> ()) -> () -> Vector Int -> ()
forall b a. Unbox b => (a -> b -> a) -> a -> Vector b -> a
VU.foldl' (\() Int
i -> let !()
_ = HasCallStack => Bool -> String -> ()
Bool -> String -> ()
ACIA.runtimeAssert (-Int
1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n) String
"AtCoder.Extra.Semigroup.Permutation.new: index boundary error" in ()) () Vector Int
xs
{-# INLINE unsafeNew #-}
unsafeNew :: (HasCallStack) => VU.Vector Int -> Permutation
unsafeNew :: HasCallStack => Vector Int -> Permutation
unsafeNew = Vector Int -> Permutation
Permutation
{-# INLINE ident #-}
ident :: Int -> Permutation
ident :: Int -> Permutation
ident = Vector Int -> Permutation
Permutation (Vector Int -> Permutation)
-> (Int -> Vector Int) -> Int -> Permutation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> (Int -> Int) -> Vector Int
forall a. Unbox a => Int -> (Int -> a) -> Vector a
`VU.generate` Int -> Int
forall a. a -> a
id)
{-# INLINE zero #-}
zero :: Int -> Permutation
zero :: Int -> Permutation
zero Int
n = Vector Int -> Permutation
Permutation (Vector Int -> Permutation) -> Vector Int -> Permutation
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Int
forall a. Unbox a => Int -> a -> Vector a
VU.replicate Int
n (-Int
1)
{-# INLINE act #-}
act :: (HasCallStack) => Permutation -> Int -> Int
act :: HasCallStack => Permutation -> Int -> Int
act (Permutation Vector Int
vec) Int
i = case Vector Int
vec Vector Int -> Int -> Int
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i of
(-1) -> Int
i
Int
i' -> Int
i'
{-# INLINE length #-}
length :: (HasCallStack) => Permutation -> Int
length :: HasCallStack => Permutation -> Int
length = Vector Int -> Int
forall a. Unbox a => Vector a -> Int
VU.length (Vector Int -> Int)
-> (Permutation -> Vector Int) -> Permutation -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Permutation -> Vector Int
unPermutation
instance Semigroup Permutation where
{-# INLINE (<>) #-}
Permutation Vector Int
r2 <> :: Permutation -> Permutation -> Permutation
<> Permutation Vector Int
r1 = Vector Int -> Permutation
Permutation (Vector Int -> Permutation) -> Vector Int -> Permutation
forall a b. (a -> b) -> a -> b
$ (Int -> Int) -> Vector Int -> Vector Int
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
VU.map Int -> Int
f Vector Int
r1
where
!()
_ = HasCallStack => Bool -> String -> ()
Bool -> String -> ()
ACIA.runtimeAssert (Vector Int -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector Int
r2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Vector Int -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector Int
r1) String
"AtCoder.Extra.Semigroup.Permutation.(<>): legth mismatch"
f :: Int -> Int
f (-1) = -Int
1
f Int
i = Vector Int -> Int -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
VG.unsafeIndex Vector Int
r2 Int
i