fortran66のブログ

fortran について書きます。

Kostka number

あるヤング図に対応する半標準ヤング盤から特定の項を抜き出して個数を数えると、シューア関数と単項対称式の変換行列の行列要素が得られます。この数をコストカ数と言います。特定の項の抜き出しは、単項対称式式に対応する半標準ヤング盤を指定することで定まります。

ある次数のシューア関数と単項対称式の変換行列が求まったとすると、基本的な行列操作(逆行列、転値等)で、基本対称式(elementary symmetric polynomial)、同次(完全)対称式 (homogeneous symmetric polynomial)、べき和対称式(power sum symmetric polynomial)、忘れられた対称式(forgotten symmetric polynomial)を含む6つの対称式の完全系間の変換行列が求められます。

I.G.MacDonald, symmetric functions and Hall polynomials, p.101.

  e h m f s
e 1 K'JK^* K'JK K'K K'J
h K'JK^* 1 K'K K'JK K'
m K^-1JK^* K^-1K^* 1 K^-1JK K^-1
f K'K^* K^-1JK^* K^-1JK 1 K^-1J
s JK^* K^* K JK 1



X'=(X)^+、 J_a,b=delta_a',b、X^*=(X^-1)^+


実行結果

λ=(3),μ=(3)  K_{\lambda,\mu}=1
 1 1 1

 total number of tableaux = 1
λ=(3),μ=(2,1)  K_{\lambda,\mu}=1
 1 1 2

 total number of tableaux = 1
λ=(3),μ=(1,1,1)  K_{\lambda,\mu}=1
 1 2 3

 total number of tableaux = 1
λ=(2,1),μ=(3)  K_{\lambda,\mu}=0

λ=(2,1),μ=(2,1)  K_{\lambda,\mu}=1
 1 1
 2

 total number of tableaux = 1
λ=(2,1),μ=(1,1,1)  K_{\lambda,\mu}=2
 1 2
 3

 1 3
 2

 total number of tableaux = 2
λ=(1,1,1),μ=(3)  K_{\lambda,\mu}=0

λ=(1,1,1),μ=(2,1)  K_{\lambda,\mu}=0

λ=(1,1,1),μ=(1,1,1)  K_{\lambda,\mu}=1
 1
 2
 3

 total number of tableaux = 1

以上の結果より、シューア関数と単項対称式の変換行列は、

      m_μ  
    (3) (2,1) (1,1,1)
  (3) 1 1 1
s_λ (2,1) 0 1 2
  (1,1,1) 0 0 1

ソース・プログラム

大好きなラベルとジャンプを使う。よくチェックしてないw

module m_kostka
  implicit none
  type :: t_box
    integer :: k, ix, iy  
  end type t_box
contains
  recursive subroutine ssyt(n, nd, table, list)
    integer, intent(in) :: n, nd
    integer, intent(in out) :: table(0:, 0:)
    type(t_box), intent(in) :: list(:)
    integer :: ix, iy, k
    if (size(list) == n) then
      write(9, *) list
    else
      do iy = 1, ubound(table, 2)
        if (any( table(:, iy - 1) == 0 )) exit
        do ix = 1, ubound(table, 1)
          do k = 1, nd
            if (is_ok(ix, iy)) then
              table(ix, iy) = k
              call ssyt(n, nd, table, [list, t_box(k, ix, iy)])
              table(ix, iy) = 0
            end if
          end do
        end do
      end do
    end if
    return
  contains 
    logical function is_ok(ix, iy)
      integer, intent(in) :: ix, iy
      if (table(ix, iy) == 0 .and. &
          table(ix - 1, iy) <= k .and. table(ix - 1, iy) /= 0 .and. &
          table(ix, iy - 1) <  k .and. table(ix, iy - 1) /= 0 ) then
        is_ok = .true.
      else
        is_ok = .false.
      end if  
      return
    end function is_ok
  end subroutine ssyt

  subroutine kostka_number(n, mu)
    implicit none
    integer, intent(in) :: n, mu(:)
    type(t_box) :: list(n)
    integer :: tableau(n, n)
    integer :: i, k
    k = 0
main:do 
      read(9, *, end = 999) list
      tableau = 0
      do i = 1, size(list)
        tableau(list(i)%ix, list(i)%iy) = list(i)%k
      end do
      do i = 1, size(mu)
        if (count(tableau == i) /= mu(i)) cycle main
      end do
      do i = 1, n
        if ( all(tableau(:, i) == 0) ) exit
        write(*, '(*(i2))') pack(tableau(:, i), tableau(:, i) /= 0)
      end do
      k = k + 1
      write(*, *) 
    end do main    
999 write(*, *) 'total number of tableaux =', k
    return
  end subroutine kostka_number
end module m_kostka

program Kostka
  use m_kostka
  implicit none
  integer, allocatable :: lambda(:), table(:, :), mu(:)
  type(t_box), allocatable :: list(:)
  integer :: n
  lambda = [3,1]
  mu = [2,1,1]
  n = sum(lambda)
  allocate( list(0) )
  call init_table(lambda)
  call ssyt(n, n, 1, table, list)
  rewind(9)
  call kostka_number(n, mu)
  stop
contains 
  subroutine init_table(lambda)
    integer, intent(in) :: lambda(:)
    integer, parameter :: NG = huge(0)
    integer :: i
    allocate( table(0:maxval(lambda, 1), 0:size(lambda)) )
    table = NG
    table(0, :) = -1
    table(:, 0) = -1
    do i = 1, size(lambda)
      table(1:lambda(i), i) = 0  
    end do
    return
  end subroutine init_table
end program Kostka