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

Changeset 2396


Ignore:
Timestamp:
2010-11-16T11:18:23+01:00 (13 years ago)
Author:
cbricaud
Message:

add modifications for atmopheric pressure forcing

Location:
branches/nemo_v3_3_beta/NEMOGCM
Files:
1 added
9 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/CONFIG/GYRE/EXP00/namelist

    r2375 r2396  
    128128   ln_blk_core = .false.   !  CORE bulk formulation  (T => fill namsbc_core)  
    129129   ln_cpl      = .false.   !  Coupled formulation    (T => fill namsbc_cpl ) 
     130   ln_apr_dyn  = .false.   !  Patm gradient added in ocean & ice Eqs.   (T => fill namsbc_apr ) 
    130131   nn_ice      = 0         !  =0 no ice boundary condition   , 
    131132                           !  =1 use observed ice-cover      , 
     
    237238   ln_rnf_tem   =  .false.  !  read in temperature information for runoff 
    238239   ln_rnf_sal   =  .false.  !  read in salinity information for runoff 
     240/ 
     241!----------------------------------------------------------------------- 
     242&namsbc_apr    !   Atmospheric pressure used as ocean forcing or in bulk 
     243!----------------------------------------------------------------------- 
     244!              ! file name ! frequency (hours) ! variable ! time interpol. !  clim   ! 'yearly'/ ! weights  ! rotation ! 
     245!              !           !  (if <0  months)  !   name   !    (logical)   !  (T/F)  ! 'monthly' ! filename ! pairing  ! 
     246   sn_apr      = 'patm'    ,         -1        , 'somslpre',    .true.      , .true.  , 'yearly'  ,  ''      ,   '' 
     247! 
     248   cn_dir      = './'      !  root directory for the location of the bulk files 
     249   ln_ref_apr  = .false.   !  ref. pressure: global mean Patm (T) or a constant (F) 
    239250/ 
    240251!----------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/CONFIG/GYRE_LOBSTER/EXP00/namelist

    r2378 r2396  
    128128   ln_blk_core = .false.   !  CORE bulk formulation  (T => fill namsbc_core)  
    129129   ln_cpl      = .false.   !  Coupled formulation    (T => fill namsbc_cpl ) 
     130   ln_apr_dyn  = .false.   !  Patm gradient added in ocean & ice Eqs.   (T => fill namsbc_apr ) 
    130131   nn_ice      = 0         !  =0 no ice boundary condition   , 
    131132                           !  =1 use observed ice-cover      , 
     
    237238   ln_rnf_tem   =  .false.  !  read in temperature information for runoff 
    238239   ln_rnf_sal   =  .false.  !  read in salinity information for runoff 
     240/ 
     241!----------------------------------------------------------------------- 
     242&namsbc_apr    !   Atmospheric pressure used as ocean forcing or in bulk 
     243!----------------------------------------------------------------------- 
     244!              ! file name ! frequency (hours) ! variable ! time interpol. !  clim   ! 'yearly'/ ! weights  ! rotation ! 
     245!              !           !  (if <0  months)  !   name   !    (logical)   !  (T/F)  ! 'monthly' ! filename ! pairing  ! 
     246   sn_apr      = 'patm'    ,         -1        , 'somslpre',    .true.      , .true.  , 'yearly'  ,  ''      ,   '' 
     247! 
     248   cn_dir      = './'      !  root directory for the location of the bulk files 
     249   ln_ref_apr  = .false.   !  ref. pressure: global mean Patm (T) or a constant (F) 
    239250/ 
    240251!----------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/CONFIG/ORCA2_LIM/EXP00/1_namelist

    r2375 r2396  
    128128   ln_blk_core = .true.    !  CORE bulk formulation  (T => fill namsbc_core)  
    129129   ln_cpl      = .false.   !  Coupled formulation    (T => fill namsbc_cpl ) 
     130   ln_apr_dyn  = .false.   !  Patm gradient added in ocean & ice Eqs.   (T => fill namsbc_apr ) 
    130131   nn_ice      = 0         !  =0 no ice boundary condition   , 
    131132                           !  =1 use observed ice-cover      , 
     
    232233   rn_avt_rnf   =   1.e-3   !  value of the additional vertical mixing coef. [m2/s] 
    233234   rn_rfact     =   1.e0    !  multiplicative factor for runoff 
     235/ 
     236!----------------------------------------------------------------------- 
     237&namsbc_apr    !   Atmospheric pressure used as ocean forcing or in bulk 
     238!----------------------------------------------------------------------- 
     239!              ! file name ! frequency (hours) ! variable ! time interpol. !  clim   ! 'yearly'/ ! weights  ! rotation ! 
     240!              !           !  (if <0  months)  !   name   !    (logical)   !  (T/F)  ! 'monthly' ! filename ! pairing  ! 
     241   sn_apr      = 'patm'    ,         -1        , 'somslpre',    .true.      , .true.  , 'yearly'  ,  ''      ,   '' 
     242! 
     243   cn_dir      = './'      !  root directory for the location of the bulk files 
     244   ln_ref_apr  = .false.   !  ref. pressure: global mean Patm (T) or a constant (F) 
    234245/ 
    235246!----------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/CONFIG/ORCA2_LIM/EXP00/namelist

    r2375 r2396  
    128128   ln_blk_core = .true.    !  CORE bulk formulation  (T => fill namsbc_core)  
    129129   ln_cpl      = .false.   !  Coupled formulation    (T => fill namsbc_cpl ) 
     130   ln_apr_dyn  = .false.   !  Patm gradient added in ocean & ice Eqs.   (T => fill namsbc_apr ) 
    130131   nn_ice      = 2         !  =0 no ice boundary condition   , 
    131132                           !  =1 use observed ice-cover      , 
     
    264265   ln_rnf_tem   =  .false.  !  read in temperature information for runoff 
    265266   ln_rnf_sal   =  .false.  !  read in salinity information for runoff 
     267/ 
     268!----------------------------------------------------------------------- 
     269&namsbc_apr    !   Atmospheric pressure used as ocean forcing or in bulk 
     270!----------------------------------------------------------------------- 
     271!              ! file name ! frequency (hours) ! variable ! time interpol. !  clim   ! 'yearly'/ ! weights  ! rotation ! 
     272!              !           !  (if <0  months)  !   name   !    (logical)   !  (T/F)  ! 'monthly' ! filename ! pairing  ! 
     273   sn_apr      = 'patm'    ,         -1        , 'somslpre',    .true.      , .true.  , 'yearly'  ,  ''      ,   '' 
     274! 
     275   cn_dir      = './'      !  root directory for the location of the bulk files 
     276   ln_ref_apr  = .false.   !  ref. pressure: global mean Patm (T) or a constant (F) 
    266277/ 
    267278!----------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/CONFIG/ORCA2_LIM_PISCES/EXP00/namelist

    r2375 r2396  
    128128   ln_blk_core = .true.    !  CORE bulk formulation  (T => fill namsbc_core)  
    129129   ln_cpl      = .false.   !  Coupled formulation    (T => fill namsbc_cpl ) 
     130   ln_apr_dyn  = .false.   !  Patm gradient added in ocean & ice Eqs.   (T => fill namsbc_apr ) 
    130131   nn_ice      = 2         !  =0 no ice boundary condition   , 
    131132                           !  =1 use observed ice-cover      , 
     
    264265   ln_rnf_tem   =  .false.  !  read in temperature information for runoff 
    265266   ln_rnf_sal   =  .false.  !  read in salinity information for runoff 
     267/ 
     268!----------------------------------------------------------------------- 
     269&namsbc_apr    !   Atmospheric pressure used as ocean forcing or in bulk 
     270!----------------------------------------------------------------------- 
     271!              ! file name ! frequency (hours) ! variable ! time interpol. !  clim   ! 'yearly'/ ! weights  ! rotation ! 
     272!              !           !  (if <0  months)  !   name   !    (logical)   !  (T/F)  ! 'monthly' ! filename ! pairing  ! 
     273   sn_apr      = 'patm'    ,         -1        , 'somslpre',    .true.      , .true.  , 'yearly'  ,  ''      ,   '' 
     274! 
     275   cn_dir      = './'      !  root directory for the location of the bulk files 
     276   ln_ref_apr  = .false.   !  ref. pressure: global mean Patm (T) or a constant (F) 
    266277/ 
    267278!----------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r2392 r2396  
    1515   USE dom_oce        ! ocean space and time domain variables 
    1616   USE obc_oce        ! ocean open boundary conditions 
     17   USE sbc_oce        ! surface boundary condition: ocean 
     18   USE sbcapr         ! surface boundary condition: atmospheric pressure 
    1719   USE dynspg_oce     ! surface pressure gradient variables 
    1820   USE dynspg_exp     ! surface pressure gradient     (dyn_spg_exp routine) 
    1921   USE dynspg_ts      ! surface pressure gradient     (dyn_spg_ts  routine) 
    2022   USE dynspg_flt     ! surface pressure gradient     (dyn_spg_flt routine) 
    21    USE dynadv          ! dynamics: vector invariant versus flux form 
     23   USE dynadv         ! dynamics: vector invariant versus flux form 
    2224   USE trdmod         ! ocean dynamics trends 
    2325   USE trdmod_oce     ! ocean variables trends 
    2426   USE prtctl         ! Print control                     (prt_ctl routine) 
    2527   USE in_out_manager ! I/O manager 
     28   USE phycst         ! physical constants 
    2629 
    2730   IMPLICIT NONE 
     
    4952      !! 
    5053      !! ** Purpose :   achieve the momentum time stepping by computing the 
    51       !!              last trend, the surface pressure gradient, and performing 
     54      !!              last trend, the surface pressure gradient including the  
     55      !!              atmospheric pressure forcing (ln_apr_dyn=T), and performing 
    5256      !!              the Leap-Frog integration. 
    5357      !!gm              In the current version only the filtered solution provide 
     
    5963      !!              - split-explicit computation: a time splitting technique is used 
    6064      !! 
     65      !!              ln_apr_dyn=T : the atmospheric pressure forcing is applied  
     66      !!             as the gradient of the inverse barometer ssh: 
     67      !!                apgu = - 1/rau0 di[apr] = 0.5*grav di[ssh_ib+ssh_ibb] 
     68      !!                apgv = - 1/rau0 dj[apr] = 0.5*grav dj[ssh_ib+ssh_ibb] 
     69      !!             Note that as all external forcing a time averaging over a two rdt 
     70      !!             period is used to prevent the divergence of odd and even time step. 
     71      !! 
    6172      !! N.B. : When key_esopa is used all the scheme are tested, regardless  
    6273      !!        of the physical meaning of the results.  
     
    6677      !! 
    6778      REAL(wp) ::   z2dt   ! temporary scalar 
     79      INTEGER  ::   ji, jj, jk                             ! dummy loop indices 
     80      REAL(wp) ::   z2dt, zg_2                             ! temporary scalar 
    6881      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrdu, ztrdv   ! 3D workspace 
    6982      !!---------------------------------------------------------------------- 
     
    8093         ztrdv(:,:,:) = va(:,:,:) 
    8194      ENDIF 
     95 
     96      IF( ln_apr_dyn ) THEN                   !==  Atmospheric pressure gradient  ==! 
     97         zg_2 = grav * 0.5 
     98         DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh 
     99            DO ji = fs_2, fs_jpim1   ! vector opt. 
     100               spgu(ji,jj) =  zg_2 * (  ssh_ib (ji+1,jj) - ssh_ib (ji,jj)    & 
     101                  &                   + ssh_ibb(ji+1,jj) - ssh_ibb(ji,jj)  ) /e1u(ji,jj) 
     102               spgv(ji,jj) =  zg_2 * (  ssh_ib (ji,jj+1) - ssh_ib (ji,jj)    & 
     103                  &                   + ssh_ibb(ji,jj+1) - ssh_ib (ji,jj)  ) /e2v(ji,jj) 
     104            END DO 
     105         END DO 
     106         DO jk = 1, jpkm1                          ! Add the apg to the general trend 
     107            DO jj = 2, jpjm1 
     108               DO ji = fs_2, fs_jpim1   ! vector opt. 
     109                  ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj) 
     110                  va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj) 
     111               END DO 
     112            END DO 
     113         END DO 
     114      ENDIF 
     115 
    82116 
    83117      SELECT CASE ( nspg )                       ! compute surf. pressure gradient trend and add it to the general trend 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r2370 r2396  
    88   !!            3.3  ! 2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps 
    99   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step 
     10   !!            3.3  ! 2010-10  (J. Chanut, C. Bricaud)  add the surface pressure forcing 
    1011   !!---------------------------------------------------------------------- 
    1112   USE par_oce          ! ocean parameters 
     
    2627   LOGICAL , PUBLIC ::   ln_rnf      = .FALSE.   !: runoffs / runoff mouths 
    2728   LOGICAL , PUBLIC ::   ln_ssr      = .FALSE.   !: Sea Surface restoring on SST and/or SSS       
     29   LOGICAL , PUBLIC ::   ln_apr_dyn  = .FALSE.   !: Atmospheric pressure forcing used on dynamics (ocean & ice) 
    2830   INTEGER , PUBLIC ::   nn_ice      = 0         !: flag on ice in the surface boundary condition (=0/1/2/3) 
    2931   INTEGER , PUBLIC ::   nn_fwb      = 0         !: FreshWater Budget:  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r2390 r2396  
    1010   !!            3.3  ! 2010-09  (D. Storkey) add ice boundary conditions (BDY) 
    1111   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step 
     12   !!             -   ! 2010-10  (J. Chanut, C. Bricaud, G. Madec)  add the surface pressure forcing 
    1213   !!---------------------------------------------------------------------- 
    1314 
     
    2324   USE sbcdcy           ! surface boundary condition: diurnal cycle 
    2425   USE sbcssm           ! surface boundary condition: sea-surface mean variables 
     26   USE sbcapr           ! surface boundary condition: atmospheric pressure 
    2527   USE sbcana           ! surface boundary condition: analytical formulation 
    2628   USE sbcflx           ! surface boundary condition: flux formulation 
     
    7577      !! 
    7678      NAMELIST/namsbc/ nn_fsbc, ln_ana  , ln_flx, ln_blk_clio, ln_blk_core, ln_cpl    ,   & 
    77          &             nn_ice , ln_dm2dc, ln_rnf, ln_ssr     , nn_fwb 
     79         &             ln_apr_dyn, nn_ice , ln_dm2dc, ln_rnf, ln_ssr     , nn_fwb 
    7880      !!---------------------------------------------------------------------- 
    7981 
     
    107109         WRITE(numout,*) '              coupled    formulation (T if key_sbc_cpl)  ln_cpl      = ', ln_cpl 
    108110         WRITE(numout,*) '           Misc. options of sbc : ' 
     111         WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn  = ', ln_apr_dyn 
    109112         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice      = ', nn_ice  
    110113         WRITE(numout,*) '              daily mean to diurnal cycle qsr            ln_dm2dc    = ', ln_dm2dc  
     
    213216 
    214217      CALL iom_setkt( kt + nn_fsbc - 1 )                 ! in sbc, iom_put is called every nn_fsbc time step 
     218      ! 
     219      IF( ln_apr_dyn ) CALL sbc_apr( kt )                ! atmospheric pressure provided at kt+0.5*nn_fsbc 
     220                                                         ! (caution called before sbc_ssm) 
    215221      ! 
    216222      CALL sbc_ssm( kt )                                 ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssm.F90

    r2287 r2396  
    55   !!====================================================================== 
    66   !! History :  9.0   !  06-07  (G. Madec)  Original code 
     7   !!            3.3  ! 2010-10  (C. Bricaud, G. Madec)  add the Patm forcing for sea-ice 
    78   !!---------------------------------------------------------------------- 
    89 
     
    1415   USE dom_oce         ! ocean space and time domain 
    1516   USE sbc_oce         ! Surface boundary condition: ocean fields 
     17   USE sbc_oce         ! surface boundary condition: ocean fields 
     18   USE sbcapr          ! surface boundary condition: atmospheric pressure 
    1619   USE prtctl          ! Print control                    (prt_ctl routine) 
    1720   USE restart         ! ocean restart 
     
    4447      !!      V-points) [m/s], temperature [Celcius] and salinity [psu] over 
    4548      !!      the periode (kt - nn_fsbc) to kt 
     49      !!         Note that the inverse barometer ssh (i.e. ssh associated with Patm) 
     50      !!      is add to ssh_m when ln_apr_dyn = T. Required for sea-ice dynamics. 
    4651      !!--------------------------------------------------------------------- 
    4752      INTEGER, INTENT(in) ::   kt        ! ocean time step 
     
    6368         sst_m(:,:) = tn(:,:,1) 
    6469         sss_m(:,:) = sn(:,:,1) 
    65          ssh_m(:,:) = sshn(:,:) 
     70         !                          ! removed inverse barometer ssh when Patm forcing is used (for sea-ice dynamics) 
     71         IF( ln_apr_dyn ) THEN   ;   ssh_m(:,:) = sshn(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) ) 
     72         ELSE                    ;   ssh_m(:,:) = sshn(:,:) 
     73         ENDIF 
     74 
    6675         ! 
    6776      ELSE 
     
    99108               sst_m(:,:) = zcoef * tn(:,:,1) 
    100109               sss_m(:,:) = zcoef * sn(:,:,1) 
    101                ssh_m(:,:) = zcoef * sshn(:,:) 
     110               !                          ! removed inverse barometer ssh when Patm forcing is used  
     111               IF( ln_apr_dyn ) THEN   ;   ssh_m(:,:) = zcoef * ( sshn(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) ) ) 
     112               ELSE                    ;   ssh_m(:,:) = zcoef *   sshn(:,:) 
     113               ENDIF 
     114 
    102115            ENDIF 
    103116            !                                             ! ---------------------------------------- ! 
     
    117130         sst_m(:,:) = sst_m(:,:) + tn(:,:,1) 
    118131         sss_m(:,:) = sss_m(:,:) + sn(:,:,1) 
    119          ssh_m(:,:) = ssh_m(:,:) + sshn(:,:) 
     132         !                          ! removed inverse barometer ssh when Patm forcing is used (for sea-ice dynamics) 
     133         IF( ln_apr_dyn ) THEN   ;   ssh_m(:,:) = ssh_m(:,:) + sshn(:,:) - 0.5 *  ( ssh_ib(:,:) + ssh_ibb(:,:) ) 
     134         ELSE                    ;   ssh_m(:,:) = ssh_m(:,:) + sshn(:,:) 
     135         ENDIF 
    120136 
    121137         !                                                ! ---------------------------------------- ! 
Note: See TracChangeset for help on using the changeset viewer.