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 15015 for NEMO/branches/2021/ticket2680_C1D_PAPA/tests/ISOMIP+/MY_SRC/istate.F90 – NEMO

Ignore:
Timestamp:
2021-06-17T19:17:25+02:00 (3 years ago)
Author:
gsamson
Message:

merge trunk into branch (#2680)

Location:
NEMO/branches/2021/ticket2680_C1D_PAPA
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/ticket2680_C1D_PAPA

    • Property svn:externals
      •  

        old new  
        99 
        1010# SETTE 
        11 ^/utils/CI/sette@14244        sette 
         11^/utils/CI/sette@HEAD        sette 
         12 
  • NEMO/branches/2021/ticket2680_C1D_PAPA/tests/ISOMIP+/MY_SRC/istate.F90

    r15011 r15015  
    3434   USE lib_mpp         ! MPP library 
    3535   USE restart         ! restart 
     36 
    3637#if defined key_agrif 
     38   USE agrif_oce       ! initial state interpolation 
    3739   USE agrif_oce_interp 
    38    USE agrif_oce 
    3940#endif    
    4041 
     
    4243   PRIVATE 
    4344 
    44    PUBLIC   istate_init   ! routine called by step.F90 
     45   PUBLIC   istate_init   ! routine called by nemogcm.F90 
    4546 
    4647   !! * Substitutions 
     
    6364      ! 
    6465      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    65       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zgdept     ! 3D table  !!st patch to use gdept subtitute 
     66      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zgdept     ! 3D table for qco substitute 
    6667!!gm see comment further down 
    6768      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::   zuvd    ! U & V data workspace 
     
    7374      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    7475 
    75 !!gm  Why not include in the first call of dta_tsd ?   
    76 !!gm  probably associated with the use of internal damping... 
    77        CALL dta_tsd_init        ! Initialisation of T & S input data 
    78 !!gm to be moved in usrdef of C1D case 
    79 !      IF( ln_c1d )   CALL dta_uvd_init        ! Initialization of U & V input data 
    80 !!gm 
     76      CALL dta_tsd_init                 ! Initialisation of T & S input data 
     77      IF( ln_c1d) CALL dta_uvd_init     ! Initialisation of U & V input data (c1d only) 
    8178 
    82       rhd  (:,:,:  ) = 0._wp   ;   rhop (:,:,:  ) = 0._wp      ! set one for all to 0 at level jpk 
    83       rn2b (:,:,:  ) = 0._wp   ;   rn2  (:,:,:  ) = 0._wp      ! set one for all to 0 at levels 1 and jpk 
    84       ts  (:,:,:,:,Kaa) = 0._wp                                   ! set one for all to 0 at level jpk 
    85       rab_b(:,:,:,:) = 0._wp   ;   rab_n(:,:,:,:) = 0._wp      ! set one for all to 0 at level jpk 
     79      rhd  (:,:,:      ) = 0._wp   ;   rhop (:,:,:  ) = 0._wp      ! set one for all to 0 at level jpk 
     80      rn2b (:,:,:      ) = 0._wp   ;   rn2  (:,:,:  ) = 0._wp      ! set one for all to 0 at levels 1 and jpk 
     81      ts   (:,:,:,:,Kaa) = 0._wp                                   ! set one for all to 0 at level jpk 
     82      rab_b(:,:,:,:    ) = 0._wp   ;   rab_n(:,:,:,:) = 0._wp      ! set one for all to 0 at level jpk 
    8683#if defined key_agrif 
    8784      uu   (:,:,:  ,Kaa) = 0._wp   ! used in agrif_oce_sponge at initialization 
     
    9491         ln_1st_euler = .true.                ! Set time-step indicator at nit000 (euler forward) 
    9592         CALL day_init  
    96          CALL agrif_istate( Kbb, Kmm, Kaa )   ! Interp from parent 
     93         CALL agrif_istate_oce( Kbb, Kmm, Kaa )   ! Interp from parent 
    9794         ! 
    98          ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)  
    99          ssh (:,:,Kmm)     = ssh(:,:,Kbb) 
    100          uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb) 
    101          vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
     95         ts (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb) 
     96         uu (:,:,:  ,Kmm) = uu (:,:,:  ,Kbb) 
     97         vv (:,:,:  ,Kmm) = vv (:,:,:  ,Kbb) 
    10298      ELSE 
    10399#endif 
    104       IF( ln_rstart ) THEN                    ! Restart from a file 
    105          !                                    ! ------------------- 
    106          CALL rst_read( Kbb, Kmm )            ! Read the restart file 
    107          CALL day_init                        ! model calendar (using both namelist and restart infos) 
    108          ! 
    109       ELSE                                    ! Start from rest 
    110          !                                    ! --------------- 
    111          numror = 0                           ! define numror = 0 -> no restart file to read 
    112          l_1st_euler = .true.                 ! Set time-step indicator at nit000 (euler forward) 
    113          CALL day_init                        ! model calendar (using both namelist and restart infos) 
    114          !                                    ! Initialization of ocean to zero 
    115          ! 
    116          IF( ln_tsd_init ) THEN                
    117             CALL dta_tsd( nit000, 'ini', ts(:,:,:,:,Kbb) )       ! read 3D T and S data at nit000 
     100         IF( ln_rstart ) THEN                    ! Restart from a file 
     101            !                                    ! ------------------- 
     102            CALL rst_read( Kbb, Kmm )            ! Read the restart file 
     103            CALL day_init                        ! model calendar (using both namelist and restart infos) 
    118104            ! 
    119             uu (:,:,:,Kbb) = 0._wp 
    120             vv (:,:,:,Kbb) = 0._wp 
     105         ELSE                                    ! Start from rest 
     106            !                                    ! --------------- 
     107            numror = 0                           ! define numror = 0 -> no restart file to read 
     108            l_1st_euler = .true.                 ! Set time-step indicator at nit000 (euler forward) 
     109            CALL day_init                        ! model calendar (using both namelist and restart infos) 
     110            !                                    ! Initialization of ocean to zero 
    121111            ! 
    122          ELSE                                 ! user defined initial T and S 
    123             DO jk = 1, jpk 
    124                zgdept(:,:,jk) = gdept(:,:,jk,Kbb) 
    125             END DO 
    126             CALL usr_def_istate( zgdept, tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb)  )          
    127          ENDIF 
    128          ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)       ! set now values from to before ones 
    129          uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb) 
    130          vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
     112            IF( ln_tsd_init ) THEN                
     113               CALL dta_tsd( nit000, 'ini', ts(:,:,:,:,Kbb) )       ! read 3D T and S data at nit000 
     114            ENDIF 
     115            ! 
     116            IF( ln_uvd_init .AND. ln_c1d ) THEN                
     117               CALL dta_uvd( nit000, Kbb, uu(:,:,:,Kbb), vv(:,:,:,Kbb) )   ! read 3D U and V data at nit000 
     118            ELSE 
     119               uu  (:,:,:,Kbb) = 0._wp               ! set the ocean at rest 
     120               vv  (:,:,:,Kbb) = 0._wp   
     121            ENDIF 
     122               ! 
     123               ! 
     124            IF( .NOT. ln_tsd_init .AND. .NOT. ln_uvd_init ) THEN 
     125               DO jk = 1, jpk 
     126                  zgdept(:,:,jk) = gdept(:,:,jk,Kbb) 
     127               END DO 
     128               CALL usr_def_istate( zgdept, tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb) )          
     129            ENDIF 
     130            ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)       ! set now values from to before ones 
     131            uu    (:,:,:,Kmm) = uu   (:,:,:,Kbb) 
     132            vv    (:,:,:,Kmm) = vv   (:,:,:,Kbb) 
    131133 
    132 !!gm POTENTIAL BUG : 
    133 !!gm  ISSUE :  if ssh(:,:,Kbb) /= 0  then, in non linear free surface, the e3._n, e3._b should be recomputed 
    134 !!             as well as gdept_ and gdepw_....   !!!!!  
    135 !!      ===>>>>   probably a call to domvvl initialisation here.... 
    136  
    137  
    138          ! 
    139 !!gm to be moved in usrdef of C1D case 
    140 !         IF ( ln_uvd_init .AND. ln_c1d ) THEN ! read 3D U and V data at nit000 
    141 !            ALLOCATE( zuvd(jpi,jpj,jpk,2) ) 
    142 !            CALL dta_uvd( nit000, zuvd ) 
    143 !            uu(:,:,:,Kbb) = zuvd(:,:,:,1) ;  uu(:,:,:,Kmm) = uu(:,:,:,Kbb) 
    144 !            vv(:,:,:,Kbb) = zuvd(:,:,:,2) ;  vv(:,:,:,Kmm) = vv(:,:,:,Kbb) 
    145 !            DEALLOCATE( zuvd ) 
    146 !         ENDIF 
    147          ! 
    148 !!gm This is to be changed !!!! 
    149 !         ! - ML - ssh(:,:,Kmm) could be modified by istate_eel, so that initialization of e3t(:,:,:,Kbb) is done here 
    150 !         IF( .NOT.ln_linssh ) THEN 
    151 !            DO jk = 1, jpk 
    152 !               e3t(:,:,jk,Kbb) = e3t(:,:,jk,Kmm) 
    153 !            END DO 
    154 !         ENDIF 
    155 !!gm  
    156          !  
    157       ENDIF  
     134         ENDIF  
    158135#if defined key_agrif 
    159136      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.