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 10969 for NEMO – NEMO

Changeset 10969 for NEMO


Ignore:
Timestamp:
2019-05-13T12:02:13+02:00 (5 years ago)
Author:
davestorkey
Message:

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : ASM and knock-on changes. NB. Only tested for compilation - no SETTE tests for ASM.

Location:
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/ASM/asmbkg.F90

    r10425 r10969  
    5252CONTAINS 
    5353 
    54    SUBROUTINE asm_bkg_wri( kt ) 
     54   SUBROUTINE asm_bkg_wri( kt, Kmm ) 
    5555      !!----------------------------------------------------------------------- 
    5656      !!                  ***  ROUTINE asm_bkg_wri *** 
     
    6565      !!----------------------------------------------------------------------- 
    6666      INTEGER, INTENT( IN ) :: kt               ! Current time-step 
     67      INTEGER, INTENT( IN ) :: Kmm              ! time level index 
    6768      ! 
    6869      CHARACTER (LEN=50) :: cl_asmbkg 
     
    9899            ! 
    99100            !                                      ! Write the information 
    100             CALL iom_rstput( kt, nitbkg_r, inum, 'rdastp' , zdate             ) 
    101             CALL iom_rstput( kt, nitbkg_r, inum, 'un'     , un                ) 
    102             CALL iom_rstput( kt, nitbkg_r, inum, 'vn'     , vn                ) 
    103             CALL iom_rstput( kt, nitbkg_r, inum, 'tn'     , tsn(:,:,:,jp_tem) ) 
    104             CALL iom_rstput( kt, nitbkg_r, inum, 'sn'     , tsn(:,:,:,jp_sal) ) 
    105             CALL iom_rstput( kt, nitbkg_r, inum, 'sshn'   , sshn              ) 
    106             IF( ln_zdftke )   CALL iom_rstput( kt, nitbkg_r, inum, 'en'     , en                ) 
     101            CALL iom_rstput( kt, nitbkg_r, inum, 'rdastp' , zdate                ) 
     102            CALL iom_rstput( kt, nitbkg_r, inum, 'un'     , uu(:,:,:,Kmm)        ) 
     103            CALL iom_rstput( kt, nitbkg_r, inum, 'vn'     , vv(:,:,:,Kmm)        ) 
     104            CALL iom_rstput( kt, nitbkg_r, inum, 'tn'     , ts(:,:,:,jp_tem,Kmm) ) 
     105            CALL iom_rstput( kt, nitbkg_r, inum, 'sn'     , ts(:,:,:,jp_sal,Kmm) ) 
     106            CALL iom_rstput( kt, nitbkg_r, inum, 'sshn'   , ssh(:,:,Kmm)         ) 
     107            IF( ln_zdftke )   CALL iom_rstput( kt, nitbkg_r, inum, 'en'     , en ) 
    107108            ! 
    108109            CALL iom_close( inum ) 
     
    133134            ! 
    134135            !                                      ! Write the information 
    135             CALL iom_rstput( kt, nitdin_r, inum, 'rdastp' , zdate             ) 
    136             CALL iom_rstput( kt, nitdin_r, inum, 'un'     , un                ) 
    137             CALL iom_rstput( kt, nitdin_r, inum, 'vn'     , vn                ) 
    138             CALL iom_rstput( kt, nitdin_r, inum, 'tn'     , tsn(:,:,:,jp_tem) ) 
    139             CALL iom_rstput( kt, nitdin_r, inum, 'sn'     , tsn(:,:,:,jp_sal) ) 
    140             CALL iom_rstput( kt, nitdin_r, inum, 'sshn'   , sshn              ) 
     136            CALL iom_rstput( kt, nitdin_r, inum, 'rdastp' , zdate                ) 
     137            CALL iom_rstput( kt, nitdin_r, inum, 'un'     , uu(:,:,:,Kmm)        ) 
     138            CALL iom_rstput( kt, nitdin_r, inum, 'vn'     , vv(:,:,:,Kmm)        ) 
     139            CALL iom_rstput( kt, nitdin_r, inum, 'tn'     , ts(:,:,:,jp_tem,Kmm) ) 
     140            CALL iom_rstput( kt, nitdin_r, inum, 'sn'     , ts(:,:,:,jp_sal,Kmm) ) 
     141            CALL iom_rstput( kt, nitdin_r, inum, 'sshn'   , ssh(:,:,Kmm)         ) 
    141142#if defined key_si3 
    142143            IF( nn_ice == 2 ) THEN 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/ASM/asminc.F90

    r10954 r10969  
    102102CONTAINS 
    103103 
    104    SUBROUTINE asm_inc_init( Kmm ) 
     104   SUBROUTINE asm_inc_init( Kbb, Kmm, Krhs ) 
    105105      !!---------------------------------------------------------------------- 
    106106      !!                    ***  ROUTINE asm_inc_init  *** 
     
    112112      !! ** Action  :  
    113113      !!---------------------------------------------------------------------- 
    114       INTEGER, INTENT(in) ::   Kmm  ! time level index 
     114      INTEGER, INTENT(in) ::  Kbb, Kmm, Krhs  ! time level indices 
     115      ! 
    115116      INTEGER :: ji, jj, jk, jt  ! dummy loop indices 
    116117      INTEGER :: imid, inum      ! local integers 
     
    416417               DO jj = 2, jpjm1 
    417418                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    418                      zhdiv(ji,jj) = (  e2u(ji  ,jj) * e3u_n(ji  ,jj,jk) * u_bkginc(ji  ,jj,jk)    & 
    419                         &            - e2u(ji-1,jj) * e3u_n(ji-1,jj,jk) * u_bkginc(ji-1,jj,jk)    & 
    420                         &            + e1v(ji,jj  ) * e3v_n(ji,jj  ,jk) * v_bkginc(ji,jj  ,jk)    & 
    421                         &            - e1v(ji,jj-1) * e3v_n(ji,jj-1,jk) * v_bkginc(ji,jj-1,jk)  ) / e3t_n(ji,jj,jk) 
     419                     zhdiv(ji,jj) = (  e2u(ji  ,jj) * e3u(ji  ,jj,jk,Kmm) * u_bkginc(ji  ,jj,jk)    & 
     420                        &            - e2u(ji-1,jj) * e3u(ji-1,jj,jk,Kmm) * u_bkginc(ji-1,jj,jk)    & 
     421                        &            + e1v(ji,jj  ) * e3v(ji,jj  ,jk,Kmm) * v_bkginc(ji,jj  ,jk)    & 
     422                        &            - e1v(ji,jj-1) * e3v(ji,jj-1,jk,Kmm) * v_bkginc(ji,jj-1,jk)  ) / e3t(ji,jj,jk,Kmm) 
    422423                  END DO 
    423424               END DO 
     
    495496      ! 
    496497      IF( lk_asminc ) THEN                            !==  data assimilation  ==! 
    497          IF( ln_bkgwri )   CALL asm_bkg_wri( nit000 - 1 )      ! Output background fields 
     498         IF( ln_bkgwri )   CALL asm_bkg_wri( nit000 - 1, Kmm )      ! Output background fields 
    498499         IF( ln_asmdin ) THEN                                  ! Direct initialization 
    499             IF( ln_trainc )   CALL tra_asm_inc( nit000 - 1, Kmm )      ! Tracers 
    500             IF( ln_dyninc )   CALL dyn_asm_inc( nit000 - 1 )      ! Dynamics 
    501             IF( ln_sshinc )   CALL ssh_asm_inc( nit000 - 1 )      ! SSH 
     500            IF( ln_trainc )   CALL tra_asm_inc( nit000 - 1, Kbb, Kmm, ts    , Krhs )      ! Tracers 
     501            IF( ln_dyninc )   CALL dyn_asm_inc( nit000 - 1, Kbb, Kmm, uu, vv, Krhs )      ! Dynamics 
     502            IF( ln_sshinc )   CALL ssh_asm_inc( nit000 - 1, Kbb, Kmm )                    ! SSH 
    502503         ENDIF 
    503504      ENDIF 
     
    506507    
    507508    
    508    SUBROUTINE tra_asm_inc( kt, Kmm ) 
     509   SUBROUTINE tra_asm_inc( kt, Kbb, Kmm, pts, Krhs ) 
    509510      !!---------------------------------------------------------------------- 
    510511      !!                    ***  ROUTINE tra_asm_inc  *** 
     
    516517      !! ** Action  :  
    517518      !!---------------------------------------------------------------------- 
    518       INTEGER, INTENT(IN) ::   kt   ! Current time step 
    519       INTEGER, INTENT(IN) ::   Kmm  ! Current time level index 
     519      INTEGER                                  , INTENT(in   ) :: kt             ! Current time step 
     520      INTEGER                                  , INTENT(in   ) :: Kbb, Kmm, Krhs ! Time level indices 
     521      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts            ! active tracers and RHS of tracer equation 
    520522      ! 
    521523      INTEGER  :: ji, jj, jk 
     
    528530      ! used to prevent the applied increments taking the temperature below the local freezing point  
    529531      DO jk = 1, jpkm1 
    530         CALL eos_fzp( tsn(:,:,jk,jp_sal), fzptnz(:,:,jk), gdept_n(:,:,jk) ) 
     532        CALL eos_fzp( pts(:,:,jk,jp_sal,Kmm), fzptnz(:,:,jk), gdept(:,:,jk,Kmm) ) 
    531533      END DO 
    532534         ! 
     
    551553                  ! Do not apply negative increments if the temperature will fall below freezing 
    552554                  WHERE(t_bkginc(:,:,jk) > 0.0_wp .OR. & 
    553                      &   tsn(:,:,jk,jp_tem) + tsa(:,:,jk,jp_tem) + t_bkginc(:,:,jk) * wgtiau(it) > fzptnz(:,:,jk) )  
    554                      tsa(:,:,jk,jp_tem) = tsa(:,:,jk,jp_tem) + t_bkginc(:,:,jk) * zincwgt   
     555                     &   pts(:,:,jk,jp_tem,Kmm) + pts(:,:,jk,jp_tem,Krhs) + t_bkginc(:,:,jk) * wgtiau(it) > fzptnz(:,:,jk) )  
     556                     pts(:,:,jk,jp_tem,Krhs) = pts(:,:,jk,jp_tem,Krhs) + t_bkginc(:,:,jk) * zincwgt   
    555557                  END WHERE 
    556558               ELSE 
    557                   tsa(:,:,jk,jp_tem) = tsa(:,:,jk,jp_tem) + t_bkginc(:,:,jk) * zincwgt   
     559                  pts(:,:,jk,jp_tem,Krhs) = pts(:,:,jk,jp_tem,Krhs) + t_bkginc(:,:,jk) * zincwgt   
    558560               ENDIF 
    559561               IF (ln_salfix) THEN 
     
    561563                  ! minimum value salfixmin 
    562564                  WHERE(s_bkginc(:,:,jk) > 0.0_wp .OR. & 
    563                      &   tsn(:,:,jk,jp_sal) + tsa(:,:,jk,jp_sal) + s_bkginc(:,:,jk) * wgtiau(it) > salfixmin )  
    564                      tsa(:,:,jk,jp_sal) = tsa(:,:,jk,jp_sal) + s_bkginc(:,:,jk) * zincwgt 
     565                     &   pts(:,:,jk,jp_sal,Kmm) + pts(:,:,jk,jp_sal,Krhs) + s_bkginc(:,:,jk) * wgtiau(it) > salfixmin )  
     566                     pts(:,:,jk,jp_sal,Krhs) = pts(:,:,jk,jp_sal,Krhs) + s_bkginc(:,:,jk) * zincwgt 
    565567                  END WHERE 
    566568               ELSE 
    567                   tsa(:,:,jk,jp_sal) = tsa(:,:,jk,jp_sal) + s_bkginc(:,:,jk) * zincwgt 
     569                  pts(:,:,jk,jp_sal,Krhs) = pts(:,:,jk,jp_sal,Krhs) + s_bkginc(:,:,jk) * zincwgt 
    568570               ENDIF 
    569571            END DO 
     
    586588            IF (ln_temnofreeze) THEN 
    587589               ! Do not apply negative increments if the temperature will fall below freezing 
    588                WHERE( t_bkginc(:,:,:) > 0.0_wp .OR. tsn(:,:,:,jp_tem) + t_bkginc(:,:,:) > fzptnz(:,:,:) )  
    589                   tsn(:,:,:,jp_tem) = t_bkg(:,:,:) + t_bkginc(:,:,:)    
     590               WHERE( t_bkginc(:,:,:) > 0.0_wp .OR. pts(:,:,:,jp_tem,Kmm) + t_bkginc(:,:,:) > fzptnz(:,:,:) )  
     591                  pts(:,:,:,jp_tem,Kmm) = t_bkg(:,:,:) + t_bkginc(:,:,:)    
    590592               END WHERE 
    591593            ELSE 
    592                tsn(:,:,:,jp_tem) = t_bkg(:,:,:) + t_bkginc(:,:,:)    
     594               pts(:,:,:,jp_tem,Kmm) = t_bkg(:,:,:) + t_bkginc(:,:,:)    
    593595            ENDIF 
    594596            IF (ln_salfix) THEN 
    595597               ! Do not apply negative increments if the salinity will fall below a specified 
    596598               ! minimum value salfixmin 
    597                WHERE( s_bkginc(:,:,:) > 0.0_wp .OR. tsn(:,:,:,jp_sal) + s_bkginc(:,:,:) > salfixmin )  
    598                   tsn(:,:,:,jp_sal) = s_bkg(:,:,:) + s_bkginc(:,:,:)    
     599               WHERE( s_bkginc(:,:,:) > 0.0_wp .OR. pts(:,:,:,jp_sal,Kmm) + s_bkginc(:,:,:) > salfixmin )  
     600                  pts(:,:,:,jp_sal,Kmm) = s_bkg(:,:,:) + s_bkginc(:,:,:)    
    599601               END WHERE 
    600602            ELSE 
    601                tsn(:,:,:,jp_sal) = s_bkg(:,:,:) + s_bkginc(:,:,:)    
     603               pts(:,:,:,jp_sal,Kmm) = s_bkg(:,:,:) + s_bkginc(:,:,:)    
    602604            ENDIF 
    603605 
    604             tsb(:,:,:,:) = tsn(:,:,:,:)                 ! Update before fields 
    605  
    606             CALL eos( tsb, rhd, rhop, gdept_0(:,:,:) )  ! Before potential and in situ densities 
     606            pts(:,:,:,:,Kbb) = pts(:,:,:,:,Kmm)                 ! Update before fields 
     607 
     608            CALL eos( pts(:,:,:,:,Kbb), rhd, rhop, gdept_0(:,:,:) )  ! Before potential and in situ densities 
    607609!!gm  fabien 
    608 !            CALL eos( tsb, rhd, rhop )                ! Before potential and in situ densities 
     610!            CALL eos( pts(:,:,:,:,Kbb), rhd, rhop )                ! Before potential and in situ densities 
    609611!!gm 
    610612 
    611613            IF( ln_zps .AND. .NOT. lk_c1d .AND. .NOT. ln_isfcav)           & 
    612                &  CALL zps_hde    ( kt, Kmm, jpts, tsb, gtsu, gtsv,        &  ! Partial steps: before horizontal gradient 
     614               &  CALL zps_hde    ( kt, Kmm, jpts, pts(:,:,:,:,Kbb), gtsu, gtsv,        &  ! Partial steps: before horizontal gradient 
    613615               &                              rhd, gru , grv               )  ! of t, s, rd at the last ocean level 
    614616            IF( ln_zps .AND. .NOT. lk_c1d .AND.       ln_isfcav)                       & 
    615                &  CALL zps_hde_isf( nit000, Kmm, jpts, tsb, gtsu, gtsv, gtui, gtvi,    &  ! Partial steps for top cell (ISF) 
     617               &  CALL zps_hde_isf( nit000, Kmm, jpts, pts(:,:,:,:,Kbb), gtsu, gtsv, gtui, gtvi,    &  ! Partial steps for top cell (ISF) 
    616618               &                                  rhd, gru , grv , grui, grvi          )  ! of t, s, rd at the last ocean level 
    617619 
     
    629631 
    630632 
    631    SUBROUTINE dyn_asm_inc( kt ) 
     633   SUBROUTINE dyn_asm_inc( kt, Kbb, Kmm, puu, pvv, Krhs ) 
    632634      !!---------------------------------------------------------------------- 
    633635      !!                    ***  ROUTINE dyn_asm_inc  *** 
     
    639641      !! ** Action  :  
    640642      !!---------------------------------------------------------------------- 
    641       INTEGER, INTENT(IN) :: kt   ! Current time step 
     643      INTEGER                             , INTENT( in )  ::  kt             ! ocean time-step index 
     644      INTEGER                             , INTENT( in )  ::  Kbb, Kmm, Krhs ! ocean time level indices 
     645      REAL(wp), DIMENSION(jpi,jpj,jpk,jpt), INTENT(inout) ::  puu, pvv       ! ocean velocities and RHS of momentum equation 
    642646      ! 
    643647      INTEGER :: jk 
     
    663667            ! Update the dynamic tendencies 
    664668            DO jk = 1, jpkm1 
    665                ua(:,:,jk) = ua(:,:,jk) + u_bkginc(:,:,jk) * zincwgt 
    666                va(:,:,jk) = va(:,:,jk) + v_bkginc(:,:,jk) * zincwgt 
     669               puu(:,:,jk,Krhs) = puu(:,:,jk,Krhs) + u_bkginc(:,:,jk) * zincwgt 
     670               pvv(:,:,jk,Krhs) = pvv(:,:,jk,Krhs) + v_bkginc(:,:,jk) * zincwgt 
    667671            END DO 
    668672            ! 
     
    682686            ! 
    683687            ! Initialize the now fields with the background + increment 
    684             un(:,:,:) = u_bkg(:,:,:) + u_bkginc(:,:,:) 
    685             vn(:,:,:) = v_bkg(:,:,:) + v_bkginc(:,:,:)   
    686             ! 
    687             ub(:,:,:) = un(:,:,:)         ! Update before fields 
    688             vb(:,:,:) = vn(:,:,:) 
     688            puu(:,:,:,Kmm) = u_bkg(:,:,:) + u_bkginc(:,:,:) 
     689            pvv(:,:,:,Kmm) = v_bkg(:,:,:) + v_bkginc(:,:,:)   
     690            ! 
     691            puu(:,:,:,Kbb) = puu(:,:,:,Kmm)         ! Update before fields 
     692            pvv(:,:,:,Kbb) = pvv(:,:,:,Kmm) 
    689693            ! 
    690694            DEALLOCATE( u_bkg    ) 
     
    699703 
    700704 
    701    SUBROUTINE ssh_asm_inc( kt ) 
     705   SUBROUTINE ssh_asm_inc( kt, Kbb, Kmm ) 
    702706      !!---------------------------------------------------------------------- 
    703707      !!                    ***  ROUTINE ssh_asm_inc  *** 
     
    709713      !! ** Action  :  
    710714      !!---------------------------------------------------------------------- 
    711       INTEGER, INTENT(IN) :: kt   ! Current time step 
     715      INTEGER, INTENT(IN) :: kt         ! Current time step 
     716      INTEGER, INTENT(IN) :: Kbb, Kmm   ! Current time step 
    712717      ! 
    713718      INTEGER :: it 
     
    756761            neuler = 0                                   ! Force Euler forward step 
    757762            ! 
    758             sshn(:,:) = ssh_bkg(:,:) + ssh_bkginc(:,:)   ! Initialize the now fields the background + increment 
    759             ! 
    760             sshb(:,:) = sshn(:,:)                        ! Update before fields 
    761             e3t_b(:,:,:) = e3t_n(:,:,:) 
    762 !!gm why not e3u_b, e3v_b, gdept_b ???? 
     763            ssh(:,:,Kmm) = ssh_bkg(:,:) + ssh_bkginc(:,:)   ! Initialize the now fields the background + increment 
     764            ! 
     765            ssh(:,:,Kbb) = ssh(:,:,Kmm)                        ! Update before fields 
     766            e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm) 
     767!!gm why not e3u(:,:,:,Kbb), e3v(:,:,:,Kbb), gdept(:,:,:,Kbb) ???? 
    763768            ! 
    764769            DEALLOCATE( ssh_bkg    ) 
     
    772777 
    773778 
    774    SUBROUTINE ssh_asm_div( kt, phdivn ) 
     779   SUBROUTINE ssh_asm_div( kt, Kbb, Kmm, phdivn ) 
    775780      !!---------------------------------------------------------------------- 
    776781      !!                  ***  ROUTINE ssh_asm_div  *** 
     
    786791      !!---------------------------------------------------------------------- 
    787792      INTEGER, INTENT(IN) :: kt                               ! ocean time-step index 
     793      INTEGER, INTENT(IN) :: Kbb, Kmm                         ! time level indices 
    788794      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   phdivn   ! horizontal divergence 
    789795      !! 
     
    793799      !  
    794800#if defined key_asminc 
    795       CALL ssh_asm_inc( kt ) !==   (calculate increments) 
     801      CALL ssh_asm_inc( kt, Kbb, Kmm ) !==   (calculate increments) 
    796802      ! 
    797803      IF( ln_linssh ) THEN  
    798          phdivn(:,:,1) = phdivn(:,:,1) - ssh_iau(:,:) / e3t_n(:,:,1) * tmask(:,:,1) 
     804         phdivn(:,:,1) = phdivn(:,:,1) - ssh_iau(:,:) / e3t(:,:,1,Kmm) * tmask(:,:,1) 
    799805      ELSE  
    800806         ALLOCATE( ztim(jpi,jpj) ) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/C1D/step_c1d.F90

    r10965 r10969  
    7979                         CALL zdf_phy( kstp )         ! vertical physics update (bfr, avt, avs, avm + MLD) 
    8080 
    81       IF(.NOT.ln_linssh )   CALL ssh_nxt       ( kstp )  ! after ssh (includes call to div_hor) 
     81      IF(.NOT.ln_linssh )   CALL ssh_nxt       ( kstp, Nbb, Nnn )  ! after ssh (includes call to div_hor) 
    8282      IF(.NOT.ln_linssh )   CALL dom_vvl_sf_nxt( kstp )  ! after vertical scale factors  
    8383 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DOM/istate.F90

    r10928 r10969  
    126126         vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
    127127         hdiv(:,:,jpk) = 0._wp               ! bottom divergence set one for 0 to zero at jpk level 
    128          CALL div_hor( 0, Kmm )              ! compute interior hdiv value   
     128         CALL div_hor( 0, Kbb, Kmm )         ! compute interior hdiv value   
    129129!!gm                                    hdiv(:,:,:) = 0._wp 
    130130 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DYN/divhor.F90

    r10928 r10969  
    4848CONTAINS 
    4949 
    50    SUBROUTINE div_hor( kt, Kmm ) 
     50   SUBROUTINE div_hor( kt, Kbb, Kmm ) 
    5151      !!---------------------------------------------------------------------- 
    5252      !!                  ***  ROUTINE div_hor  *** 
     
    6060      !! ** Action  : - update hdiv, the now horizontal divergence 
    6161      !!---------------------------------------------------------------------- 
    62       INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    63       INTEGER, INTENT(in) ::   Kmm  ! ocean time level index 
     62      INTEGER, INTENT(in) ::   kt        ! ocean time-step index 
     63      INTEGER, INTENT(in) ::   Kbb, Kmm  ! ocean time level indices 
    6464      ! 
    6565      INTEGER  ::   ji, jj, jk    ! dummy loop indices 
     
    9898      ! 
    9999#if defined key_asminc  
    100       IF( ln_sshinc .AND. ln_asmiau )   CALL ssh_asm_div( kt, hdiv )   !==  SSH assimilation  ==!   (update hdiv field) 
     100      IF( ln_sshinc .AND. ln_asmiau )   CALL ssh_asm_div( kt, Kbb, Kmm, hdiv )   !==  SSH assimilation  ==!   (update hdiv field) 
    101101      !  
    102102#endif 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DYN/sshwzv.F90

    r10922 r10969  
    5454CONTAINS 
    5555 
    56    SUBROUTINE ssh_nxt( kt, Kmm ) 
     56   SUBROUTINE ssh_nxt( kt, Kbb, Kmm ) 
    5757      !!---------------------------------------------------------------------- 
    5858      !!                ***  ROUTINE ssh_nxt  *** 
     
    6868      !! Reference  : Leclair, M., and G. Madec, 2009, Ocean Modelling. 
    6969      !!---------------------------------------------------------------------- 
    70       INTEGER, INTENT(in) ::   kt   ! time step 
    71       INTEGER, INTENT(in) ::   Kmm  ! time level index 
     70      INTEGER, INTENT(in) ::   kt        ! time step 
     71      INTEGER, INTENT(in) ::   Kbb, Kmm  ! time level index 
    7272      !  
    7373      INTEGER  ::   jk            ! dummy loop indice 
     
    9595      ENDIF 
    9696 
    97       CALL div_hor( kt, Kmm )                          ! Horizontal divergence 
     97      CALL div_hor( kt, Kbb, Kmm )                     ! Horizontal divergence 
    9898      ! 
    9999      zhdiv(:,:) = 0._wp 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/nemogcm.F90

    r10965 r10969  
    435435            CALL dia_obs( nit000 - 1, Nnn )              ! Observation operator for restart 
    436436         ENDIF      
    437          IF( lk_asminc )   CALL asm_inc_init( Nnn )   ! Assimilation increments 
     437         IF( lk_asminc )   CALL asm_inc_init( Nbb, Nnn, Nrhs )   ! Assimilation increments 
    438438         ! 
    439439         RETURN                                       ! end of initialization 
     
    497497 
    498498      !                                      ! Assimilation increments 
    499       IF( lk_asminc    )   CALL asm_inc_init( Nnn )        ! Initialize assimilation increments 
     499      IF( lk_asminc    )   CALL asm_inc_init( Nbb, Nnn, Nrhs )   ! Initialize assimilation increments 
    500500      ! 
    501501      IF(lwp) WRITE(numout,cform_aaa)           ! Flag AAAAAAA 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/step.F90

    r10965 r10969  
    165165      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    166166 
    167                             CALL ssh_nxt       ( kstp, Nnn )  ! after ssh (includes call to div_hor) 
     167                            CALL ssh_nxt       ( kstp, Nbb, Nnn )  ! after ssh (includes call to div_hor) 
    168168      IF( .NOT.ln_linssh )  CALL dom_vvl_sf_nxt( kstp )  ! after vertical scale factors  
    169169                            CALL wzv           ( kstp )  ! now cross-level velocity  
     
    187187 
    188188      IF(  lk_asminc .AND. ln_asmiau .AND. ln_dyninc )   & 
    189                &         CALL dyn_asm_inc   ( kstp )  ! apply dynamics assimilation increment 
    190       IF( ln_bdy     )   CALL bdy_dyn3d_dmp ( kstp, Nbb, uu, vv, Nrhs )  ! bdy damping trends 
     189               &         CALL dyn_asm_inc   ( kstp, Nbb, Nnn, uu, vv, Nrhs )  ! apply dynamics assimilation increment 
     190      IF( ln_bdy     )   CALL bdy_dyn3d_dmp ( kstp, Nbb,      uu, vv, Nrhs )  ! bdy damping trends 
    191191#if defined key_agrif 
    192192      IF(.NOT. Agrif_Root())  &  
     
    202202                                                      ! With split-explicit free surface, since now transports have been updated and ssha as well 
    203203      IF( ln_dynspg_ts ) THEN                         ! vertical scale factors and vertical velocity need to be updated 
    204                             CALL div_hor    ( kstp, Nnn )         ! Horizontal divergence  (2nd call in time-split case) 
     204                            CALL div_hor    ( kstp, Nbb, Nnn )    ! Horizontal divergence  (2nd call in time-split case) 
    205205         IF(.NOT.ln_linssh) CALL dom_vvl_sf_nxt( kstp, kcall=2 )  ! after vertical scale factors (update depth average component) 
    206206                            CALL wzv        ( kstp )              ! now cross-level velocity  
     
    241241 
    242242      IF(  lk_asminc .AND. ln_asmiau .AND. & 
    243          & ln_trainc )   CALL tra_asm_inc   ( kstp, Nnn      )  ! apply tracer assimilation increment 
    244                          CALL tra_sbc       ( kstp, Nnn, Nrhs )  ! surface boundary condition 
    245       IF( ln_traqsr  )   CALL tra_qsr       ( kstp, Nnn, Nrhs )  ! penetrative solar radiation qsr 
    246       IF( ln_trabbc  )   CALL tra_bbc       ( kstp, Nnn, Nrhs )  ! bottom heat flux 
     243         & ln_trainc )   CALL tra_asm_inc   ( kstp, Nbb, Nnn, ts, Nrhs )  ! apply tracer assimilation increment 
     244                         CALL tra_sbc       ( kstp,      Nnn, Nrhs )  ! surface boundary condition 
     245      IF( ln_traqsr  )   CALL tra_qsr       ( kstp,      Nnn, Nrhs )  ! penetrative solar radiation qsr 
     246      IF( ln_trabbc  )   CALL tra_bbc       ( kstp,      Nnn, Nrhs )  ! bottom heat flux 
    247247      IF( ln_trabbl  )   CALL tra_bbl       ( kstp, Nbb, Nnn, Nrhs )  ! advective (and/or diffusive) bottom boundary layer scheme 
    248248      IF( ln_tradmp  )   CALL tra_dmp       ( kstp, Nbb, Nnn, Nrhs )  ! internal damping trends 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcsub.F90

    r10963 r10969  
    488488      ! 
    489489!!gm BUG here !   hdiv will include the runoff divergence at the wrong timestep !!!! 
    490       CALL div_hor( kt, Kmm )                         ! Horizontal divergence & Relative vorticity 
     490      CALL div_hor( kt, Kbb, Kmm )                    ! Horizontal divergence & Relative vorticity 
    491491      ! 
    492492      z2dt = 2._wp * rdt                              ! set time step size (Euler/Leapfrog) 
Note: See TracChangeset for help on using the changeset viewer.