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 14062 for NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/DOM/istate.F90 – NEMO

Ignore:
Timestamp:
2020-12-03T17:39:30+01:00 (3 years ago)
Author:
ayoung
Message:

Updating to trunk at 14060 and resolving conflicts with ticket #2480. Ticket #2506.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/DOM/istate.F90

    r13295 r14062  
    4242   PRIVATE 
    4343 
    44    PUBLIC   istate_init   ! routine called by step.F90 
     44   PUBLIC   istate_init   ! routine called by nemogcm.F90 
    4545 
    4646   !! * Substitutions 
     
    5959      !!  
    6060      !! ** Purpose :   Initialization of the dynamics and tracer fields. 
     61      !! 
     62      !! ** Method  :    
    6163      !!---------------------------------------------------------------------- 
    6264      INTEGER, INTENT( in )  ::  Kbb, Kmm, Kaa   ! ocean time level indices 
    6365      ! 
    6466      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    65       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zgdept     ! 3D table  !!st patch to use gdept subtitute 
     67      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zgdept     ! 3D table for qco substitute 
    6668!!gm see comment further down 
    6769      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::   zuvd    ! U & V data workspace 
     
    7375      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    7476 
    75 !!gm  Why not include in the first call of dta_tsd ?   
    76 !!gm  probably associated with the use of internal damping... 
    7777       CALL dta_tsd_init        ! Initialisation of T & S input data 
    78 !!gm to be moved in usrdef of C1D case 
     78 
    7979!      IF( lk_c1d )   CALL dta_uvd_init        ! Initialization of U & V input data 
    80 !!gm 
    8180 
    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 
     81      rhd  (:,:,:      ) = 0._wp   ;   rhop (:,:,:  ) = 0._wp      ! set one for all to 0 at level jpk 
     82      rn2b (:,:,:      ) = 0._wp   ;   rn2  (:,:,:  ) = 0._wp      ! set one for all to 0 at levels 1 and jpk 
     83      ts   (:,:,:,:,Kaa) = 0._wp                                   ! set one for all to 0 at level jpk 
     84      rab_b(:,:,:,:    ) = 0._wp   ;   rab_n(:,:,:,:) = 0._wp      ! set one for all to 0 at level jpk 
    8685#if defined key_agrif 
    8786      uu   (:,:,:  ,Kaa) = 0._wp   ! used in agrif_oce_sponge at initialization 
     
    9695         CALL agrif_istate( Kbb, Kmm, Kaa )   ! Interp from parent 
    9796         ! 
    98          ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)  
    99          ssh (:,:,Kmm)     = ssh(:,:,Kbb) 
    100          uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb) 
    101          vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
     97         ts (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb) 
     98!!st 
     99!!st need for a recent agrif version to be displaced toward ssh_init_rst with agrif_istate_ssh 
     100         ssh(:,:,    Kmm) = ssh(:,:    ,Kbb) 
     101!!st end 
     102         uu (:,:,:  ,Kmm) = uu (:,:,:  ,Kbb) 
     103         vv (:,:,:  ,Kmm) = vv (:,:,:  ,Kbb) 
    102104      ELSE 
    103105#endif 
     
    117119            CALL dta_tsd( nit000, ts(:,:,:,:,Kbb) )       ! read 3D T and S data at nit000 
    118120            ! 
    119             ssh(:,:,Kbb)   = 0._wp               ! set the ocean at rest 
    120             uu  (:,:,:,Kbb) = 0._wp 
    121             vv  (:,:,:,Kbb) = 0._wp   
     121            uu (:,:,:,Kbb) = 0._wp 
     122            vv (:,:,:,Kbb) = 0._wp   
    122123            ! 
    123             IF( ll_wd ) THEN 
    124                ssh(:,:,Kbb) =  -ssh_ref  ! Added in 30 here for bathy that adds 30 as Iterative test CEOD  
    125                ! 
    126                ! Apply minimum wetdepth criterion 
    127                ! 
    128                DO_2D( 1, 1, 1, 1 ) 
    129                   IF( ht_0(ji,jj) + ssh(ji,jj,Kbb)  < rn_wdmin1 ) THEN 
    130                      ssh(ji,jj,Kbb) = tmask(ji,jj,1)*( rn_wdmin1 - (ht_0(ji,jj)) ) 
    131                   ENDIF 
    132                END_2D 
    133             ENDIF  
    134              ! 
    135124         ELSE                                 ! user defined initial T and S 
    136125            DO jk = 1, jpk 
    137126               zgdept(:,:,jk) = gdept(:,:,jk,Kbb) 
    138127            END DO 
    139             CALL usr_def_istate( zgdept, tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb), ssh(:,:,Kbb)  )          
     128            CALL usr_def_istate( zgdept, tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb) ) 
    140129         ENDIF 
    141          ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)       ! set now values from to before ones 
    142          ssh (:,:,Kmm)     = ssh(:,:,Kbb)    
    143          uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb) 
    144          vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
    145  
    146 !!gm POTENTIAL BUG : 
    147 !!gm  ISSUE :  if ssh(:,:,Kbb) /= 0  then, in non linear free surface, the e3._n, e3._b should be recomputed 
    148 !!             as well as gdept_ and gdepw_....   !!!!!  
    149 !!      ===>>>>   probably a call to domvvl initialisation here.... 
    150  
     130         ts (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)       ! set now values from to before ones 
     131         uu (:,:,:  ,Kmm) = uu (:,:,:  ,Kbb) 
     132         vv (:,:,:  ,Kmm) = vv (:,:,:  ,Kbb) 
    151133 
    152134         ! 
    153 !!gm to be moved in usrdef of C1D case 
    154 !         IF ( ln_uvd_init .AND. lk_c1d ) THEN ! read 3D U and V data at nit000 
    155 !            ALLOCATE( zuvd(jpi,jpj,jpk,2) ) 
    156 !            CALL dta_uvd( nit000, zuvd ) 
    157 !            uu(:,:,:,Kbb) = zuvd(:,:,:,1) ;  uu(:,:,:,Kmm) = uu(:,:,:,Kbb) 
    158 !            vv(:,:,:,Kbb) = zuvd(:,:,:,2) ;  vv(:,:,:,Kmm) = vv(:,:,:,Kbb) 
    159 !            DEALLOCATE( zuvd ) 
    160 !         ENDIF 
     135!!gm ==>>>  to be moved in usrdef_istate of C1D case  
     136         IF ( ln_uvd_init .AND. lk_c1d ) THEN ! read 3D U and V data at nit000 
     137            ALLOCATE( zuvd(jpi,jpj,jpk,2) ) 
     138            CALL dta_uvd( nit000, Kbb, zuvd ) 
     139            uu(:,:,:,Kbb) = zuvd(:,:,:,1) ;  uu(:,:,:,Kmm) = uu(:,:,:,Kbb) 
     140            vv(:,:,:,Kbb) = zuvd(:,:,:,2) ;  vv(:,:,:,Kmm) = vv(:,:,:,Kbb) 
     141            DEALLOCATE( zuvd ) 
     142         ENDIF 
    161143         ! 
    162 !!gm This is to be changed !!!! 
    163 !         ! - ML - ssh(:,:,Kmm) could be modified by istate_eel, so that initialization of e3t(:,:,:,Kbb) is done here 
    164 !         IF( .NOT.ln_linssh ) THEN 
    165 !            DO jk = 1, jpk 
    166 !               e3t(:,:,jk,Kbb) = e3t(:,:,jk,Kmm) 
    167 !            END DO 
    168 !         ENDIF 
    169 !!gm  
    170144         !  
    171145      ENDIF  
Note: See TracChangeset for help on using the changeset viewer.