New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 13540 for NEMO/branches/2020/r12377_ticket2386/src/OCE/STO/stopar.F90 – NEMO

Ignore:
Timestamp:
2020-09-29T12:41:06+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2386: update to latest trunk

Location:
NEMO/branches/2020/r12377_ticket2386
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r12377_ticket2386

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
        88 
        99# SETTE 
        10 ^/utils/CI/sette@HEAD         sette 
         10^/utils/CI/sette@13507        sette 
  • NEMO/branches/2020/r12377_ticket2386/src/OCE/STO/stopar.F90

    r12377 r13540  
    5656   INTEGER,          DIMENSION(:),       ALLOCATABLE :: sto3d_ord  ! order of autoregressive process 
    5757 
    58    CHARACTER(len=1), DIMENSION(:),       ALLOCATABLE :: sto2d_typ  ! nature of grid point (T, U, V, W, F, I) 
    59    CHARACTER(len=1), DIMENSION(:),       ALLOCATABLE :: sto3d_typ  ! nature of grid point (T, U, V, W, F, I) 
     58   CHARACTER(len=lca), DIMENSION(:),       ALLOCATABLE :: sto2d_typ  ! nature of grid point (T, U, V, W, F, I) 
     59   CHARACTER(len=lca), DIMENSION(:),       ALLOCATABLE :: sto3d_typ  ! nature of grid point (T, U, V, W, F, I) 
    6060   REAL(wp),         DIMENSION(:),       ALLOCATABLE :: sto2d_sgn  ! control of the sign accross the north fold 
    6161   REAL(wp),         DIMENSION(:),       ALLOCATABLE :: sto3d_sgn  ! control of the sign accross the north fold 
     
    684684      !! ** Purpose :   read stochastic parameters from restart file 
    685685      !!---------------------------------------------------------------------- 
    686       INTEGER  :: jsto, jseed 
     686      INTEGER             ::   jsto, jseed 
     687      INTEGER             ::   idg                 ! number of digits 
    687688      INTEGER(KIND=8)     ::   ziseed(4)           ! RNG seeds in integer type 
    688       REAL(KIND=8)        ::   zrseed(4)           ! RNG seeds in real type (with same bits to save in restart) 
     689      REAL(KIND=dp)       ::   zrseed(4)           ! RNG seeds in double-precision (with same bits to save in restart) 
    689690      CHARACTER(LEN=9)    ::   clsto2d='sto2d_000' ! stochastic parameter variable name 
    690691      CHARACTER(LEN=9)    ::   clsto3d='sto3d_000' ! stochastic parameter variable name 
    691       CHARACTER(LEN=10)   ::   clseed='seed0_0000' ! seed variable name 
     692      CHARACTER(LEN=15)   ::   clseed='seed0_0000' ! seed variable name 
     693      CHARACTER(LEN=6)    ::   clfmt               ! writing format 
    692694      !!---------------------------------------------------------------------- 
    693695 
     
    707709         DO jsto = 1 , jpsto2d 
    708710            WRITE(clsto2d(7:9),'(i3.3)') jsto 
    709             CALL iom_get( numstor, jpdom_autoglo, clsto2d , sto2d(:,:,jsto) ) 
     711            CALL iom_get( numstor, jpdom_auto, clsto2d, sto2d(:,:,  jsto) ) 
    710712         END DO 
    711713         ! 3D stochastic parameters 
    712714         DO jsto = 1 , jpsto3d 
    713715            WRITE(clsto3d(7:9),'(i3.3)') jsto 
    714             CALL iom_get( numstor, jpdom_autoglo, clsto3d , sto3d(:,:,:,jsto) ) 
     716            CALL iom_get( numstor, jpdom_auto, clsto3d, sto3d(:,:,:,jsto) ) 
    715717         END DO 
    716718 
    717719         IF (ln_rstseed) THEN 
    718720            ! Get saved state of the random number generator 
     721            idg = MAX( INT(LOG10(REAL(jpnij,wp))) + 1, 4 )        ! how many digits to we need to write? min=4, max=9 
     722            WRITE(clfmt, "('(i', i1, '.', i1, ')')") idg, idg     ! "(ix.x)" 
    719723            DO jseed = 1 , 4 
    720                WRITE(clseed(5:5) ,'(i1.1)') jseed 
    721                WRITE(clseed(7:10),'(i4.4)') narea 
    722                CALL iom_get( numstor, clseed , zrseed(jseed) ) 
     724               WRITE(clseed(5:5)      ,'(i1.1)') jseed 
     725               WRITE(clseed(7:7+idg-1),  clfmt ) narea 
     726               CALL iom_get( numstor, clseed(1:7+idg-1) , zrseed(jseed) ) 
    723727            END DO 
    724728            ziseed = TRANSFER( zrseed , ziseed) 
     
    742746      INTEGER, INTENT(in) ::   kt     ! ocean time-step 
    743747      !! 
    744       INTEGER  :: jsto, jseed 
     748      INTEGER             ::   jsto, jseed 
     749      INTEGER             ::   idg                 ! number of digits 
    745750      INTEGER(KIND=8)     ::   ziseed(4)           ! RNG seeds in integer type 
    746       REAL(KIND=8)        ::   zrseed(4)           ! RNG seeds in real type (with same bits to save in restart) 
     751      REAL(KIND=dp)       ::   zrseed(4)           ! RNG seeds in double-precision (with same bits to save in restart) 
    747752      CHARACTER(LEN=20)   ::   clkt                ! ocean time-step defined as a character 
    748753      CHARACTER(LEN=50)   ::   clname              ! restart file name 
    749754      CHARACTER(LEN=9)    ::   clsto2d='sto2d_000' ! stochastic parameter variable name 
    750755      CHARACTER(LEN=9)    ::   clsto3d='sto3d_000' ! stochastic parameter variable name 
    751       CHARACTER(LEN=10)   ::   clseed='seed0_0000' ! seed variable name 
     756      CHARACTER(LEN=15)   ::   clseed='seed0_0000' ! seed variable name 
     757      CHARACTER(LEN=6)    ::   clfmt               ! writing format 
    752758      !!---------------------------------------------------------------------- 
    753759 
     
    771777            CALL kiss_state( ziseed(1) , ziseed(2) , ziseed(3) , ziseed(4) ) 
    772778            zrseed = TRANSFER( ziseed , zrseed) 
     779            idg = MAX( INT(LOG10(REAL(jpnij,wp))) + 1, 4 )        ! how many digits to we need to write? min=4, max=9 
     780            WRITE(clfmt, "('(i', i1, '.', i1, ')')") idg, idg     ! "(ix.x)" 
    773781            DO jseed = 1 , 4 
    774                WRITE(clseed(5:5) ,'(i1.1)') jseed 
    775                WRITE(clseed(7:10),'(i4.4)') narea 
    776                CALL iom_rstput( kt, nitrst, numstow, clseed , zrseed(jseed) ) 
     782               WRITE(clseed(5:5)      ,'(i1.1)') jseed 
     783               WRITE(clseed(7:7+idg-1),  clfmt ) narea 
     784               CALL iom_rstput( kt, nitrst, numstow, clseed(1:7+idg-1), zrseed(jseed) ) 
    777785            END DO 
    778786            ! 2D stochastic parameters 
     
    827835      !! 
    828836      INTEGER  :: ji, jj 
    829       REAL(KIND=8) :: gran   ! Gaussian random number (forced KIND=8 as in kiss_gaussian) 
    830  
    831       DO_2D_11_11 
     837      REAL(wp) :: gran   ! Gaussian random number (forced KIND=8 as in kiss_gaussian) 
     838 
     839      DO_2D( 1, 1, 1, 1 ) 
    832840         CALL kiss_gaussian( gran ) 
    833841         psto(ji,jj) = gran 
     
    847855      INTEGER  :: ji, jj 
    848856 
    849       DO_2D_00_00 
     857      DO_2D( 0, 0, 0, 0 ) 
    850858         psto(ji,jj) = 0.5_wp * psto(ji,jj) + 0.125_wp * & 
    851859                           &  ( psto(ji-1,jj) + psto(ji+1,jj) +  & 
Note: See TracChangeset for help on using the changeset viewer.