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 9537 for branches – NEMO

Changeset 9537 for branches


Ignore:
Timestamp:
2018-05-02T16:41:22+02:00 (6 years ago)
Author:
jcastill
Message:

Bug fix for key_asminc
WARNING - this fix is applied to revision 9196 of the branch, so the fix at revision 9473 is not included - it will be included in the next revision: this is done so we can use the same version as the operational suite, which at the moment does not contain the fix included in r9473

Location:
branches/UKMO/AMM15_v3_6_STABLE_package/NEMOGCM/NEMO/OPA_SRC
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/AMM15_v3_6_STABLE_package/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r9196 r9537  
    10181018            ENDIF 
    10191019 
     1020#if defined key_asminc 
    10201021         ELSE 
    10211022            ssh_iau(:,:) = 0._wp 
     1023#endif 
    10221024         ENDIF 
    10231025 
  • branches/UKMO/AMM15_v3_6_STABLE_package/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r9473 r9537  
    2727   PRIVATE 
    2828 
     29   PUBLIC   zdf_mxl_tref  ! called by asminc.F90 
    2930   PUBLIC   zdf_mxl       ! called by step.F90 
    3031 
     32   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld_tref  !: mixed layer depth at t-points - temperature criterion [m] 
    3133   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   nmln    !: number of level in the mixed layer (used by TOP) 
    3234   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld    !: mixing layer depth (turbocline)      [m] 
     
    7880        &          ll_found(jpi,jpj), ll_belowml(jpi,jpj,jpk), STAT= zdf_mxl_alloc ) 
    7981         ! 
     82         ALLOCATE(hmld_tref(jpi,jpj)) 
    8083         IF( lk_mpp             )   CALL mpp_sum ( zdf_mxl_alloc ) 
    8184         IF( zdf_mxl_alloc /= 0 )   CALL ctl_warn('zdf_mxl_alloc: failed to allocate arrays.') 
     
    8487   END FUNCTION zdf_mxl_alloc 
    8588 
     89   SUBROUTINE zdf_mxl_tref()  
     90      !!----------------------------------------------------------------------  
     91      !!                  ***  ROUTINE zdf_mxl_tref  ***  
     92      !!                     
     93      !! ** Purpose :   Compute the mixed layer depth with temperature criteria.  
     94      !!  
     95      !! ** Method  :   The temperature-defined mixed layer depth is required  
     96      !!                   when assimilating SST in a 2D analysis.   
     97      !!  
     98      !! ** Action  :   hmld_tref  
     99      !!----------------------------------------------------------------------  
     100      !  
     101      INTEGER  ::   ji, jj, jk   ! dummy loop indices  
     102      REAL(wp) ::   t_ref               ! Reference temperature    
     103      REAL(wp) ::   temp_c = 0.2        ! temperature criterion for mixed layer depth    
     104      !!----------------------------------------------------------------------  
     105      !  
     106      ! Initialise array  
     107      IF( zdf_mxl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl_tref : unable to allocate arrays' )  
     108        
     109      !For the AMM model assimiation uses a temperature based mixed layer depth    
     110      !This is defined here    
     111      DO jj = 1, jpj    
     112         DO ji = 1, jpi    
     113           hmld_tref(ji,jj)=fsdept(ji,jj,1  )     
     114           IF(ssmask(ji,jj) > 0.)THEN    
     115             t_ref=tsn(ji,jj,1,jp_tem)   
     116             DO jk=2,jpk    
     117               IF(ssmask(ji,jj)==0.)THEN    
     118                  hmld_tref(ji,jj)=fsdept(ji,jj,jk )    
     119                  EXIT    
     120               ELSEIF( ABS(tsn(ji,jj,jk,jp_tem)-t_ref) < temp_c)THEN    
     121                  hmld_tref(ji,jj)=fsdept(ji,jj,jk )    
     122               ELSE    
     123                  EXIT    
     124               ENDIF    
     125             ENDDO    
     126           ENDIF    
     127         ENDDO    
     128      ENDDO  
     129    
     130   END SUBROUTINE zdf_mxl_tref  
    86131 
    87132   SUBROUTINE zdf_mxl( kt ) 
     
    551596            IF( i_cnt_25h .EQ. 25 .AND.  MOD( kt, i_steps*24) == 0 .AND. kt .NE. nn_it000 ) THEN 
    552597               i_cnt_25h = 1  
    553                DO jn = 1, nn_mld_diag 
    554                      hmld_zint_25h(:,:,jn) = hmld_zint(:,:) 
    555                ENDDO 
    556598            ENDIF 
    557599         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.