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 9169 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90 – NEMO

Ignore:
Timestamp:
2017-12-26T17:32:56+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90

    r9125 r9169  
    44   !! TOP :   PISCES CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE 
    55   !!====================================================================== 
    6    !! History :    -   !  1988-07  (E. MAIER-REIMER) Original code 
    7    !!              -   !  1998     (O. Aumont) additions 
    8    !!              -   !  1999     (C. Le Quere) modifications 
    9    !!             1.0  !  2004     (O. Aumont) modifications 
    10    !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    11    !!                  !  2011-02  (J. Simeon, J. Orr) Include total atm P correction  
     6   !! History :   -   !  1988-07  (E. MAIER-REIMER) Original code 
     7   !!             -   !  1998     (O. Aumont) additions 
     8   !!             -   !  1999     (C. Le Quere) modifications 
     9   !!            1.0  !  2004     (O. Aumont) modifications 
     10   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
     11   !!                 !  2011-02  (J. Simeon, J. Orr) Include total atm P correction  
    1212   !!---------------------------------------------------------------------- 
    1313   !!   p4z_flx       :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE 
     
    1515   !!   p4z_patm      :   Read sfc atm pressure [atm] for each grid cell 
    1616   !!---------------------------------------------------------------------- 
    17    USE oce_trc                      !  shared variables between ocean and passive tracers  
    18    USE trc                          !  passive tracers common variables 
    19    USE sms_pisces                   !  PISCES Source Minus Sink variables 
    20    USE p4zche                       !  Chemical model 
    21    USE prtctl_trc                   !  print control for debugging 
    22    USE iom                          !  I/O manager 
    23    USE fldread                      !  read input fields 
     17   USE oce_trc        !  shared variables between ocean and passive tracers  
     18   USE trc            !  passive tracers common variables 
     19   USE sms_pisces     !  PISCES Source Minus Sink variables 
     20   USE p4zche         !  Chemical model 
     21   USE prtctl_trc     !  print control for debugging 
     22   USE iom            !  I/O manager 
     23   USE fldread        !  read input fields 
    2424 
    2525   IMPLICIT NONE 
     
    3030   PUBLIC   p4z_flx_alloc   
    3131 
    32    !                               !!** Namelist  nampisext  ** 
    33    REAL(wp)          ::  atcco2     !: pre-industrial atmospheric [co2] (ppm)     
    34    LOGICAL           ::  ln_co2int  !: flag to read in a file and interpolate atmospheric pco2 or not 
    35    CHARACTER(len=34) ::  clname     !: filename of pco2 values 
    36    INTEGER           ::  nn_offset  !: Offset model-data start year (default = 0)  
     32   !                                 !!** Namelist  nampisext  ** 
     33   REAL(wp)          ::   atcco2      !: pre-industrial atmospheric [co2] (ppm)   
     34   LOGICAL           ::   ln_co2int   !: flag to read in a file and interpolate atmospheric pco2 or not 
     35   CHARACTER(len=34) ::   clname      !: filename of pco2 values 
     36   INTEGER           ::   nn_offset   !: Offset model-data start year (default = 0)  
    3737 
    3838   !!  Variables related to reading atmospheric CO2 time history     
    39    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) :: atcco2h, years 
    40    INTEGER  :: nmaxrec, numco2 
    41  
    42    !                               !!* nampisatm namelist (Atmospheric PRessure) * 
     39   INTEGER                                   ::   nmaxrec, numco2   ! 
     40   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   atcco2h, years    ! 
     41 
     42   !                                  !!* nampisatm namelist (Atmospheric PRessure) * 
    4343   LOGICAL, PUBLIC ::   ln_presatm     !: ref. pressure: global mean Patm (F) or a constant (F) 
    4444   LOGICAL, PUBLIC ::   ln_presatmco2  !: accounting for spatial atm CO2 in the compuation of carbon flux (T) or not (F) 
    4545 
    46    REAL(wp) , ALLOCATABLE, SAVE, DIMENSION(:,:) ::  patm      ! atmospheric pressure at kt                 [N/m2] 
    47    TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::  sf_patm   ! structure of input fields (file informations, fields read) 
    48    TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::  sf_atmco2 ! structure of input fields (file informations, fields read) 
    49  
    50    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: satmco2   !: atmospheric pco2  
    51  
    52    REAL(wp) ::  xconv  = 0.01_wp / 3600._wp !: coefficients for conversion  
     46   REAL(wp) , ALLOCATABLE, SAVE, DIMENSION(:,:) ::   patm      ! atmospheric pressure at kt                 [N/m2] 
     47   TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::   sf_patm   ! structure of input fields (file informations, fields read) 
     48   TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::   sf_atmco2 ! structure of input fields (file informations, fields read) 
     49 
     50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  satmco2   !: atmospheric pco2  
     51 
     52   REAL(wp) ::   xconv  = 0.01_wp / 3600._wp  !: coefficients for conversion  
    5353 
    5454   !!---------------------------------------------------------------------- 
     
    7070      !!              - Add option for time-interpolation of atcco2.txt   
    7171      !!--------------------------------------------------------------------- 
    72       ! 
    7372      INTEGER, INTENT(in) ::   kt, knt   ! 
    7473      ! 
     
    7978      REAL(wp) ::   zph, zdic, zsch_o2, zsch_co2 
    8079      REAL(wp) ::   zyr_dec, zdco2dt 
    81       CHARACTER (len=25) :: charout 
    82       REAL(wp), DIMENSION(jpi,jpj) :: zkgco2, zkgo2, zh2co3, zoflx,  zpco2atm   
    83       REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zw2d 
     80      CHARACTER (len=25) ::   charout 
     81      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3, zoflx,  zpco2atm   
     82      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zw2d 
    8483      !!--------------------------------------------------------------------- 
    8584      ! 
    8685      IF( ln_timing )   CALL timing_start('p4z_flx') 
    8786      ! 
    88  
    8987      ! SURFACE CHEMISTRY (PCO2 AND [H+] IN 
    9088      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION 
    9189      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2 
    9290 
    93       IF( kt /= nit000 .AND. .NOT.l_co2cpl .AND. knt == 1 ) CALL p4z_patm( kt )    ! Get sea-level pressure (E&K [1981] climatology) for use in flux calcs 
     91      IF( kt /= nit000 .AND. .NOT.l_co2cpl .AND. knt == 1 )   CALL p4z_patm( kt )   ! Get sea-level pressure (E&K [1981] climatology) for use in flux calcs 
    9492 
    9593      IF( ln_co2int .AND. .NOT.ln_presatmco2 .AND. .NOT.l_co2cpl ) THEN  
     
    226224      !! ** Method  :   Read the nampisext namelist and check the parameters 
    227225      !!      called at the first timestep (nittrc000) 
     226      !! 
    228227      !! ** input   :   Namelist nampisext 
    229228      !!---------------------------------------------------------------------- 
    230       INTEGER ::   jm 
    231       INTEGER ::   ios   ! Local integer  
    232       ! 
     229      INTEGER ::   jm, ios   ! Local integer  
     230      !! 
    233231      NAMELIST/nampisext/ln_co2int, atcco2, clname, nn_offset 
    234232      !!---------------------------------------------------------------------- 
    235       ! 
    236  
     233      IF(lwp) THEN 
     234         WRITE(numout,*) 
     235         WRITE(numout,*) ' p4z_flx_init : atmospheric conditions for air-sea flux calculation' 
     236         WRITE(numout,*) ' ~~~~~~~~~~~~' 
     237      ENDIF 
     238      ! 
    237239      REWIND( numnatp_ref )              ! Namelist nampisext in reference namelist : Pisces atm. conditions 
    238240      READ  ( numnatp_ref, nampisext, IOSTAT = ios, ERR = 901) 
    239 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisext in reference namelist', lwp ) 
    240  
     241901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisext in reference namelist', lwp ) 
    241242      REWIND( numnatp_cfg )              ! Namelist nampisext in configuration namelist : Pisces atm. conditions 
    242243      READ  ( numnatp_cfg, nampisext, IOSTAT = ios, ERR = 902 ) 
    243 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisext in configuration namelist', lwp ) 
     244902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisext in configuration namelist', lwp ) 
    244245      IF(lwm) WRITE ( numonp, nampisext ) 
    245246      ! 
    246247      IF(lwp) THEN                         ! control print 
    247          WRITE(numout,*) ' ' 
    248          WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext' 
    249          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    250          WRITE(numout,*) '    Choice for reading in the atm pCO2 file or constant value, ln_co2int =', ln_co2int 
    251          WRITE(numout,*) ' ' 
    252       ENDIF 
     248         WRITE(numout,*) '   Namelist : nampisext --- parameters for air-sea exchange' 
     249         WRITE(numout,*) '      reading in the atm pCO2 file or constant value   ln_co2int =', ln_co2int 
     250      ENDIF 
     251 
     252!!gm  BUG !!!   ===>>>  ln_presatm and ln_presatmco2 are used below, but read in namelist  
     253!!gm                    at the end of the routine via a CALL to CALL p4z_patm( nit000 ) 
     254 
    253255     IF( .NOT.ln_co2int .AND. .NOT.ln_presatmco2 ) THEN 
    254256         IF(lwp) THEN                         ! control print 
    255             WRITE(numout,*) '    Constant Atmospheric pCO2 value  atcco2    =', atcco2 
    256             WRITE(numout,*) ' ' 
     257            WRITE(numout,*) '         Constant Atmospheric pCO2 value               atcco2    =', atcco2 
    257258         ENDIF 
    258259         satmco2(:,:)  = atcco2      ! Initialisation of atmospheric pco2 
    259260      ELSEIF( ln_co2int .AND. .NOT.ln_presatmco2 ) THEN 
    260261         IF(lwp)  THEN 
    261             WRITE(numout,*) '    Atmospheric pCO2 value  from file clname      =', TRIM( clname ) 
    262             WRITE(numout,*) '    Offset model-data start year      nn_offset   =', nn_offset 
    263             WRITE(numout,*) ' ' 
     262            WRITE(numout,*) '         Constant Atmospheric pCO2 value               atcco2    =', atcco2 
     263            WRITE(numout,*) '         Atmospheric pCO2 value  from file             clname    =', TRIM( clname ) 
     264            WRITE(numout,*) '         Offset model-data start year                  nn_offset =', nn_offset 
    264265         ENDIF 
    265266         CALL ctl_opn( numco2, TRIM( clname) , 'OLD', 'FORMATTED', 'SEQUENTIAL', -1 , numout, lwp ) 
     
    270271         END DO 
    271272 100     nmaxrec = jm - 1  
    272          ALLOCATE( years  (nmaxrec) )     ;      years  (:) = 0._wp 
    273          ALLOCATE( atcco2h(nmaxrec) )     ;      atcco2h(:) = 0._wp 
    274  
     273         ALLOCATE( years  (nmaxrec) )   ;   years  (:) = 0._wp 
     274         ALLOCATE( atcco2h(nmaxrec) )   ;   atcco2h(:) = 0._wp 
     275         ! 
    275276         REWIND(numco2) 
    276277         DO jm = 1, nmaxrec          ! get  xCO2 data 
     
    282283         IF(lwp)  THEN 
    283284            WRITE(numout,*) '    Spatialized Atmospheric pCO2 from an external file' 
    284             WRITE(numout,*) ' ' 
    285285         ENDIF 
    286286      ELSE 
    287287         IF(lwp)  THEN 
    288288            WRITE(numout,*) '    Spatialized Atmospheric pCO2 from an external file' 
    289             WRITE(numout,*) ' ' 
    290289         ENDIF 
    291290      ENDIF 
     
    304303      !!                  ***  ROUTINE p4z_atm  *** 
    305304      !! 
    306       !! ** Purpose :   Read and interpolate the external atmospheric sea-levl pressure 
     305      !! ** Purpose :   Read and interpolate the external atmospheric sea-level pressure 
    307306      !! ** Method  :   Read the files and interpolate the appropriate variables 
    308307      !! 
    309308      !!---------------------------------------------------------------------- 
    310       INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    311       ! 
    312       INTEGER            ::  ierr 
    313       INTEGER            ::  ios      ! Local integer output status for namelist read 
    314       CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files 
    315       TYPE(FLD_N)        ::  sn_patm  ! informations about the fields to be read 
    316       TYPE(FLD_N)        ::  sn_atmco2 ! informations about the fields to be read 
     309      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     310      ! 
     311      INTEGER            ::   ierr, ios   ! Local integer 
     312      CHARACTER(len=100) ::   cn_dir      ! Root directory for location of ssr files 
     313      TYPE(FLD_N)        ::   sn_patm     ! informations about the fields to be read 
     314      TYPE(FLD_N)        ::   sn_atmco2   ! informations about the fields to be read 
    317315      !! 
    318316      NAMELIST/nampisatm/ ln_presatm, ln_presatmco2, sn_patm, sn_atmco2, cn_dir 
    319317      !!---------------------------------------------------------------------- 
    320  
    321       !                                         ! ----------------------- ! 
    322       IF( kt == nit000 ) THEN                   ! First call kt=nittrc000 ! 
    323  
     318      ! 
     319      IF( kt == nit000 ) THEN    !==  First call kt=nittrc000  ==! 
     320         ! 
     321         IF(lwp) THEN 
     322            WRITE(numout,*) 
     323            WRITE(numout,*) ' p4z_patm : sea-level atmospheric pressure' 
     324            WRITE(numout,*) ' ~~~~~~~~' 
     325         ENDIF 
     326         ! 
    324327         REWIND( numnatp_ref )              ! Namelist nampisatm in reference namelist : Pisces atm. sea level pressure file 
    325328         READ  ( numnatp_ref, nampisatm, IOSTAT = ios, ERR = 901) 
    326329901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in reference namelist', lwp ) 
    327  
    328330         REWIND( numnatp_cfg )              ! Namelist nampisatm in configuration namelist : Pisces atm. sea level pressure file  
    329331         READ  ( numnatp_cfg, nampisatm, IOSTAT = ios, ERR = 902 ) 
    330 902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in configuration namelist', lwp ) 
     332902      IF( ios >  0 )  CALL ctl_nam ( ios , 'nampisatm in configuration namelist', lwp ) 
    331333         IF(lwm) WRITE ( numonp, nampisatm ) 
    332334         ! 
    333335         ! 
    334336         IF(lwp) THEN                                 !* control print 
    335             WRITE(numout,*) 
    336             WRITE(numout,*) '   Namelist nampisatm : Atmospheric Pressure as external forcing' 
    337             WRITE(numout,*) '      constant atmopsheric pressure (F) or from a file (T)  ln_presatm = ', ln_presatm 
    338             WRITE(numout,*) '      spatial atmopsheric CO2 for flux calcs  ln_presatmco2 = ', ln_presatmco2 
    339             WRITE(numout,*) 
     337            WRITE(numout,*) '   Namelist : nampisatm --- Atmospheric Pressure as external forcing' 
     338            WRITE(numout,*) '      constant atmopsheric pressure (F) or from a file (T)  ln_presatm    = ', ln_presatm 
     339            WRITE(numout,*) '      spatial atmopsheric CO2 for flux calcs                ln_presatmco2 = ', ln_presatmco2 
    340340         ENDIF 
    341341         ! 
     
    358358         ENDIF 
    359359         ! 
    360          IF( .NOT.ln_presatm )   patm(:,:) = 1.e0    ! Initialize patm if no reading from a file 
     360         IF( .NOT.ln_presatm )   patm(:,:) = 1._wp    ! Initialize patm if no reading from a file 
    361361         ! 
    362362      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.