jj1gujのブログ

アイコン画像は音速の奇行子 様よりいただきました

ABC232 をFortranで解く(A問題~D問題)

コンテスト中のFortranでの提出がぼくのB問題だけだったのでD問題までFortranで解き直しました.
ちなみにE問題から後ろは筆者の実力がないので解いていないです…

A問題 - QQ solver

コンテスト中はPythonで通しました. Pythonだと楽勝なのですがFortranだとかなりめんどくさいです.
Fortranを日常的に使わない茶色以上の人たちはPythonとかC++とかもっと書きやすい言語に逃げるのが得策だと思います. 解説にもある通りcharacter型の"0"から引き算をして"0"よりいくつ大きいかを計算してあげるといいと思います.
Fortranの場合cchar型の変数とした時, C++みたいにc-'0'と書くとおこられるのでichar()を使いましょう.
実装

program main
    implicit none
    integer::i=ichar("0")
    character(3) S
    read*,S
    print'(i0)',(ichar(S(1:1))-i)*(ichar(S(3:3))-i)
end program main

提出

atcoder.jp

B問題 - Caesar Cipher

まあまあ典型です. Kは0~26のいずれかなので全探索して一致するか見てしまえば終わりです.
FortranだとアルファベットをK個後ろにずらすという操作がまあまあ面倒です. ccharacter(1)型の変数としたときに愚直にchar(ichar(c)+K)とすると例えばc="z"K=1だったときに"a"ではなく"{"になってしまい, 大変なことになってしまいます.
そこで, まずc"a"から何文字後ろの文字なのかを見て, そこからKだけ後ろにしてあげるという処理を行います. これに26で割ったあまりを取ってあげることで必ず0~26のいずれかの値になり, 必ず"a"~"z"のいずれかになってくれます.
下の実装のうちref=mod(ichar(S(j:j))-97+i,26)ichar(S(j:j))から97を引いているのはichar("a")が97だからです.

実装

program main
    implicit none
    integer i,j,ref
    character(100000)S,T
    logical flg
    
    read*,S,T
    do i=0,26
        flg=.true.
        do j=1,len_trim(S)
            ref=mod(ichar(S(j:j))-97+i,26)
            if(char(97+ref)/=T(j:j))then
                flg=.false.
                exit
            end if
        end do
        if(flg)exit
    end do

    if(flg)then
        print'(A)',"Yes"
    else
        print'(A)',"No"
    end if
end program main

提出

atcoder.jp

C問題 - Graph Isomorphism

考察パートは特に難しくなく, 一瞬で全探索が浮かぶのですがFortranでの実装がかなり面倒です. コンテスト中は素直にC++とかPythonのように順列を生成するライブラリが実装されている言語を使用しましょう() ぼくもコンテスト中はPythonで書きました. 当然Fortranには順列を生成するライブラリはないので自分で実装しました.

!pythonのitertools.permutationsのFortran版のようなもの
module permutations_values
    implicit none
    integer(8)::cnt=1,l_len=10**8
end module permutations_values
program main
    use permutations_values
    implicit none
    integer(8)N,i
    integer(8),allocatable::L(:,:),A(:)
    read*,N
    allocate(A(N))
    allocate(L(l_len,N))
    do i=1,N
        A(i)=i
    end do
    !第2引数に生成したい順列の長さ,
    !第3引数に順列を生成したい配列(1~Nまでの順列なら1~Nの配列),
    !第4引数に結果を格納する配列を入れる
    call permutations(1_8,N,A,L)
    print'(i0)',cnt
    do i=1,cnt
        print*,L(i,1:N)
    end do
end program main

recursive subroutine permutations(k,n,a,L)
    use permutations_values
    implicit none
    integer(8),intent(inout)::n,a(1:n),L(1:l_len,1:n)
    integer(8) i,tmp,k

    if(k==n)then
        L(cnt,:)=a
        cnt=cnt+1
    else
        do i=k,n
            tmp=a(k)
            a(k)=a(i)
            a(i)=tmp
            call permutations(k+1_8,n,a,L)
            tmp=a(k)
            a(k)=a(i)
            a(i)=tmp
        end do    
    end if
    return
end subroutine permutations

これが完成すればもう8割は解けたようなもので, グラフを隣接行列で管理して, 高橋くんのグラフと青木くんのグラフが完全に一致するか判定してあげれば終わりです.

実装

module permutations_values
    implicit none
    integer(8)::cnt=0,l_len=10**5
end module permutations_values
program main
    use permutations_values
    implicit none
    integer(8)N,i,M,a,b,j,k
    integer(8),allocatable::P(:,:),ref(:)
    integer(8),allocatable::L1(:,:),L2(:,:),E(:,:)
    logical flg,ans
    read*,N,M
    allocate(L1(N,N))
    allocate(L2(N,N))
    allocate(E(M,2))
    L1=0

    do i=1,M
        !高橋くんが持っているグラフの隣接行列を作る
        read*,a,b
        L1(a,b)=1
        L1(b,a)=1
    end do

    do i=1,M
        read*,E(i,:)
    end do

    !順列を生成する
    allocate(ref(N))
    allocate(P(l_len,N))
    do i=1,N
        ref(i)=i
    end do
    !第2引数に生成したい順列の長さ,
    !第3引数に順列を生成したい配列(1~Nまでの順列なら1~Nの配列),
    !第4引数に結果を格納する配列を入れる
    call permutations(1_8,N,ref,P)

    do i=1,cnt
        !数列Pを順番に変えて青木くんの隣接行列を作り, 高橋くんのグラフと一致するか見る
        ans=.false.
        !青木くんの隣接行列を構成する
        L2=0
        do j=1,M
            L2(P(i,E(j,1)),P(i,E(j,2)))=1
            L2(P(i,E(j,2)),P(i,E(j,1)))=1
        end do

        !青木くんの隣接行列が高橋くんの隣接行列と一致するか見る
        flg=.true.
        do j=1,N
            do k=1,N
                if(L1(j,k)/=L2(j,k))then
                    flg=.false.
                    exit
                end if
            end do
            if(.not.flg)exit
        end do

        !完全に一致したならループから抜ける
        if(flg)then
            ans=.true.
            exit
        end if
    end do

    if(flg)then
        print'(A)',"Yes"
    else
        print'(A)',"No"
    end if
end program main

recursive subroutine permutations(k,n,a,L)
    use permutations_values
    implicit none
    integer(8),intent(inout)::n,a(1:n),L(1:l_len,1:n)
    integer(8) i,tmp,k

    if(k==n)then
        cnt=cnt+1
        L(cnt,:)=a
    else
        do i=k,n
            tmp=a(k)
            a(k)=a(i)
            a(i)=tmp
            call permutations(k+1_8,n,a,L)
            tmp=a(k)
            a(k)=a(i)
            a(i)=tmp
        end do    
    end if
    return
end subroutine permutations

3行目のl_lenを小さくしているのは, メモリ確保に失敗してREになったからです.

提出

atcoder.jp

D問題 - Weak Takahashi

これも考察は難しくなくて, とりあえずBFSしてスタートから最も遠い距離を出力してしまえばいいです. コンテスト中はqueueのライブラリ確か持ってないな~って思ってPythonに逃げたのですが, 自分のライブラリ見たらちゃんとFortranでqueueを実装したライブラリがありました… しかもご丁寧にBFSも実装してた…(なおコメントアウトが全く無くて解読するのが辛かった)

実装

!queueとBFS
program main
    implicit none
    type::auto
        integer(8)::y,x !xが行, yが列に対応
    end type auto
    integer(8)::elements=10**8
    integer(8)::top=1,tail=1,len=0
    type(auto),allocatable::que(:)

    integer(8)::dy(2)=(/0,1/)
    integer(8)::dx(2)=(/1,0/)
    type(auto) cn,nn
    integer(8)::H,W,ans=0
    integer(8)i
    integer(8),allocatable::dist(:,:)
    character(100),allocatable::S(:)
    allocate(que(elements))
    
    read*,H,W
    allocate(dist(H,W))
    dist=-1
    allocate(S(H))

    do i=1,H
        read*,S(i)
    end do
    dist(1,1)=1
    cn%x=1
    cn%y=1
    call push(que,cn)

    do while(len>0)
        cn=pop(que)
        do i=1,2
            nn%x=cn%x+dx(i)
            nn%y=cn%y+dy(i)
            if(nn%x>=1.and.nn%x<=H.and.nn%y>=1.and.nn%y<=W.and.S(nn%x)(nn%y:nn%y)==".".and.dist(nn%x,nn%y)==-1)then
                dist(nn%x,nn%y)=dist(cn%x,cn%y)+1
                call push(que,nn)
            end if
        end do
    end do

    do i=1,H
        ans=max(ans,maxval(dist(i,:)))
    end do
    print'(i0)',ans
contains
subroutine push(L,a)
    implicit none
    type(auto),intent(inout)::L(:)
    type(auto),intent(in)::a
    L(tail)=a
    tail=tail+1
    if(tail>elements)tail=tail-elements
    len=len+1
end subroutine push

type(auto) function pop(L)
    implicit none
    type(auto),intent(inout)::L(:)
    pop=L(top)
    top=top+1
    if(top>elements)top=top-elements
    len=len-1
    return
end function pop
end program main

提出

atcoder.jp

最後に

久しぶりにABC出たんですが, Fortranユーザーに優しくない問題が多すぎないか…?*1*2
あといい加減Fortran版APG4b完成させなさい

*1:そもそもAtCoderFortranユーザー少ないから仕方ない

*2:もともとFortranユーザーに優しくない問題が多い説はある