{-|
Module      : Math.Algebra.JackPol
Description : Symbolic Jack polynomials.
Copyright   : (c) Stéphane Laurent, 2024
License     : GPL-3
Maintainer  : laurent_step@outlook.fr

Computation of symbolic Jack polynomials, zonal polynomials, Schur polynomials and skew Schur polynomials. 
See README for examples and references.
-}

{-# LANGUAGE BangPatterns        #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Math.Algebra.JackPol
  ( jackPol', zonalPol', schurPol', skewSchurPol'
  , jackPol, zonalPol, schurPol, skewSchurPol )
  where
import           Prelude 
  hiding ((*), (+), (-), (/), (^), (*>), product, sum, fromIntegral, fromInteger)
import           Algebra.Additive           ( (+), (-), sum )
import           Algebra.Module             ( (*>) )
import           Algebra.Ring               ( (*), product, one, fromInteger )
import qualified Algebra.Module             as AlgMod
import qualified Algebra.Field              as AlgField
import qualified Algebra.Ring               as AlgRing
import           Control.Lens               ( (.~), element )
import           Data.Array                 ( Array, (!), (//), listArray )
import qualified Data.Map.Strict            as DM
import           Data.Maybe                 ( fromJust, isJust )
import           Math.Algebra.Jack.Internal ( (.^), _betaratio, jackCoeffC
                                            , _N, _isPartition, Partition
                                            , jackCoeffP, jackCoeffQ
                                            , skewSchurLRCoefficients
                                            , isSkewPartition, _fromInt )
import           Math.Algebra.Hspray        ( (*^), (^**^), (^*^), (^+^)
                                            , lone, Spray
                                            , zeroSpray, unitSpray )

-- | Symbolic Jack polynomial

jackPol' 
  :: Int       -- ^ number of variables

  -> Partition -- ^ partition of integers

  -> Rational  -- ^ Jack parameter

  -> Char      -- ^ which Jack polynomial, @'J'@, @'C'@, @'P'@ or @'Q'@

  -> Spray Rational
jackPol' :: Int -> Partition -> Rational -> Char -> Spray Rational
jackPol' = Int -> Partition -> Rational -> Char -> Spray Rational
forall a. (Eq a, C a) => Int -> Partition -> a -> Char -> Spray a
jackPol

-- | Symbolic Jack polynomial

jackPol :: forall a. (Eq a, AlgField.C a)
  => Int       -- ^ number of variables

  -> Partition -- ^ partition of integers

  -> a         -- ^ Jack parameter

  -> Char      -- ^ which Jack polynomial, @'J'@, @'C'@, @'P'@ or @'Q'@

  -> Spray a
jackPol :: forall a. (Eq a, C a) => Int -> Partition -> a -> Char -> Spray a
jackPol Int
n Partition
lambda a
alpha Char
which =
  case Partition -> Bool
_isPartition Partition
lambda of
    Bool
False -> [Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"jackPol: invalid integer partition"
    Bool
True -> case Char
which of 
      Char
'J' -> Spray a
resultJ
      Char
'C' -> Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffC Partition
lambda a
alpha a -> Spray a -> Spray a
forall a v. C a v => a -> v -> v
*> Spray a
resultJ
      Char
'P' -> Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffP Partition
lambda a
alpha a -> Spray a -> Spray a
forall a v. C a v => a -> v -> v
*> Spray a
resultJ
      Char
'Q' -> Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffQ Partition
lambda a
alpha a -> Spray a -> Spray a
forall a v. C a v => a -> v -> v
*> Spray a
resultJ
      Char
_   -> [Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"jackPol: please use 'J', 'C', 'P' or 'Q' for last argument"
      where
      resultJ :: Spray a
resultJ = Int
-> Int
-> Partition
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> a
-> Spray a
jac ([Spray a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Spray a]
x) Int
0 Partition
lambda Partition
lambda Array (Int, Int) (Maybe (Spray a))
forall {a}. Array (Int, Int) (Maybe a)
arr0 a
forall a. C a => a
one
      nll :: Int
nll = Partition -> Partition -> Int
_N Partition
lambda Partition
lambda
      x :: [Spray a]
x = (Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Spray a
forall a. C a => Int -> Spray a
lone [Int
1 .. Int
n] :: [Spray a]
      arr0 :: Array (Int, Int) (Maybe a)
arr0 = ((Int, Int), (Int, Int)) -> [Maybe a] -> Array (Int, Int) (Maybe a)
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray ((Int
1, Int
1), (Int
nll, Int
n)) (Int -> Maybe a -> [Maybe a]
forall a. Int -> a -> [a]
replicate (Int
nll Int -> Int -> Int
forall a. C a => a -> a -> a
* Int
n) Maybe a
forall a. Maybe a
Nothing)
      theproduct :: Int -> a
      theproduct :: Int -> a
theproduct Int
nu0 = if Int
nu0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1
        then a
forall a. C a => a
one
        else [a] -> a
forall a. C a => [a] -> a
product ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ (Int -> a) -> Partition -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
i -> Int
i Int -> a -> a
forall a. C a => Int -> a -> a
.^ a
alpha a -> a -> a
forall a. C a => a -> a -> a
+ a
forall a. C a => a
one) [Int
1 .. Int
nu0Int -> Int -> Int
forall a. C a => a -> a -> a
-Int
1]
      jac :: Int -> Int -> Partition -> Partition -> Array (Int,Int) (Maybe (Spray a)) -> a -> Spray a
      jac :: Int
-> Int
-> Partition
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> a
-> Spray a
jac Int
m Int
k Partition
mu Partition
nu Array (Int, Int) (Maybe (Spray a))
arr a
beta
        | Partition -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Partition
nu Bool -> Bool -> Bool
|| Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Spray a
forall a. C a => Spray a
unitSpray
        | Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
m Bool -> Bool -> Bool
&& Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0      = Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
        | Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1                          = Int -> a
theproduct (Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0) a -> Spray a -> Spray a
forall a. (C a, Eq a) => a -> Spray a -> Spray a
*^ ([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!Int
0 Spray a -> Int -> Spray a
forall a. (C a, Eq a) => Spray a -> Int -> Spray a
^**^ Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0) 
        | Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Maybe (Spray a) -> Bool
forall a. Maybe a -> Bool
isJust (Array (Int, Int) (Maybe (Spray a))
arr Array (Int, Int) (Maybe (Spray a)) -> (Int, Int) -> Maybe (Spray a)
forall i e. Ix i => Array i e -> i -> e
! (Partition -> Partition -> Int
_N Partition
lambda Partition
nu, Int
m)) =
                      Maybe (Spray a) -> Spray a
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Spray a) -> Spray a) -> Maybe (Spray a) -> Spray a
forall a b. (a -> b) -> a -> b
$ Array (Int, Int) (Maybe (Spray a))
arr Array (Int, Int) (Maybe (Spray a)) -> (Int, Int) -> Maybe (Spray a)
forall i e. Ix i => Array i e -> i -> e
! (Partition -> Partition -> Int
_N Partition
lambda Partition
nu, Int
m)
        | Bool
otherwise = Spray a
s
          where
            s :: Spray a
s = Spray a -> Int -> Spray a
go (a
beta a -> Spray a -> Spray a
forall a. (C a, Eq a) => a -> Spray a -> Spray a
*^ (Int
-> Int
-> Partition
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> a
-> Spray a
jac (Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int
0 Partition
nu Partition
nu Array (Int, Int) (Maybe (Spray a))
arr a
forall a. C a => a
one Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^*^ (([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)) Spray a -> Int -> Spray a
forall a. (C a, Eq a) => Spray a -> Int -> Spray a
^**^ (Partition -> Int
forall a. C a => [a] -> a
sum Partition
mu Int -> Int -> Int
forall a. C a => a -> a -> a
- Partition -> Int
forall a. C a => [a] -> a
sum Partition
nu))))
                (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 Int
k)
            go :: Spray a -> Int -> Spray a
            go :: Spray a -> Int -> Spray a
go !Spray a
ss Int
ii
              | Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ii Bool -> Bool -> Bool
|| Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Spray a
ss
              | Bool
otherwise =
                let u :: Int
u = Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) in
                if Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
ii Bool -> Bool -> Bool
&& Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
|| Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
ii
                  then
                    let nu' :: Partition
nu'   = (Int -> IndexedTraversal' Int Partition Int
forall (t :: * -> *) a.
Traversable t =>
Int -> IndexedTraversal' Int (t a) a
element (Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) ((Int -> Identity Int) -> Partition -> Identity Partition)
-> Int -> Partition -> Partition
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
uInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Partition
nu in
                    let gamma :: a
gamma = a
beta a -> a -> a
forall a. C a => a -> a -> a
* Partition -> Partition -> Int -> a -> a
forall a. C a => Partition -> Partition -> Int -> a -> a
_betaratio Partition
mu Partition
nu Int
ii a
alpha in
                    if Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
                      then
                        Spray a -> Int -> Spray a
go (Spray a
ss Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ Int
-> Int
-> Partition
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> a
-> Spray a
jac Int
m Int
ii Partition
mu Partition
nu' Array (Int, Int) (Maybe (Spray a))
arr a
gamma) (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
                      else
                        if Partition
nu'Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
                          then
                            Spray a -> Int -> Spray a
go (Spray a
ss Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ (a
gamma a -> Spray a -> Spray a
forall a. (C a, Eq a) => a -> Spray a -> Spray a
*^ ([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Spray a -> Int -> Spray a
forall a. (C a, Eq a) => Spray a -> Int -> Spray a
^**^ Partition -> Int
forall a. C a => [a] -> a
sum Partition
mu))) (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
                          else
                            let arr' :: Array (Int, Int) (Maybe (Spray a))
arr' = Array (Int, Int) (Maybe (Spray a))
arr Array (Int, Int) (Maybe (Spray a))
-> [((Int, Int), Maybe (Spray a))]
-> Array (Int, Int) (Maybe (Spray a))
forall i e. Ix i => Array i e -> [(i, e)] -> Array i e
// [((Partition -> Partition -> Int
_N Partition
lambda Partition
nu, Int
m), Spray a -> Maybe (Spray a)
forall a. a -> Maybe a
Just Spray a
ss)] in
                            let jck :: Spray a
jck  = Int
-> Int
-> Partition
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> a
-> Spray a
jac (Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int
0 Partition
nu' Partition
nu' Array (Int, Int) (Maybe (Spray a))
arr' a
forall a. C a => a
one in
                            let jck' :: Spray a
jck' = a
gamma a -> Spray a -> Spray a
forall a. (C a, Eq a) => a -> Spray a -> Spray a
*^ (Spray a
jck Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^*^ 
                                        ([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Spray a -> Int -> Spray a
forall a. (C a, Eq a) => Spray a -> Int -> Spray a
^**^ (Partition -> Int
forall a. C a => [a] -> a
sum Partition
mu Int -> Int -> Int
forall a. C a => a -> a -> a
- Partition -> Int
forall a. C a => [a] -> a
sum Partition
nu'))) in
                            Spray a -> Int -> Spray a
go (Spray a
ss Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ Spray a
jck') (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
                  else
                    Spray a -> Int -> Spray a
go Spray a
ss (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)

-- | Symbolic zonal polynomial

zonalPol' 
  :: Int       -- ^ number of variables

  -> Partition -- ^ partition of integers

  -> Spray Rational
zonalPol' :: Int -> Partition -> Spray Rational
zonalPol' = Int -> Partition -> Spray Rational
forall a. (Eq a, C a) => Int -> Partition -> Spray a
zonalPol

-- | Symbolic zonal polynomial

zonalPol :: forall a. (Eq a, AlgField.C a) 
  => Int       -- ^ number of variables

  -> Partition -- ^ partition of integers

  -> Spray a
zonalPol :: forall a. (Eq a, C a) => Int -> Partition -> Spray a
zonalPol Int
n Partition
lambda = 
  Int -> Partition -> a -> Char -> Spray a
forall a. (Eq a, C a) => Int -> Partition -> a -> Char -> Spray a
jackPol Int
n Partition
lambda (Integer -> a
forall a. C a => Integer -> a
fromInteger Integer
2) Char
'C'

-- | Symbolic Schur polynomial

schurPol' 
  :: Int       -- ^ number of variables

  -> Partition -- ^ partition of integers

  -> Spray Rational
schurPol' :: Int -> Partition -> Spray Rational
schurPol' = Int -> Partition -> Spray Rational
forall a. (Ord a, C a) => Int -> Partition -> Spray a
schurPol

-- | Symbolic Schur polynomial

schurPol :: forall a. (Ord a, AlgRing.C a)
  => Int       -- ^ number of variables

  -> Partition -- ^ partition of integers

  -> Spray a
schurPol :: forall a. (Ord a, C a) => Int -> Partition -> Spray a
schurPol Int
n Partition
lambda =
  case Partition -> Bool
_isPartition Partition
lambda of
    Bool
False -> [Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"schurPol: invalid integer partition"
    Bool
True -> Int
-> Int
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> Spray a
sch Int
n Int
1 Partition
lambda Array (Int, Int) (Maybe (Spray a))
forall {a}. Array (Int, Int) (Maybe a)
arr0
      where
        x :: [Spray a]
x = (Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Spray a
forall a. C a => Int -> Spray a
lone [Int
1 .. Int
n] :: [Spray a]
        nll :: Int
nll = Partition -> Partition -> Int
_N Partition
lambda Partition
lambda
        arr0 :: Array (Int, Int) (Maybe a)
arr0 = ((Int, Int), (Int, Int)) -> [Maybe a] -> Array (Int, Int) (Maybe a)
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray ((Int
1, Int
1), (Int
nll, Int
n)) (Int -> Maybe a -> [Maybe a]
forall a. Int -> a -> [a]
replicate (Int
nll Int -> Int -> Int
forall a. C a => a -> a -> a
* Int
n) Maybe a
forall a. Maybe a
Nothing)
        sch :: Int -> Int -> [Int] -> Array (Int,Int) (Maybe (Spray a)) -> Spray a
        sch :: Int
-> Int
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> Spray a
sch Int
m Int
k Partition
nu Array (Int, Int) (Maybe (Spray a))
arr
          | Partition -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Partition
nu Bool -> Bool -> Bool
|| Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Spray a
forall a. C a => Spray a
unitSpray
          | Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
m Bool -> Bool -> Bool
&& Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
          | Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = [Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!Int
0 Spray a -> Int -> Spray a
forall a. (C a, Eq a) => Spray a -> Int -> Spray a
^**^ Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0
          | Maybe (Spray a) -> Bool
forall a. Maybe a -> Bool
isJust (Array (Int, Int) (Maybe (Spray a))
arr Array (Int, Int) (Maybe (Spray a)) -> (Int, Int) -> Maybe (Spray a)
forall i e. Ix i => Array i e -> i -> e
! (Partition -> Partition -> Int
_N Partition
lambda Partition
nu, Int
m)) = Maybe (Spray a) -> Spray a
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Spray a) -> Spray a) -> Maybe (Spray a) -> Spray a
forall a b. (a -> b) -> a -> b
$ Array (Int, Int) (Maybe (Spray a))
arr Array (Int, Int) (Maybe (Spray a)) -> (Int, Int) -> Maybe (Spray a)
forall i e. Ix i => Array i e -> i -> e
! (Partition -> Partition -> Int
_N Partition
lambda Partition
nu, Int
m)
          | Bool
otherwise = Spray a
s
            where
              s :: Spray a
s = Spray a -> Int -> Spray a
go (Int
-> Int
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> Spray a
sch (Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int
1 Partition
nu Array (Int, Int) (Maybe (Spray a))
arr) Int
k
              go :: Spray a -> Int -> Spray a
              go :: Spray a -> Int -> Spray a
go !Spray a
ss Int
ii
                | Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ii Bool -> Bool -> Bool
|| Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Spray a
ss
                | Bool
otherwise =
                  let u :: Int
u = Partition
nuPartition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) in
                  if Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
ii Bool -> Bool -> Bool
&& Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
|| Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Partition
nu Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
ii
                    then
                      let nu' :: Partition
nu' = (Int -> IndexedTraversal' Int Partition Int
forall (t :: * -> *) a.
Traversable t =>
Int -> IndexedTraversal' Int (t a) a
element (Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) ((Int -> Identity Int) -> Partition -> Identity Partition)
-> Int -> Partition -> Partition
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
uInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Partition
nu in
                      if Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
                        then
                          Spray a -> Int -> Spray a
go (Spray a
ss Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ (([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)) Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^*^ Int
-> Int
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> Spray a
sch Int
m Int
ii Partition
nu' Array (Int, Int) (Maybe (Spray a))
arr)) (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
                        else
                          if Partition
nu'Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!!Int
0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
                            then
                              Spray a -> Int -> Spray a
go (Spray a
ss Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ ([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1))) (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
                            else
                              let arr' :: Array (Int, Int) (Maybe (Spray a))
arr' = Array (Int, Int) (Maybe (Spray a))
arr Array (Int, Int) (Maybe (Spray a))
-> [((Int, Int), Maybe (Spray a))]
-> Array (Int, Int) (Maybe (Spray a))
forall i e. Ix i => Array i e -> [(i, e)] -> Array i e
// [((Partition -> Partition -> Int
_N Partition
lambda Partition
nu, Int
m), Spray a -> Maybe (Spray a)
forall a. a -> Maybe a
Just Spray a
ss)] in
                              Spray a -> Int -> Spray a
go (Spray a
ss Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ (([Spray a]
x[Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)) Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^*^ Int
-> Int
-> Partition
-> Array (Int, Int) (Maybe (Spray a))
-> Spray a
sch (Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int
1 Partition
nu' Array (Int, Int) (Maybe (Spray a))
arr')) (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
                    else
                      Spray a -> Int -> Spray a
go Spray a
ss (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)

-- | Symbolic skew Schur polynomial

skewSchurPol' 
  :: Int       -- ^ number of variables

  -> Partition -- ^ outer partition of the skew partition

  -> Partition -- ^ inner partition of the skew partition

  -> Spray Rational
skewSchurPol' :: Int -> Partition -> Partition -> Spray Rational
skewSchurPol' = Int -> Partition -> Partition -> Spray Rational
forall a. (Ord a, C a) => Int -> Partition -> Partition -> Spray a
skewSchurPol

-- | Symbolic skew Schur polynomial

skewSchurPol :: forall a. (Ord a, AlgRing.C a)
  => Int       -- ^ number of variables

  -> Partition -- ^ outer partition of the skew partition

  -> Partition -- ^ inner partition of the skew partition

  -> Spray a
skewSchurPol :: forall a. (Ord a, C a) => Int -> Partition -> Partition -> Spray a
skewSchurPol Int
n Partition
lambda Partition
mu =
  case Partition -> Partition -> Bool
isSkewPartition Partition
lambda Partition
mu of
    Bool
False -> [Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"skewSchurPol: invalid skew partition"
    Bool
True  -> (Spray a -> Partition -> Int -> Spray a)
-> Spray a -> Map Partition Int -> Spray a
forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
DM.foldlWithKey' Spray a -> Partition -> Int -> Spray a
f Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray Map Partition Int
lrCoefficients
  where
    lrCoefficients :: Map Partition Int
lrCoefficients = Partition -> Partition -> Map Partition Int
skewSchurLRCoefficients Partition
lambda Partition
mu
    f :: Spray a -> Partition -> Int -> Spray a
    f :: Spray a -> Partition -> Int -> Spray a
f Spray a
spray Partition
nu Int
k = Spray a
spray Spray a -> Spray a -> Spray a
forall a. (C a, Eq a) => Spray a -> Spray a -> Spray a
^+^ (Int -> a
_fromInt' Int
k) a -> Spray a -> Spray a
forall a v. C a v => a -> v -> v
AlgMod.*> (Int -> Partition -> Spray a
forall a. (Ord a, C a) => Int -> Partition -> Spray a
schurPol Int
n Partition
nu)
    _fromInt' :: Int -> a
    _fromInt' :: Int -> a
_fromInt' = Int -> a
forall a. C a => Int -> a
_fromInt