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 9213 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90 – NEMO

Ignore:
Timestamp:
2018-01-12T10:38:50+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: nemogcm.F90 : updated in SAS & OFF + data assimilation initial calls (asm_bkg_wri , tra_asm_inc ...) moved to asm_inc_init + closed sea : restructure namcfg & its control print + set ln_closea = false if domcfg file not read (ln_domcfg=F

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r9168 r9213  
    7474   REAL(wp), PUBLIC, DIMENSION(:)    , ALLOCATABLE ::   wgtiau               !: IAU weights for each time step 
    7575#if defined key_asminc 
    76    REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ssh_iau           !: IAU-weighted sea surface height increment 
     76   REAL(wp), PUBLIC, DIMENSION(:,:)  , ALLOCATABLE ::   ssh_iau              !: IAU-weighted sea surface height increment 
    7777#endif 
    7878   !                                !!! time steps relative to the cycle interval [0,nitend-nit000-1] 
     
    254254      !-------------------------------------------------------------------- 
    255255 
    256       IF ( ln_asmiau ) THEN 
    257  
     256      IF( ln_asmiau ) THEN 
     257         ! 
    258258         ALLOCATE( wgtiau( icycper ) ) 
    259  
     259         ! 
    260260         wgtiau(:) = 0._wp 
    261  
    262          IF ( niaufn == 0 ) THEN 
    263  
    264             !--------------------------------------------------------- 
    265             ! Constant IAU forcing  
    266             !--------------------------------------------------------- 
    267  
     261         ! 
     262         !                                !--------------------------------------------------------- 
     263         IF( niaufn == 0 ) THEN           ! Constant IAU forcing  
     264            !                             !--------------------------------------------------------- 
    268265            DO jt = 1, iiauper 
    269266               wgtiau(jt+nitiaustr-1) = 1.0 / REAL( iiauper ) 
    270267            END DO 
    271  
    272          ELSEIF ( niaufn == 1 ) THEN 
    273  
    274             !--------------------------------------------------------- 
    275             ! Linear hat-like, centred in middle of IAU interval  
    276             !--------------------------------------------------------- 
    277  
     268            !                             !--------------------------------------------------------- 
     269         ELSEIF ( niaufn == 1 ) THEN      ! Linear hat-like, centred in middle of IAU interval  
     270            !                             !--------------------------------------------------------- 
    278271            ! Compute the normalization factor 
    279             znorm = 0.0 
    280             IF ( MOD( iiauper, 2 ) == 0 ) THEN  ! Even number of time steps in IAU interval 
     272            znorm = 0._wp 
     273            IF( MOD( iiauper, 2 ) == 0 ) THEN   ! Even number of time steps in IAU interval 
    281274               imid = iiauper / 2  
    282275               DO jt = 1, imid 
     
    284277               END DO 
    285278               znorm = 2.0 * znorm 
    286             ELSE                               ! Odd number of time steps in IAU interval 
     279            ELSE                                ! Odd number of time steps in IAU interval 
    287280               imid = ( iiauper + 1 ) / 2         
    288281               DO jt = 1, imid - 1 
     
    292285            ENDIF 
    293286            znorm = 1.0 / znorm 
    294  
     287            ! 
    295288            DO jt = 1, imid - 1 
    296289               wgtiau(jt+nitiaustr-1) = REAL( jt ) * znorm 
     
    299292               wgtiau(jt+nitiaustr-1) = REAL( iiauper - jt + 1 ) * znorm 
    300293            END DO 
    301  
     294            ! 
    302295         ENDIF 
    303296 
     
    325318      !-------------------------------------------------------------------- 
    326319 
    327       ALLOCATE( t_bkginc(jpi,jpj,jpk) ) 
    328       ALLOCATE( s_bkginc(jpi,jpj,jpk) ) 
    329       ALLOCATE( u_bkginc(jpi,jpj,jpk) ) 
    330       ALLOCATE( v_bkginc(jpi,jpj,jpk) ) 
    331       ALLOCATE( ssh_bkginc(jpi,jpj)   ) 
    332       ALLOCATE( seaice_bkginc(jpi,jpj)) 
    333       t_bkginc     (:,:,:) = 0._wp 
    334       s_bkginc     (:,:,:) = 0._wp 
    335       u_bkginc     (:,:,:) = 0._wp 
    336       v_bkginc     (:,:,:) = 0._wp 
    337       ssh_bkginc   (:,:)   = 0._wp 
    338       seaice_bkginc(:,:)   = 0._wp 
     320      ALLOCATE( t_bkginc     (jpi,jpj,jpk) )   ;   t_bkginc     (:,:,:) = 0._wp 
     321      ALLOCATE( s_bkginc     (jpi,jpj,jpk) )   ;   s_bkginc     (:,:,:) = 0._wp 
     322      ALLOCATE( u_bkginc     (jpi,jpj,jpk) )   ;   u_bkginc     (:,:,:) = 0._wp 
     323      ALLOCATE( v_bkginc     (jpi,jpj,jpk) )   ;   v_bkginc     (:,:,:) = 0._wp 
     324      ALLOCATE( ssh_bkginc   (jpi,jpj)     )   ;   ssh_bkginc   (:,:)   = 0._wp 
     325      ALLOCATE( seaice_bkginc(jpi,jpj)     )   ;   seaice_bkginc(:,:)   = 0._wp 
    339326#if defined key_asminc 
    340       ALLOCATE( ssh_iau(jpi,jpj)      ) 
    341       ssh_iau      (:,:)   = 0._wp 
     327      ALLOCATE( ssh_iau      (jpi,jpj)     )   ;   ssh_iau      (:,:)   = 0._wp 
    342328#endif 
    343329#if defined key_cice && defined key_asminc 
    344       ALLOCATE( ndaice_da(jpi,jpj)    ) 
    345       ndaice_da    (:,:)   = 0._wp 
    346 #endif 
    347       IF ( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ).OR.( ln_seaiceinc ) ) THEN 
    348  
    349          !-------------------------------------------------------------------- 
    350          ! Read the increments from file 
    351          !-------------------------------------------------------------------- 
    352  
     330      ALLOCATE( ndaice_da    (jpi,jpj)     )   ;   ndaice_da    (:,:)   = 0._wp 
     331#endif 
     332      ! 
     333      IF ( ln_trainc .OR. ln_dyninc .OR.   &       !-------------------------------------- 
     334         & ln_sshinc .OR. ln_seaiceinc   ) THEN    ! Read the increments from file 
     335         !                                         !-------------------------------------- 
    353336         CALL iom_open( c_asminc, inum ) 
    354  
    355          CALL iom_get( inum, 'time', zdate_inc )  
    356  
     337         ! 
     338         CALL iom_get( inum, 'time'       , zdate_inc   )  
    357339         CALL iom_get( inum, 'z_inc_dateb', z_inc_dateb ) 
    358340         CALL iom_get( inum, 'z_inc_datef', z_inc_datef ) 
    359341         z_inc_dateb = zdate_inc 
    360342         z_inc_datef = zdate_inc 
    361  
     343         ! 
    362344         IF(lwp) THEN 
    363345            WRITE(numout,*)  
    364             WRITE(numout,*) 'asm_inc_init : Assimilation increments valid ', & 
    365                &            ' between dates ', z_inc_dateb,' and ',  & 
    366                &            z_inc_datef 
     346            WRITE(numout,*) 'asm_inc_init : Assimilation increments valid between dates ', z_inc_dateb,' and ', z_inc_datef 
    367347            WRITE(numout,*) '~~~~~~~~~~~~' 
    368348         ENDIF 
    369  
    370          IF (     ( z_inc_dateb < ndastp + nn_time0*0.0001_wp ) & 
    371             & .OR.( z_inc_datef > ditend_date ) ) & 
    372             & CALL ctl_warn( ' Validity time of assimilation increments is ', & 
    373             &                ' outside the assimilation interval' ) 
     349         ! 
     350         IF ( ( z_inc_dateb < ndastp + nn_time0*0.0001_wp ) .OR.  & 
     351            & ( z_inc_datef > ditend_date ) ) & 
     352            &    CALL ctl_warn( ' Validity time of assimilation increments is ', & 
     353            &                   ' outside the assimilation interval' ) 
    374354 
    375355         IF ( ( ln_asmdin ).AND.( zdate_inc /= ditdin_date ) ) & 
     
    418398            WHERE( ABS( seaice_bkginc(:,:) ) > 1.0e+10 ) seaice_bkginc(:,:) = 0.0 
    419399         ENDIF 
    420  
     400         ! 
    421401         CALL iom_close( inum ) 
    422   
    423       ENDIF 
    424  
    425       !----------------------------------------------------------------------- 
    426       ! Apply divergence damping filter 
    427       !----------------------------------------------------------------------- 
    428  
    429       IF ( ln_dyninc .AND. nn_divdmp > 0 ) THEN 
    430          ! 
     402         ! 
     403      ENDIF 
     404      ! 
     405      !                                            !-------------------------------------- 
     406      IF ( ln_dyninc .AND. nn_divdmp > 0 ) THEN    ! Apply divergence damping filter 
     407         !                                         !-------------------------------------- 
    431408         ALLOCATE( zhdiv(jpi,jpj) )  
    432409         ! 
     
    460437         ! 
    461438      ENDIF 
    462  
    463       !----------------------------------------------------------------------- 
    464       ! Allocate and initialize the background state arrays 
    465       !----------------------------------------------------------------------- 
    466  
    467       IF ( ln_asmdin ) THEN 
    468          ! 
    469          ALLOCATE( t_bkg(jpi,jpj,jpk) ) 
    470          ALLOCATE( s_bkg(jpi,jpj,jpk) ) 
    471          ALLOCATE( u_bkg(jpi,jpj,jpk) ) 
    472          ALLOCATE( v_bkg(jpi,jpj,jpk) ) 
    473          ALLOCATE( ssh_bkg(jpi,jpj)   ) 
    474          ! 
    475          t_bkg(:,:,:) = 0._wp 
    476          s_bkg(:,:,:) = 0._wp 
    477          u_bkg(:,:,:) = 0._wp 
    478          v_bkg(:,:,:) = 0._wp 
    479          ssh_bkg(:,:) = 0._wp 
     439      ! 
     440      !                             !----------------------------------------------------- 
     441      IF ( ln_asmdin ) THEN         ! Allocate and initialize the background state arrays 
     442         !                          !----------------------------------------------------- 
     443         ! 
     444         ALLOCATE( t_bkg  (jpi,jpj,jpk) )   ;   t_bkg  (:,:,:) = 0._wp 
     445         ALLOCATE( s_bkg  (jpi,jpj,jpk) )   ;   s_bkg  (:,:,:) = 0._wp 
     446         ALLOCATE( u_bkg  (jpi,jpj,jpk) )   ;   u_bkg  (:,:,:) = 0._wp 
     447         ALLOCATE( v_bkg  (jpi,jpj,jpk) )   ;   v_bkg  (:,:,:) = 0._wp 
     448         ALLOCATE( ssh_bkg(jpi,jpj)     )   ;   ssh_bkg(:,:)   = 0._wp 
     449         ! 
    480450         ! 
    481451         !-------------------------------------------------------------------- 
     
    489459         IF(lwp) THEN 
    490460            WRITE(numout,*)  
    491             WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', & 
    492                &  zdate_bkg 
    493             WRITE(numout,*) '~~~~~~~~~~~~' 
    494          ENDIF 
    495          ! 
    496          IF ( zdate_bkg /= ditdin_date ) & 
     461            WRITE(numout,*) '   ==>>>  Assimilation background state valid at : ', zdate_bkg 
     462            WRITE(numout,*) 
     463         ENDIF 
     464         ! 
     465         IF ( zdate_bkg /= ditdin_date )   & 
    497466            & CALL ctl_warn( ' Validity time of assimilation background state does', & 
    498467            &                ' not agree with Direct Initialization time' ) 
     
    521490      ENDIF 
    522491      ! 
     492      IF(lwp) WRITE(numout,*) '   ==>>>   Euler time step switch is ', neuler 
     493      ! 
     494      IF( lk_asminc ) THEN                            !==  data assimilation  ==! 
     495         IF( ln_bkgwri )   CALL asm_bkg_wri( nit000 - 1 )      ! Output background fields 
     496         IF( ln_asmdin ) THEN                                  ! Direct initialization 
     497            IF( ln_trainc )   CALL tra_asm_inc( nit000 - 1 )      ! Tracers 
     498            IF( ln_dyninc )   CALL dyn_asm_inc( nit000 - 1 )      ! Dynamics 
     499            IF( ln_sshinc )   CALL ssh_asm_inc( nit000 - 1 )      ! SSH 
     500         ENDIF 
     501      ENDIF 
     502      ! 
    523503   END SUBROUTINE asm_inc_init 
     504    
     505    
    524506   SUBROUTINE tra_asm_inc( kt ) 
    525507      !!---------------------------------------------------------------------- 
     
    786768   END SUBROUTINE ssh_asm_inc 
    787769 
     770 
    788771   SUBROUTINE ssh_asm_div( kt, phdivn ) 
    789772      !!---------------------------------------------------------------------- 
     
    824807   END SUBROUTINE ssh_asm_div 
    825808 
     809 
    826810   SUBROUTINE seaice_asm_inc( kt, kindic ) 
    827811      !!---------------------------------------------------------------------- 
     
    886870            ! seaice salinity balancing (to add) 
    887871#endif 
    888  
     872            ! 
    889873#if defined key_cice && defined key_asminc 
    890874            ! Sea-ice : CICE case. Pass ice increment tendency into CICE 
    891875            ndaice_da(:,:) = seaice_bkginc(:,:) * zincwgt / rdt 
    892876#endif 
    893  
     877            ! 
    894878            IF ( kt == nitiaufin_r ) THEN 
    895879               DEALLOCATE( seaice_bkginc ) 
    896880            ENDIF 
    897  
     881            ! 
    898882         ELSE 
    899  
     883            ! 
    900884#if defined key_cice && defined key_asminc 
    901885            ndaice_da(:,:) = 0._wp        ! Sea-ice : CICE case. Zero ice increment tendency into CICE 
    902886#endif 
    903  
     887            ! 
    904888         ENDIF 
    905889         !                          !----------------------------------------- 
     
    949933#if defined key_cice && defined key_asminc 
    950934            ndaice_da(:,:) = 0._wp     ! Sea-ice : CICE case. Zero ice increment tendency into CICE 
    951  
    952935#endif 
    953936            ! 
Note: See TracChangeset for help on using the changeset viewer.