43#if defined PIO_LIB && defined DISTRIBUTE
95 logical,
intent(inout) :: first
97 integer,
intent(in),
optional :: mpiCOMM
101 logical :: allocate_vars = .true.
104 integer :: MyError, MySize
106 integer :: chunk_size, ng, thread
108 integer :: my_threadnum
111 character (len=*),
parameter :: MyFile = &
112 & __FILE__//
", ROMS_initialize"
120 IF (
PRESENT(mpicomm))
THEN
170#elif defined DISTRIBUTE
187 10
FORMAT (/,
' Process Information:',/)
191 DO thread=thread_range
204#if defined MCT_LIB && (defined ATM_COUPLING || defined WAV_COUPLING)
212 CALL initialize_ocn2atm_coupling (ng,
myrank)
215 CALL initialize_ocn2wav_coupling (ng,
myrank)
346 real(dp),
intent(in) :: RunInterval
350 logical :: ITERATE, Lcomplex
355 integer :: Fcount, Is, Ie, i, icount, iter, ng, srec
356 integer :: NconvRitz(Ngrids)
360 TYPE (T_GST),
allocatable :: ad_state(:)
361 TYPE (T_GST),
allocatable :: state(:)
363 character (len=55) :: string
365 character (len=*),
parameter :: MyFile = &
366 & __FILE__//
", ROMS_run"
375 IF (.not.
allocated(ad_state))
THEN
376 allocate ( ad_state(ngrids) )
378 IF (.not.
allocated(state))
THEN
379 allocate ( state(ngrids) )
391 iter_loop :
DO WHILE (iterate)
430 & (any(
ido.eq.99)))
THEN
448 IF (any(abs(
ido).eq.1))
THEN
451 adm(ng)%Nrec(fcount)=0
459 IF (
ASSOCIATED(state(ng)%vector))
THEN
460 nullify (state(ng)%vector)
464 state(ng)%vector =>
storage(ng)%SworkD(is:ie)
466 IF (
ASSOCIATED(ad_state(ng)%vector))
THEN
467 nullify (ad_state(ng)%vector)
471 ad_state(ng)%vector =>
storage(ng)%SworkD(is:ie)
478 IF (any(
info.ne.0))
THEN
480 IF (
info(ng).ne.0)
THEN
483 WRITE (
stdout,10)
'DNAUPD', trim(string), &
484 &
', info = ',
info(ng)
496 nconvritz(ng)=
iparam(5,ng)
498 WRITE (
stdout,20)
'Number of converged Ritz values:', &
500 WRITE (
stdout,20)
'Number of Arnoldi iterations:', &
537 IF (any(
info.ne.0))
THEN
539 IF (
info(ng).ne.0)
THEN
542 WRITE (
stdout,10)
'DNEUPD', trim(string), &
543 &
', info = ',
info(ng)
557 DO i=1,maxval(nconvritz)
561 adm(ng)%Nrec(fcount)=0
567 WRITE (
adm(ng)%name,30) trim(
adm(ng)%base), icount
573 IF (any(
rvaluei(i,:).eq.0.0_r8))
THEN
580 IF (
ASSOCIATED(state(ng)%vector))
THEN
581 nullify (state(ng)%vector)
584 IF (
ASSOCIATED(ad_state(ng)%vector))
THEN
585 nullify (ad_state(ng)%vector)
587 state(ng)%vector =>
storage(ng)%Rvector(is:ie,i)
588 ad_state(ng)%vector =>
sworkr(is:ie)
593 & __line__, myfile))
RETURN
598 & state(ng)%vector, &
599 & ad_state(ng)%vector, enorm)
603 ELSE IF (lcomplex)
THEN
610 IF (
ASSOCIATED(state(ng)%vector))
THEN
611 nullify (state(ng)%vector)
614 IF (
ASSOCIATED(ad_state(ng)%vector))
THEN
615 nullify (ad_state(ng)%vector)
617 state(ng)%vector =>
storage(ng)%Rvector(is:ie,i)
618 ad_state(ng)%vector =>
sworkr(is:ie)
623 & __line__, myfile))
RETURN
630 & ad_state(ng)%vector, enorm)
637 IF (
ASSOCIATED(state(ng)%vector))
THEN
638 nullify (state(ng)%vector)
641 IF (
ASSOCIATED(ad_state(ng)%vector))
THEN
642 nullify (ad_state(ng)%vector)
644 state(ng)%vector =>
storage(ng)%Rvector(is:ie,i+1)
645 ad_state(ng)%vector =>
sworkr(is:ie)
650 & __line__, myfile))
RETURN
657 & ad_state(ng)%vector, enorm)
679 IF (.not.lcomplex.or.(
rvaluei(i,ng).eq.0.0_r8))
THEN
689 SELECT CASE (
adm(ng)%IOtype)
695 & start = (/srec/), &
697 & ncid =
adm(ng)%ncid)
700 & __line__, myfile))
RETURN
706 & start = (/srec/), &
708 & ncid =
adm(ng)%ncid)
711 & __line__, myfile))
RETURN
717 & start = (/srec/), &
719 & ncid =
adm(ng)%ncid)
722 & __line__, myfile))
RETURN
724#if defined PIO_LIB && defined DISTRIBUTE
730 & start = (/srec/), &
732 & piofile =
adm(ng)%pioFile)
735 & __line__, myfile))
RETURN
741 & start = (/srec/), &
743 & piofile =
adm(ng)%pioFile)
746 & __line__, myfile))
RETURN
752 & start = (/srec/), &
754 & piofile =
adm(ng)%pioFile)
757 & __line__, myfile))
RETURN
764 & __line__, myfile))
RETURN
776 10
FORMAT (/,1x,
'Error in ',a,1x,a,a,1x,i5,/)
777 20
FORMAT (/,a,1x,i2,/)
778 30
FORMAT (a,
'_',i3.3,
'.nc')
779 40
FORMAT (1x,i4.4,
'-th residual',1p,e14.6,0p, &
780 &
' Ritz values',1pe14.6,0p,1x,1pe14.6,2x,i4.4)
796 integer :: Fcount, ng, thread
798 character (len=*),
parameter :: MyFile = &
799 & __FILE__//
", ROMS_finalize"
811 10
FORMAT (/,
' Blowing-up: Saving latest model state into ', &
838 20
FORMAT (/,
'Elapsed wall CPU time for each process (seconds):',/)
842 DO thread=thread_range
873 integer,
intent(in) ::
info, icall
875 character (len=*),
intent(out) :: string
882 string=
'Normal exit '
883 ELSE IF (
info.eq.1)
THEN
885 string=
'Maximum number of iterations taken '
887 string=
'Could not reorder Schur vectors '
889 ELSE IF (
info.eq.3)
THEN
890 string=
'No shifts could be applied during an IRAM cycle '
891 ELSE IF (
info.eq.-1)
THEN
892 string=
'Nstate must be positive '
893 ELSE IF (
info.eq.-2)
THEN
894 string=
'NEV must be positive '
895 ELSE IF (
info.eq.-3)
THEN
896 string=
'NCV must be greater NEV and less than or equal Nstate '
897 ELSE IF (
info.eq.-4)
THEN
898 string=
'Maximum number of iterations must be greater than zero '
899 ELSE IF (
info.eq.-5)
THEN
900 string=
'WHICH must be one of LM, SM, LA, SA or BE '
901 ELSE IF (
info.eq.-6)
THEN
902 string=
'BMAT must be one of I or G '
903 ELSE IF (
info.eq.-7)
THEN
904 string=
'Length of private work array SworkL is not sufficient '
905 ELSE IF (
info.eq.-8)
THEN
907 string=
'Error return from LAPACK eigenvalue calculation '
909 string=
'Error in DLAHQR in the Shurn vectors calculation '
911 ELSE IF (
info.eq.-9)
THEN
913 string=
'Starting vector is zero'
915 string=
'Error in DTREVC in the eigenvectors calculation '
917 ELSE IF (
info.eq.-10)
THEN
918 string=
'IPARAM(7) must be 1, 2, 3, 4, 5 '
919 ELSE IF (
info.eq.-11)
THEN
920 string=
'IPARAM(7) = 1 and BMAT = G are incompatable '
921 ELSE IF (
info.eq.-12)
THEN
923 string=
'IPARAM(1) must be equal to 0 or 1 '
925 string=
'HOWMANY = S not yet implemented '
927 ELSE IF (
info.eq.-13)
THEN
928 string=
'HOWMANY must be one of A or P if Lrvec = .TRUE. '
929 ELSE IF (
info.eq.-14)
THEN
930 string=
'Did not find any eigenvalues to sufficient accuaracy '
931 ELSE IF (
info.eq.-15)
THEN
932 string=
'Different count of converge Ritz values in DNEUPD '
933 ELSE IF (
info.eq.-9999)
THEN
934 string=
'Could not build and Arnoldi factorization '
subroutine ad_initial(ng)
subroutine edit_multifile(task)
subroutine, public close_out
subroutine, public close_file(ng, model, s, ncname, lupdate)
subroutine, public close_inp(ng, model)
subroutine, public def_gst(ng, model)
subroutine, public get_gst(ng, model)
subroutine, public inp_par(model)
subroutine, public roms_initialize_arrays
subroutine, public roms_allocate_arrays(allocate_vars)
type(t_io), dimension(:), allocatable adm
type(t_io), dimension(:), allocatable rst
character(len=256) sourcefile
integer, parameter io_nf90
integer, parameter io_pio
subroutine, public initialize_parallel
integer, dimension(:), allocatable first_tile
integer, dimension(:), allocatable last_tile
integer, dimension(:), allocatable nstr
integer, dimension(:), allocatable ntilex
integer, dimension(:), allocatable nsize
integer, dimension(:), allocatable ntilee
integer, dimension(:), allocatable nend
integer, dimension(:), allocatable ntimes
integer, dimension(:), allocatable nconv
logical, dimension(:), allocatable lreadfrc
logical, dimension(:), allocatable ldefadj
logical, dimension(:), allocatable lcycleadj
logical, dimension(:), allocatable lwrtadj
logical, dimension(:), allocatable lwrtper
logical, dimension(:), allocatable lwrtrst
integer, dimension(:), allocatable nadj
logical, dimension(:), allocatable lreadfwd
logical, dimension(:), allocatable lcyclerst
logical, dimension(:), allocatable lreadblk
integer, dimension(8) iaup2
integer, dimension(:), allocatable ido
real(r8), dimension(:,:), allocatable rvaluei
real(r8), dimension(:,:), allocatable sworkl
integer, dimension(:,:), allocatable ipntr
real(r8), dimension(:,:), allocatable sworkev
type(t_storage), dimension(:), allocatable storage
real(r8), dimension(:,:), allocatable norm
integer, dimension(:), allocatable info
subroutine, public allocate_storage
integer, dimension(:,:), allocatable iparam
logical, dimension(:,:), allocatable pick
real(r8), dimension(:), pointer sworkr
real(r8), dimension(:,:), allocatable rvaluer
subroutine, public propagator_afte(runinterval, state, ad_state)
subroutine, public roms_finalize
subroutine, public roms_run(runinterval)
subroutine, private iram_error(info, icall, string)
subroutine, public roms_initialize(first, mpicomm)
integer function, public stdout_unit(mymaster)
logical, save set_stdoutunit
logical function, public founderror(flag, noerr, line, routine)
subroutine, public wrt_gst(ng, model)
subroutine, public wrt_rst(ng, tile)
subroutine c_norm2(ng, model, mstr, mend, evaluer, evaluei, evectorr, evectori, state, norm2)
subroutine r_norm2(ng, model, mstr, mend, evalue, evector, state, norm2)
recursive subroutine wclock_off(ng, model, region, line, routine)
recursive subroutine wclock_on(ng, model, region, line, routine)