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 6661 – NEMO

Changeset 6661


Ignore:
Timestamp:
2016-06-03T10:51:04+02:00 (8 years ago)
Author:
kingr
Message:

Made changes to code to fix bug in appplying 2D assimilation increments.

Location:
branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r6650 r6661  
    436436            ELSE 
    437437               lk_surft = .TRUE. 
     438               CALL ctl_warn( ' Applying 2D temperature increment to bottom of ML: ', & 
     439            &                 ' bckinsurft found in increments file.' ) 
    438440            ENDIF              
    439441 
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r6630 r6661  
    2727 
    2828   PUBLIC   zdf_mxl       ! called by step.F90 
     29   PUBLIC   zdf_mxl_tref  ! called by asminc.F90 
    2930   PUBLIC   zdf_mxl_alloc ! Used in zdf_tke_init 
    3031 
     
    8687      REAL(wp) ::   zN2_c        ! local scalar 
    8788      INTEGER, POINTER, DIMENSION(:,:) ::   imld   ! 2D workspace 
    88       REAL(wp) ::   t_ref               ! Reference temperature   
    89       REAL(wp) ::   temp_c = 0.2        ! temperature criterion for mixed layer depth   
    9089      !!---------------------------------------------------------------------- 
    9190      ! 
     
    141140         CALL iom_put( "mldkz5"  , hmld )   ! turbocline depth 
    142141      ENDIF 
     142       
     143      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 ) 
     144      ! 
     145      CALL wrk_dealloc( jpi,jpj, imld ) 
     146      ! 
     147      IF( nn_timing == 1 )  CALL timing_stop('zdf_mxl') 
     148      ! 
     149   END SUBROUTINE zdf_mxl 
    143150 
     151 
     152   SUBROUTINE zdf_mxl_tref() 
     153      !!---------------------------------------------------------------------- 
     154      !!                  ***  ROUTINE zdf_mxl_tref  *** 
     155      !!                    
     156      !! ** Purpose :   Compute the mixed layer depth with temperature criteria. 
     157      !! 
     158      !! ** Method  :   The temperature-defined mixed layer depth is required 
     159      !!                   when assimilating SST in a 2D analysis.  
     160      !! 
     161      !! ** Action  :   hmld_tref 
     162      !!---------------------------------------------------------------------- 
     163      ! 
     164      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
     165      REAL(wp) ::   t_ref               ! Reference temperature   
     166      REAL(wp) ::   temp_c = 0.2        ! temperature criterion for mixed layer depth   
     167      !!---------------------------------------------------------------------- 
     168      ! 
     169      ! Initialise array 
     170      IF( zdf_mxl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl_tref : unable to allocate arrays' ) 
     171       
    144172      !For the AMM model assimiation uses a temperature based mixed layer depth   
    145173      !This is defined here   
     
    162190         ENDDO   
    163191      ENDDO 
    164        
    165       IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 ) 
    166       ! 
    167       CALL wrk_dealloc( jpi,jpj, imld ) 
    168       ! 
    169       IF( nn_timing == 1 )  CALL timing_stop('zdf_mxl') 
    170       ! 
    171    END SUBROUTINE zdf_mxl 
     192 
     193   END SUBROUTINE zdf_mxl_tref 
    172194 
    173195   !!====================================================================== 
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6630 r6661  
    475475      IF( lk_asminc ) THEN  
    476476#if defined key_shelf  
    477          ios = zdf_mxl_alloc() 
    478          nmln(:,:) = nlb10           ! Initialization of nmln 
     477         CALL  zdf_mxl_tref()     ! Initialization of hmld_tref 
    479478#endif  
    480479         CALL asm_inc_init     ! Initialize assimilation increments  
Note: See TracChangeset for help on using the changeset viewer.