{-# LANGUAGE ForeignFunctionInterface #-}
module Sym.Perm.Stat
(
asc
, des
, exc
, fp
, sfp
, cyc
, inv
, maj
, comaj
, peak
, vall
, dasc
, ddes
, lmin
, lmax
, rmin
, rmax
, head
, last
, lir
, ldr
, rir
, rdr
, comp
, scomp
, ep
, dim
, asc0
, des0
, lis
, lds
) where
import Prelude hiding (head, last)
import Sym.Perm
import qualified Sym.Perm.SSYT as Y
import qualified Sym.Perm.D8 as D8
import Foreign.Ptr
import Foreign.C.Types
import System.IO.Unsafe
marshal :: (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal :: (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
f Perm
w =
CLong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CLong -> Int)
-> ((Ptr CLong -> IO CLong) -> CLong)
-> (Ptr CLong -> IO CLong)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO CLong -> CLong
forall a. IO a -> a
unsafePerformIO (IO CLong -> CLong)
-> ((Ptr CLong -> IO CLong) -> IO CLong)
-> (Ptr CLong -> IO CLong)
-> CLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> (Ptr CLong -> IO CLong) -> IO CLong
forall a. Perm -> (Ptr CLong -> IO a) -> IO a
unsafeWith Perm
w ((Ptr CLong -> IO CLong) -> Int) -> (Ptr CLong -> IO CLong) -> Int
forall a b. (a -> b) -> a -> b
$ \Ptr CLong
p ->
CLong -> IO CLong
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CLong -> IO CLong) -> CLong -> IO CLong
forall a b. (a -> b) -> a -> b
$ Ptr CLong -> CLong -> CLong
f Ptr CLong
p (Int -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Perm -> Int
forall a. Size a => a -> Int
size Perm
w))
{-# INLINE marshal #-}
foreign import ccall unsafe "stat.h asc" c_asc
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h des" c_des
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h exc" c_exc
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h fp" c_fp
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h sfp" c_sfp
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h cyc" c_cyc
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h inv" c_inv
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h maj" c_maj
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h comaj" c_comaj
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h peak" c_peak
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h vall" c_vall
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h dasc" c_dasc
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h ddes" c_ddes
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h lmin" c_lmin
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h lmax" c_lmax
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h lir" c_lir
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h ldr" c_ldr
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h comp" c_comp
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h ep" c_ep
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h dim" c_dim
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h asc0" c_asc0
:: Ptr CLong -> CLong -> CLong
foreign import ccall unsafe "stat.h des0" c_des0
:: Ptr CLong -> CLong -> CLong
asc :: Perm -> Int
asc :: Perm -> Int
asc = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_asc
des :: Perm -> Int
des :: Perm -> Int
des = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_des
exc :: Perm -> Int
exc :: Perm -> Int
exc = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_exc
fp :: Perm -> Int
fp :: Perm -> Int
fp = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_fp
sfp :: Perm -> Int
sfp :: Perm -> Int
sfp = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_sfp
cyc :: Perm -> Int
cyc :: Perm -> Int
cyc = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_cyc
inv :: Perm -> Int
inv :: Perm -> Int
inv = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_inv
maj :: Perm -> Int
maj :: Perm -> Int
maj = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_maj
comaj :: Perm -> Int
comaj :: Perm -> Int
comaj = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_comaj
peak :: Perm -> Int
peak :: Perm -> Int
peak = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_peak
vall :: Perm -> Int
vall :: Perm -> Int
vall = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_vall
dasc :: Perm -> Int
dasc :: Perm -> Int
dasc = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_dasc
ddes :: Perm -> Int
ddes :: Perm -> Int
ddes = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_ddes
lmin :: Perm -> Int
lmin :: Perm -> Int
lmin = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_lmin
lmax :: Perm -> Int
lmax :: Perm -> Int
lmax = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_lmax
rmin :: Perm -> Int
rmin :: Perm -> Int
rmin = Perm -> Int
lmin (Perm -> Int) -> (Perm -> Perm) -> Perm -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> Perm
D8.reverse
rmax :: Perm -> Int
rmax :: Perm -> Int
rmax = Perm -> Int
lmax (Perm -> Int) -> (Perm -> Perm) -> Perm -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> Perm
D8.reverse
head :: Perm -> Int
head :: Perm -> Int
head Perm
w | Perm -> Int
forall a. Size a => a -> Int
size Perm
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Perm
w Perm -> Int -> Int
`unsafeAt` Int
0)
| Bool
otherwise = Int
0
last :: Perm -> Int
last :: Perm -> Int
last Perm
w | Perm -> Int
forall a. Size a => a -> Int
size Perm
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Perm
w Perm -> Int -> Int
`unsafeAt` (Perm -> Int
forall a. Size a => a -> Int
size Perm
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))
| Bool
otherwise = Int
0
lir :: Perm -> Int
lir :: Perm -> Int
lir = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_lir
ldr :: Perm -> Int
ldr :: Perm -> Int
ldr = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_ldr
rir :: Perm -> Int
rir :: Perm -> Int
rir = Perm -> Int
ldr (Perm -> Int) -> (Perm -> Perm) -> Perm -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> Perm
D8.reverse
rdr :: Perm -> Int
rdr :: Perm -> Int
rdr = Perm -> Int
lir (Perm -> Int) -> (Perm -> Perm) -> Perm -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> Perm
D8.reverse
comp :: Perm -> Int
comp :: Perm -> Int
comp = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_comp
scomp :: Perm -> Int
scomp :: Perm -> Int
scomp = Perm -> Int
comp (Perm -> Int) -> (Perm -> Perm) -> Perm -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> Perm
D8.complement
ep :: Perm -> Int
ep :: Perm -> Int
ep = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_ep
dim :: Perm -> Int
dim :: Perm -> Int
dim = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_dim
asc0 :: Perm -> Int
asc0 :: Perm -> Int
asc0 = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_asc0
des0 :: Perm -> Int
des0 :: Perm -> Int
des0 = (Ptr CLong -> CLong -> CLong) -> Perm -> Int
marshal Ptr CLong -> CLong -> CLong
c_des0
lis :: Perm -> Int
lis :: Perm -> Int
lis Perm
w = case SSYTPair -> [Int]
forall a. Shape a => a -> [Int]
Y.shape (Perm -> SSYTPair
Y.fromPerm Perm
w) of
[] -> Int
0
(Int
x:[Int]
_) -> Int
x
lds :: Perm -> Int
lds :: Perm -> Int
lds = [[Int]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([[Int]] -> Int) -> (Perm -> [[Int]]) -> Perm -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SSYTPair -> [[Int]]
Y.recordingTableau (SSYTPair -> [[Int]]) -> (Perm -> SSYTPair) -> Perm -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Perm -> SSYTPair
Y.fromPerm