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

Changeset 7726 for branches


Ignore:
Timestamp:
2017-02-23T12:16:04+01:00 (7 years ago)
Author:
dford
Message:

Merge in changes to apply logchl assimilation increments to FABM-ERSEM, and the basic framework for HadOCC and MEDUSA. See internal Met Office NEMO ticket 668.

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

Legend:

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

    r7477 r7726  
    2222   !!   ssh_asm_inc    : Apply the SSH increment 
    2323   !!   seaice_asm_inc : Apply the seaice increment 
     24   !!   logchl_asm_inc : Apply the logchl increment 
    2425   !!---------------------------------------------------------------------- 
    2526   USE wrk_nemo         ! Memory Allocation 
     
    5253   USE bdy_oce, ONLY: bdytmask   
    5354#endif   
     55#if defined key_top 
     56   USE trc, ONLY: & 
     57      & trn,      & 
     58      & trb 
     59   USE par_trc, ONLY: & 
     60      & jptra 
     61#endif 
     62#if defined key_fabm 
     63   USE asmlogchlbal_ersem, ONLY: & 
     64      & asm_logchl_bal_ersem 
     65   USE par_fabm 
     66#elif defined key_medusa && defined key_foam_medusa 
     67   USE asmlogchlbal_medusa, ONLY: & 
     68      & asm_logchl_bal_medusa 
     69   USE par_medusa 
     70#elif defined key_hadocc 
     71   USE asmlogchlbal_hadocc, ONLY: & 
     72      & asm_logchl_bal_hadocc 
     73   USE par_hadocc 
     74#endif 
    5475 
    5576   IMPLICIT NONE 
     
    6283   PUBLIC   ssh_asm_inc    !: Apply the SSH increment 
    6384   PUBLIC   seaice_asm_inc !: Apply the seaice increment 
     85   PUBLIC   logchl_asm_inc !: Apply the logchl increment 
    6486 
    6587#if defined key_asminc 
     
    6991#endif 
    7092   LOGICAL, PUBLIC :: ln_bkgwri = .FALSE.      !: No output of the background state fields 
     93   LOGICAL, PUBLIC :: ln_balwri = .FALSE.      !: No output of the assimilation balancing increments 
    7194   LOGICAL, PUBLIC :: ln_avgbkg = .FALSE.      !: No output of the mean background state fields 
    7295   LOGICAL, PUBLIC :: ln_asmiau = .FALSE.      !: No applying forcing with an assimilation increment 
     
    7598   LOGICAL, PUBLIC :: ln_dyninc = .FALSE.      !: No dynamics (u and v) assimilation increments 
    7699   LOGICAL, PUBLIC :: ln_sshinc = .FALSE.      !: No sea surface height assimilation increment 
    77    LOGICAL, PUBLIC :: ln_seaiceinc             !: No sea ice concentration increment 
     100   LOGICAL, PUBLIC :: ln_seaiceinc = .FALSE.   !: No sea ice concentration increment 
     101   LOGICAL, PUBLIC :: ln_logchltotinc = .FALSE. !: No total log10(chlorophyll) increment 
     102   LOGICAL, PUBLIC :: ln_logchlpftinc = .FALSE. !: No PFT   log10(chlorophyll) increment 
    78103   LOGICAL, PUBLIC :: ln_salfix = .FALSE.      !: Apply minimum salinity check 
    79104   LOGICAL, PUBLIC :: ln_temnofreeze = .FALSE. !: Don't allow the temperature to drop below freezing 
     
    102127   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   seaice_bkginc         ! Increment to the background sea ice conc 
    103128 
     129   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE :: logchl_bkginc !: Increment to background logchl 
     130#if defined key_top 
     131   REAL(wp), PUBLIC, DIMENSION(:,:,:,:), ALLOCATABLE :: logchl_balinc  !: Increment to BGC variables from logchl assim 
     132#endif 
     133 
    104134   INTEGER :: mld_choice        = 4   !: choice of mld criteria to use for physics assimilation 
    105135                                      !: 1) hmld      - Turbocline/mixing depth                           [W points] 
     
    108138                                      !: 4) hmld_tref - Temperature criterion (0.2 K change from surface) [T points] 
    109139 
     140   INTEGER :: mld_choice_bgc    = 4   !: choice of mld criteria to use for physics assimilation 
     141                                      !: 1) hmld      - Turbocline/mixing depth                           [W points] 
     142                                      !: 2) hmlp      - Density criterion (0.01 kg/m^3 change from 10m)   [W points] 
     143                                      !: 3) hmld_kara - Kara MLD                                          [Interpolated] 
     144                                      !: 4) hmld_tref - Temperature criterion (0.2 K change from surface) [T points] 
     145                                      !: 5) hmlpt     - Density criterion (0.01 kg/m^3 change from 10m)   [T points] 
     146 
     147   INTEGER :: nn_asmpfts        = 0   !: number of logchl PFTs assimilated 
    110148 
    111149   !! * Substitutions 
     
    160198      LOGICAL :: lk_surft      ! Logical: T => Increments file contains surft variable  
    161199                               !               so only apply surft increments. 
    162       !! 
    163       NAMELIST/nam_asminc/ ln_bkgwri, ln_avgbkg,                           & 
     200      ! 
     201      CHARACTER(LEN=2) :: cl_pftstr 
     202      !! 
     203      NAMELIST/nam_asminc/ ln_bkgwri, ln_balwri, ln_avgbkg,                & 
    164204         &                 ln_trainc, ln_dyninc, ln_sshinc,                & 
     205         &                 ln_logchltotinc, ln_logchlpftinc,               & 
    165206         &                 ln_asmdin, ln_asmiau,                           & 
    166207         &                 nitbkg, nitdin, nitiaustr, nitiaufin, niaufn,   & 
    167          &                 ln_salfix, salfixmin, nn_divdmp, nitavgbkg, mld_choice 
     208         &                 ln_salfix, salfixmin, nn_divdmp, nitavgbkg, mld_choice, & 
     209         &                 mld_choice_bgc 
    168210      !!---------------------------------------------------------------------- 
    169211 
     
    174216      ! Set default values 
    175217      ln_bkgwri = .FALSE. 
     218      ln_balwri = .FALSE. 
    176219      ln_avgbkg = .FALSE. 
    177220      ln_trainc = .FALSE. 
     
    179222      ln_sshinc = .FALSE. 
    180223      ln_seaiceinc = .FALSE. 
     224      ln_logchltotinc = .FALSE. 
     225      ln_logchlpftinc = .FALSE. 
    181226      ln_asmdin = .FALSE. 
    182227      ln_asmiau = .TRUE. 
     
    190235      niaufn    = 0 
    191236      nitavgbkg = 1 
     237#if defined key_fabm 
     238      nn_asmpfts = 4 
     239#elif defined key_medusa && defined key_foam_medusa 
     240      nn_asmpfts = 2 
     241#elif defined key_hadocc 
     242      nn_asmpfts = 1 
     243#else 
     244      nn_asmpfts = 0 
     245#endif 
    192246 
    193247      REWIND( numnam_ref )              ! Namelist nam_asminc in reference namelist : Assimilation increment 
     
    199253902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_asminc in configuration namelist', lwp ) 
    200254      IF(lwm) WRITE ( numond, nam_asminc ) 
     255 
     256      IF ( ln_logchltotinc ) THEN 
     257         nn_asmpfts = 1 
     258      ELSE IF ( .NOT.( ln_logchlpftinc ) ) THEN 
     259         nn_asmpfts = 0 
     260      ENDIF 
    201261 
    202262      ! Control print 
     
    207267         WRITE(numout,*) '   Namelist namasm : set assimilation increment parameters' 
    208268         WRITE(numout,*) '      Logical switch for writing out background state          ln_bkgwri = ', ln_bkgwri 
     269         WRITE(numout,*) '      Logical switch for writing out balancing increments      ln_balwri = ', ln_balwri 
    209270         WRITE(numout,*) '      Logical switch for writing mean background state         ln_avgbkg = ', ln_avgbkg 
    210271         WRITE(numout,*) '      Logical switch for applying tracer increments            ln_trainc = ', ln_trainc 
     
    213274         WRITE(numout,*) '      Logical switch for Direct Initialization (DI)            ln_asmdin = ', ln_asmdin 
    214275         WRITE(numout,*) '      Logical switch for applying sea ice increments        ln_seaiceinc = ', ln_seaiceinc 
     276         WRITE(numout,*) '      Logical switch for applying total logchl incs      ln_logchltotinc = ', ln_logchltotinc 
     277         WRITE(numout,*) '      Logical switch for applying PFT   logchl incs      ln_logchlpftinc = ', ln_logchlpftinc 
     278         WRITE(numout,*) '      Number of logchl PFTs assimilated                       nn_asmpfts = ', nn_asmpfts 
    215279         WRITE(numout,*) '      Logical switch for Incremental Analysis Updating (IAU)   ln_asmiau = ', ln_asmiau 
    216280         WRITE(numout,*) '      Timestep of background in [0,nitend-nit000-1]            nitbkg    = ', nitbkg 
     
    223287         WRITE(numout,*) '      Minimum salinity after applying the increments           salfixmin = ', salfixmin 
    224288         WRITE(numout,*) '      Choice of MLD for physics assimilation                  mld_choice = ', mld_choice 
     289         WRITE(numout,*) '      Choice of MLD for BGC assimilation                  mld_choice_bgc = ', mld_choice_bgc 
    225290      ENDIF 
    226291 
     
    274339 
    275340      IF (      ( ( .NOT. ln_asmdin ).AND.( .NOT. ln_asmiau ) ) & 
    276            .AND.( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ) .OR. ( ln_seaiceinc) )) & 
    277          & CALL ctl_stop( ' One or more of ln_trainc, ln_dyninc, ln_sshinc and ln_seaiceinc is set to .true.', & 
     341         & .AND.( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ).OR.( ln_seaiceinc ).OR. & 
     342         &        ( ln_logchltotinc ).OR.( ln_logchlpftinc ) )) & 
     343         & CALL ctl_stop( ' One or more of ln_trainc, ln_dyninc, ln_sshinc, ln_seaiceinc,', & 
     344         &                ' ln_logchltotinc, and ln_logchlpftinc is set to .true.', & 
    278345         &                ' but ln_asmdin and ln_asmiau are both set to .false. :', & 
    279346         &                ' Inconsistent options') 
     
    284351 
    285352      IF ( ( .NOT. ln_trainc ).AND.( .NOT. ln_dyninc ).AND.( .NOT. ln_sshinc ).AND.( .NOT. ln_seaiceinc ) & 
    286          &                     )  & 
    287          & CALL ctl_warn( ' ln_trainc, ln_dyninc, ln_sshinc and ln_seaiceinc are set to .false. :', & 
     353         & .AND.( .NOT. ln_logchltotinc ).AND.( .NOT. ln_logchlpftinc ) )  & 
     354         & CALL ctl_warn( ' ln_trainc, ln_dyninc, ln_sshinc, ln_seaiceinc,', & 
     355         &                ' ln_logchltotinc, and ln_logchlpftinc are set to .false. :', & 
    288356         &                ' The assimilation increments are not applied') 
    289357 
     
    310378         &                ' Assim bkg averaging period is outside', & 
    311379         &                ' the cycle interval') 
     380 
     381      IF ( ( ln_logchltotinc ).AND.( ln_logchlpftinc ) ) THEN 
     382         CALL ctl_stop( ' ln_logchltotinc and ln_logchlpftinc both set:', & 
     383            &           ' These options are not compatible') 
     384      ENDIF 
     385 
     386      IF ( ( ln_balwri ).AND.( .NOT. ( ( ln_logchltotinc ).OR.( ln_logchlpftinc ) ) ) ) THEN 
     387         CALL ctl_warn( ' Balancing increments are only calculated for logchl', & 
     388            &           ' Not assimilating logchl, so ln_balwri will be set to .false.') 
     389         ln_balwri = .FALSE. 
     390      ENDIF 
    312391 
    313392      IF ( nstop > 0 ) RETURN       ! if there are any errors then go no further 
     
    412491      ssh_iau(:,:)    = 0.0 
    413492#endif 
    414       IF ( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ).OR.( ln_seaiceinc ) ) THEN 
     493      IF ( ( ln_logchltotinc ).OR.( ln_logchlpftinc ) ) THEN 
     494         ALLOCATE( logchl_bkginc(jpi,jpj,nn_asmpfts)) 
     495         logchl_bkginc(:,:,:) = 0.0 
     496#if defined key_top 
     497         ALLOCATE( logchl_balinc(jpi,jpj,jpk,jptra) ) 
     498         logchl_balinc(:,:,:,:) = 0.0 
     499#endif 
     500      ENDIF 
     501      IF ( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ).OR.( ln_seaiceinc ) & 
     502         &  .OR.( ln_logchltotinc ).OR.( ln_logchlpftinc ) ) THEN 
    415503 
    416504         !-------------------------------------------------------------------- 
     
    545633         ENDIF 
    546634 
     635         IF ( ln_logchltotinc ) THEN 
     636            CALL iom_get( inum, jpdom_autoglo, 'bckinlogchl', logchl_bkginc(:,:,1), 1 ) 
     637            ! Apply the masks 
     638            logchl_bkginc(:,:,1) = logchl_bkginc(:,:,1) * tmask(:,:,1) 
     639            ! Set missing increments to 0.0 rather than 1e+20 
     640            ! to allow for differences in masks 
     641            WHERE( ABS( logchl_bkginc(:,:,1) ) > 1.0e+10 ) logchl_bkginc(:,:,1) = 0.0 
     642         ENDIF 
     643 
     644         IF ( ln_logchlpftinc ) THEN 
     645            DO jt = 1, nn_asmpfts 
     646               WRITE(cl_pftstr,'(I2.2)') jt 
     647               CALL iom_get( inum, jpdom_autoglo, 'bckinlogchl'//cl_pftstr, logchl_bkginc(:,:,jt), 1 ) 
     648               ! Apply the masks 
     649               logchl_bkginc(:,:,jt) = logchl_bkginc(:,:,jt) * tmask(:,:,1) 
     650               ! Set missing increments to 0.0 rather than 1e+20 
     651               ! to allow for differences in masks 
     652               WHERE( ABS( logchl_bkginc(:,:,jt) ) > 1.0e+10 ) logchl_bkginc(:,:,jt) = 0.0 
     653            END DO 
     654         ENDIF 
     655 
    547656         CALL iom_close( inum ) 
    548657  
     
    12721381 
    12731382   END SUBROUTINE seaice_asm_inc 
     1383 
     1384   SUBROUTINE logchl_asm_inc( kt ) 
     1385      !!---------------------------------------------------------------------- 
     1386      !!                    ***  ROUTINE logchl_asm_inc  *** 
     1387      !!           
     1388      !! ** Purpose : Apply the chlorophyll assimilation increments. 
     1389      !! 
     1390      !! ** Method  : Calculate increments to state variables using nitrogen 
     1391      !!              balancing. 
     1392      !!              Direct initialization or Incremental Analysis Updating. 
     1393      !! 
     1394      !! ** Action  :  
     1395      !!---------------------------------------------------------------------- 
     1396      INTEGER, INTENT(IN) :: kt   ! Current time step 
     1397      ! 
     1398      INTEGER  :: jk              ! Loop counter 
     1399      INTEGER  :: it              ! Index 
     1400      REAL(wp) :: zincwgt         ! IAU weight for current time step 
     1401      REAL(wp) :: zincper         ! IAU interval in seconds 
     1402      !!---------------------------------------------------------------------- 
     1403 
     1404      IF ( kt <= nit000 ) THEN 
     1405 
     1406         zincper = (nitiaufin_r - nitiaustr_r + 1) * rdt 
     1407 
     1408#if defined key_fabm 
     1409         CALL asm_logchl_bal_ersem( ln_logchlpftinc, nn_asmpfts, mld_choice_bgc, & 
     1410            &                       logchl_bkginc, logchl_balinc ) 
     1411#elif defined key_medusa && defined key_foam_medusa 
     1412         !CALL asm_logchl_bal_medusa() 
     1413         CALL ctl_stop( 'Attempting to assimilate logchl into MEDUSA, ', & 
     1414            &           'but not fully implemented yet' ) 
     1415#elif defined key_hadocc 
     1416         !CALL asm_logchl_bal_hadocc() 
     1417         CALL ctl_stop( 'Attempting to assimilate logchl into HadOCC, ', & 
     1418            &           'but not fully implemented yet' ) 
     1419#else 
     1420         CALL ctl_stop( 'Attempting to assimilate logchl, ', & 
     1421            &           'but not defined a biogeochemical model' ) 
     1422#endif 
     1423 
     1424      ENDIF 
     1425 
     1426      IF ( ln_asmiau ) THEN 
     1427 
     1428         !-------------------------------------------------------------------- 
     1429         ! Incremental Analysis Updating 
     1430         !-------------------------------------------------------------------- 
     1431 
     1432         IF ( ( kt >= nitiaustr_r ).AND.( kt <= nitiaufin_r ) ) THEN 
     1433 
     1434            it = kt - nit000 + 1 
     1435            zincwgt = wgtiau(it)      ! IAU weight for the current time step 
     1436            ! note this is not a tendency so should not be divided by rdt 
     1437 
     1438            IF(lwp) THEN 
     1439               WRITE(numout,*)  
     1440               WRITE(numout,*) 'logchl_asm_inc : logchl IAU at time step = ', & 
     1441                  &  kt,' with IAU weight = ', wgtiau(it) 
     1442               WRITE(numout,*) '~~~~~~~~~~~~' 
     1443            ENDIF 
     1444 
     1445            ! Update the biogeochemical variables 
     1446            ! Add directly to trn and trb, rather than to tra, as not a tendency 
     1447#if defined key_fabm 
     1448            DO jk = 1, jpkm1 
     1449               trn(:,:,jk,jp_fabm0:jp_fabm1) = trn(:,:,jk,jp_fabm0:jp_fabm1) + & 
     1450                  &                            logchl_balinc(:,:,jk,jp_fabm0:jp_fabm1) * zincwgt 
     1451               trb(:,:,jk,jp_fabm0:jp_fabm1) = trb(:,:,jk,jp_fabm0:jp_fabm1) + & 
     1452                  &                            logchl_balinc(:,:,jk,jp_fabm0:jp_fabm1) * zincwgt 
     1453            END DO 
     1454#elif defined key_medusa && defined key_foam_medusa 
     1455            DO jk = 1, jpkm1 
     1456               trn(:,:,jk,jp_msa0:jp_msa1) = trn(:,:,jk,jp_msa0:jp_msa1) + & 
     1457                  &                          logchl_balinc(:,:,jk,jp_msa0:jp_msa1) * zincwgt 
     1458               trb(:,:,jk,jp_msa0:jp_msa1) = trb(:,:,jk,jp_msa0:jp_msa1) + & 
     1459                  &                          logchl_balinc(:,:,jk,jp_msa0:jp_msa1) * zincwgt 
     1460            END DO 
     1461#elif defined key_hadocc 
     1462            DO jk = 1, jpkm1 
     1463               trn(:,:,jk,jp_had0:jp_had1) = trn(:,:,jk,jp_had0:jp_had1) + & 
     1464                  &                          logchl_balinc(:,:,jk,jp_had0:jp_had1) * zincwgt 
     1465               trb(:,:,jk,jp_had0:jp_had1) = trb(:,:,jk,jp_had0:jp_had1) + & 
     1466                  &                          logchl_balinc(:,:,jk,jp_had0:jp_had1) * zincwgt 
     1467            END DO 
     1468#endif 
     1469            
     1470            ! Do not deallocate arrays - needed by asm_bal_wri 
     1471            ! which is called at end of model run 
     1472 
     1473         ENDIF 
     1474 
     1475      ELSEIF ( ln_asmdin ) THEN  
     1476 
     1477         !-------------------------------------------------------------------- 
     1478         ! Direct Initialization 
     1479         !-------------------------------------------------------------------- 
     1480          
     1481         IF ( kt == nitdin_r ) THEN 
     1482 
     1483            neuler = 0                    ! Force Euler forward step 
     1484 
     1485#if defined key_fabm 
     1486            ! Initialize the now fields with the background + increment 
     1487            ! Background currently is what the model is initialised with 
     1488            CALL ctl_warn( ' Doing direct initialisation of ERSEM with chlorophyll assimilation', & 
     1489               &           ' Background state is taken from model rather than background file' ) 
     1490            trn(:,:,:,jp_fabm0:jp_fabm1) = trn(:,:,:,jp_fabm0:jp_fabm1) + & 
     1491               &                           logchl_balinc(:,:,:,jp_fabm0:jp_fabm1) 
     1492            trb(:,:,:,jp_fabm0:jp_fabm1) = trn(:,:,:,jp_fabm0:jp_fabm1) 
     1493#elif defined key_medusa && defined key_foam_medusa 
     1494            ! Initialize the now fields with the background + increment 
     1495            ! Background currently is what the model is initialised with 
     1496            CALL ctl_warn( ' Doing direct initialisation of MEDUSA with chlorophyll assimilation', & 
     1497               &           ' Background state is taken from model rather than background file' ) 
     1498            trn(:,:,:,jp_msa0:jp_msa1) = trn(:,:,:,jp_msa0:jp_msa1) + & 
     1499               &                         logchl_balinc(:,:,:,jp_msa0:jp_msa1) 
     1500            trb(:,:,:,jp_msa0:jp_msa1) = trn(:,:,:,jp_msa0:jp_msa1) 
     1501#elif defined key_hadocc 
     1502            ! Initialize the now fields with the background + increment 
     1503            ! Background currently is what the model is initialised with 
     1504            CALL ctl_warn( ' Doing direct initialisation of HadOCC with chlorophyll assimilation', & 
     1505               &           ' Background state is taken from model rather than background file' ) 
     1506            trn(:,:,:,jp_had0:jp_had1) = trn(:,:,:,jp_had0:jp_had1) + & 
     1507               &                         logchl_balinc(:,:,:,jp_had0:jp_had1) 
     1508            trb(:,:,:,jp_had0:jp_had1) = trn(:,:,:,jp_had0:jp_had1) 
     1509#endif 
     1510  
     1511            ! Do not deallocate arrays - needed by asm_bal_wri 
     1512            ! which is called at end of model run 
     1513         ENDIF 
     1514         ! 
     1515      ENDIF 
     1516      ! 
     1517   END SUBROUTINE logchl_asm_inc 
    12741518    
    12751519   !!====================================================================== 
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ASM/asmpar.F90

    r7477 r7726  
    2020      & c_asmtrj = 'assim_trj',                  & !: Filename for storing the  
    2121                                                   !: reference trajectory 
    22       & c_asminc = 'assim_background_increments'  !: Filename for storing the  
     22      & c_asminc = 'assim_background_increments', & !: Filename for storing the  
    2323                                                   !: increments to the background 
    2424                                                   !: state 
     25      & c_asmbal = 'assim.balincs'                 !: Filename for storing the  
     26                                                   !: balancing increments calculated 
     27                                                   !: for biogeochemistry 
    2528 
    2629   INTEGER, PUBLIC :: nitbkg_r      !: Background time step referenced to nit000 
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6661 r7726  
    6161   USE asminc          ! assimilation increments      
    6262   USE asmbkg          ! writing out state trajectory 
     63   USE asmbal          ! writing out assimilation balancing increments 
    6364   USE diaptr          ! poleward transports           (dia_ptr_init routine) 
    6465   USE diadct          ! sections transports           (dia_dct_init routine) 
     
    158159                IF( ln_dyninc ) CALL dyn_asm_inc( nit000 - 1 )    ! Dynamics 
    159160                IF( ln_sshinc ) CALL ssh_asm_inc( nit000 - 1 )    ! SSH 
     161                IF( ln_logchltotinc .OR. ln_logchlpftinc ) CALL logchl_asm_inc( nit000 - 1 ) 
    160162             ENDIF 
    161163          ENDIF 
     
    177179 
    178180      IF( lk_diaobs   )   CALL dia_obs_wri 
     181      ! 
     182      IF( ( lk_asminc ).AND.( ln_balwri ) ) CALL asm_bal_wri( nitend )  ! Output balancing increments 
    179183      ! 
    180184      IF( ln_icebergs )   CALL icb_end( nitend ) 
  • branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/step.F90

    r7477 r7726  
    242242      ! Passive Tracer Model 
    243243      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     244      IF( lk_asminc .AND. ln_asmiau .AND. ( ln_logchltotinc .OR. ln_logchlpftinc ) ) & 
     245         &               CALL logchl_asm_inc( kstp )  ! logchl assimilation 
    244246                         CALL trc_stp( kstp )         ! time-stepping 
    245247#endif 
Note: See TracChangeset for help on using the changeset viewer.