Changeset 3838 for palm/trunk


Ignore:
Timestamp:
Mar 28, 2019 6:09:50 PM (5 years ago)
Author:
forkel
Message:

some formatting and comments for chem_photolysis_mod.f90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/chem_photolysis_mod.f90

    r3824 r3838  
    2626! -----------------
    2727! $Id$
     28! some formatting and comments added
     29!
     30! 3824 2019-03-27 15:56:16Z pavelkrc
    2831! unused variables removed
    2932!
     
    5356! ------------
    5457!> photolysis models and interfaces (Adapted from photolysis_model_mod.f90)
    55 !> @todo Alles!
     58!> @todo more complex scheme, add shading
    5659!------------------------------------------------------------------------------!
    5760 MODULE chem_photolysis_mod
     
    6366        ONLY:  time_since_reference_point
    6467
    65     USE pegrid,             ONLY: myid, threads_per_task
     68    USE pegrid,                                                                &
     69        ONLY: myid, threads_per_task
    6670
    6771    USE indices,                                                               &
     
    102106
    103107! Names for predefined fixed photolysis frequencies at zenith angle 0
    104     CHARACTER(LEN=10), PARAMETER, DIMENSION(nconst) :: names_c =  (/                    &
    105                      'J_O31D    ','J_O33P    ','J_NO2     ','J_HNO3    ','J_RCHO    ', &
    106                      'J         ','J         ','J         ','J         ','J         ', &
     108    CHARACTER(LEN=10), PARAMETER, DIMENSION(nconst) :: names_c =  (/                     &
     109                     'J_O31D    ','J_O33P    ','J_NO2     ','J_HNO3    ','J_RCHO    ',   &
     110                     'J         ','J         ','J         ','J         ','J         ',   &
    107111                     'J         ','J         ','J         ','J         ','J         ' /)
    108 ! Photolysis frequency at zenith angle 0 in 1/s
    109     REAL(wp), PARAMETER, DIMENSION(nconst) :: phot0 =  (/                             &
    110                       2.489E-05_wp,3.556E-04_wp, 8.89E-03_wp,5.334E-07_wp,3.734E-05_wp, &
    111                       0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp, &
     112! Photolysis frequency at zenith angle 0 degrees in 1/s
     113    REAL(wp), PARAMETER, DIMENSION(nconst) :: phot0 =  (/                                &
     114                      2.489E-05_wp,3.556E-04_wp, 8.89E-03_wp,5.334E-07_wp,3.734E-05_wp,  &
     115                      0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,  &
    112116                      0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp /)
    113117
    114 
    115 !-- Parameters for simple photolysis frequencies
    116     INTEGER,PARAMETER :: nsimple = 15               !< available predefined photolysis prequencies for simpel parameterisation
     118!-- Parameters for simple photolysis frequencies from MCM (http://mcm.leeds.ac.uk/MCM)
     119!-- Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
     120   INTEGER,PARAMETER :: nsimple = 15               !< available predefined photolysis prequencies for simple parameterisation
    117121! Names for simple photolysis frequencies parameterisation (
    118      CHARACTER(LEN=10), PARAMETER, DIMENSION(nsimple) :: names_s =  (/                 &
    119                      'J_O31D    ','J_O33P    ','J_H2O2    ','J_NO2     ','J_NO3_A   ', &
    120                      'J_NO3_B   ','J_HONO    ','J_HNO3    ','J_HCHO_A  ','J_HCHO_B  ', &
     122    CHARACTER(LEN=10), PARAMETER, DIMENSION(nsimple) :: names_s =  (/                    &
     123                     'J_O31D    ','J_O33P    ','J_H2O2    ','J_NO2     ','J_NO3_A   ',   &
     124                     'J_NO3_B   ','J_HONO    ','J_HNO3    ','J_HCHO_A  ','J_HCHO_B  ',   &
    121125                     'J_CH3CHO  ','J         ','J         ','J         ','J_RCHO    ' /)
    122126
    123 !-- Parameters for simeple photolysis frequencies from MCM (http://mcm.leeds.ac.uk/MCM)
    124 !-- Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
    125      REAL(wp), PARAMETER, DIMENSION(nconst) :: par_l =  (/                             &
    126                      6.073E-05_wp,4.775E-04_wp,1.041E-05_wp,1.165E-02_wp,2.485E-02_wp, &
    127                      1.747E-01_wp,2.644E-03_wp,9.312E-07_wp,4.642E-05_wp,6.853E-05_wp, &
    128                      7.344E-06_wp,0.0000E00_wp,0.0000E00_wp,0.000E00_wp, 6.853E-05_wp /)
    129 
    130      REAL(wp), PARAMETER, DIMENSION(nconst) :: par_m =  (/                             &
    131                          1.743_wp,    0.298_wp,    0.723_wp,    0.244_wp,    0.168_wp, &
    132                          0.155_wp,    0.261_wp,    1.230_wp,    0.762_wp,    0.477_wp, &
    133                          1.202_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.477_wp /)
    134 
    135      REAL(wp), PARAMETER, DIMENSION(nconst) :: par_n =  (/                             &
    136                          0.474_wp,    0.080_wp,    0.279_wp,    0.267_wp,    0.108_wp, &
    137                          0.125_wp,    0.288_wp,    0.307_wp,    0.353_wp,    0.323_wp, &
    138                          0.417_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.323_wp /)
    139 
    140 
    141     REAL(wp)     :: cosz = 0.7_wp                   !< cosine of Zenith angle (45 deg, if not specified otherwise)
     127!-- Species dependent parameters for simple photolysis frequencies from MCM (http://mcm.leeds.ac.uk/MCM)
     128!-- J = l*COSx@m*EXP(-n*SECx)  with l,m,n named par_l etc., x is the zenith angle
     129   REAL(wp), PARAMETER, DIMENSION(nconst) :: par_l =  (/                                 &
     130                       6.073E-05_wp,4.775E-04_wp,1.041E-05_wp,1.165E-02_wp,2.485E-02_wp, &
     131                       1.747E-01_wp,2.644E-03_wp,9.312E-07_wp,4.642E-05_wp,6.853E-05_wp, &
     132                       7.344E-06_wp,0.0000E00_wp,0.0000E00_wp,0.000E00_wp, 6.853E-05_wp /)
     133
     134   REAL(wp), PARAMETER, DIMENSION(nconst) :: par_m =  (/                                 &
     135                           1.743_wp,    0.298_wp,    0.723_wp,    0.244_wp,    0.168_wp, &
     136                           0.155_wp,    0.261_wp,    1.230_wp,    0.762_wp,    0.477_wp, &
     137                           1.202_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.477_wp /)
     138
     139   REAL(wp), PARAMETER, DIMENSION(nconst) :: par_n =  (/                                 &
     140                           0.474_wp,    0.080_wp,    0.279_wp,    0.267_wp,    0.108_wp, &
     141                           0.125_wp,    0.288_wp,    0.307_wp,    0.353_wp,    0.323_wp, &
     142                           0.417_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.323_wp /)
     143
     144
     145    REAL(wp)     :: cosz = 0.7_wp                   !< cosine of fixed zenith angle (45 deg, if not specified otherwise)
    142146
    143147!
     
    158162    END INTERFACE photolysis_control
    159163
    160 
    161164    SAVE
    162165
     
    166169
    167170    PUBLIC  photolysis_scheme
    168 !
    169171
    170172 CONTAINS
     
    176178!> This subroutine controls the calls of the photolysis schemes
    177179!------------------------------------------------------------------------------!
    178     SUBROUTINE photolysis_control
     180 SUBROUTINE photolysis_control
    179181 
    180        IMPLICIT NONE
    181 
    182        SELECT CASE ( TRIM( photolysis_scheme ) )
    183 
    184           CASE ( 'constant' )
    185              CALL photolysis_constant
     182    IMPLICIT NONE
     183
     184    SELECT CASE ( TRIM( photolysis_scheme ) )
     185
     186       CASE ( 'constant' )
     187          CALL photolysis_constant
    186188         
    187           CASE ( 'simple' )
    188              CALL photolysis_simple
     189       CASE ( 'simple' )
     190          CALL photolysis_simple
    189191       
    190 !         CASE ( 'fastj' )
    191 !            CALL photolysis_fastj
    192 
    193           CASE DEFAULT
    194 
    195        END SELECT
    196 
    197 
    198     END SUBROUTINE photolysis_control
     192!      CASE ( 'fastj' )
     193!         CALL photolysis_fastj
     194
     195       CASE DEFAULT
     196
     197    END SELECT
     198
     199
     200 END SUBROUTINE photolysis_control
    199201
    200202
     
    205207!> Default zenith angle is 45 deg
    206208!------------------------------------------------------------------------------!
    207     SUBROUTINE photolysis_constant
    208 
    209        IMPLICIT NONE
    210 
    211        INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
    212 
    213        DO iphot = 1,nphot
    214           DO iav = 1,nconst
    215              IF ( TRIM( names_c(iav) ) == TRIM( phot_names(iphot) ) ) then
    216 !--             Prescribe fixed photolysis frequencies  [1/s]
    217                 phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =    &
     209 SUBROUTINE photolysis_constant
     210
     211    IMPLICIT NONE
     212
     213    INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
     214
     215    DO  iphot = 1, nphot
     216       DO  iav = 1, nconst
     217          IF ( TRIM( names_c(iav) ) == TRIM( phot_names(iphot) ) ) THEN
     218!--  Prescribe fixed photolysis frequencies  [1/s]
     219                phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =                      &
    218220                             phot0(iav) * cosz
     221          ENDIF
     222       ENDDO
     223    ENDDO
     224
     225
     226 END SUBROUTINE photolysis_constant
     227
     228
     229!------------------------------------------------------------------------------!
     230! Description:
     231! ------------
     232!> This scheme applies a simple parameterisation for clear sky photolysis frequencies
     233!> from the Master Chemical Mechanism, MCM v3.2 (http://mcm.leeds.ac.uk/MCM).
     234!> Reference: Saunders et al., Atmos. Chem. Phys., 3, 161, 2003
     235!> J = l*COSx@m*EXP(-n*SECx)  with l,m,n named par_l etc., x is the zenith angle
     236!------------------------------------------------------------------------------!
     237 SUBROUTINE photolysis_simple
     238
     239    USE radiation_model_mod,                                                   &
     240        ONLY:  calc_zenith, cos_zenith
     241
     242    IMPLICIT NONE
     243
     244    INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
     245    REAL(wp)     :: coszi     !< 1./cosine of zenith angle
     246
     247    DO  iphot = 1, nphot
     248       phot_frequen(iphot)%freq = 0.0_wp
     249    ENDDO
     250
     251    CALL calc_zenith
     252
     253    IF ( cos_zenith > 0.0_wp ) THEN
     254       coszi = 1. / cos_zenith
     255
     256       DO iphot = 1, nphot
     257          DO iav = 1, nsimple
     258             IF ( TRIM( names_s(iav) ) == TRIM( phot_names(iphot) ) ) then
     259                phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =                                &
     260                         par_l(iav) * cos_zenith**par_m(iav) * EXP( -par_n(iav) * coszi )
    219261             ENDIF
    220262          ENDDO
    221263       ENDDO
    222 
    223     END SUBROUTINE photolysis_constant
    224 
    225 
    226 !------------------------------------------------------------------------------!
    227 ! Description:
    228 ! ------------
    229 !> This scheme applies a simple parameterisation for clear sky photolysis frequencies
    230 !> from the Master Chemical Mechanism, MCM v3.2 (http://mcm.leeds.ac.uk/MCM).
    231 !> Reference: Saunders et al., Atmos. Chem. Phys., 3, 161, 2003
    232 !------------------------------------------------------------------------------!
    233     SUBROUTINE photolysis_simple
    234 
    235        USE radiation_model_mod,                                                   &
    236            ONLY:  calc_zenith, cos_zenith
    237 
    238        IMPLICIT NONE
    239 
    240        INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
    241        REAL(wp)     :: coszi     !< 1./cosine of zenith angle
    242 
    243        DO iphot = 1,nphot
    244           phot_frequen(iphot)%freq = 0.0_wp
    245        ENDDO
    246 
    247        CALL calc_zenith
    248 
    249        IF ( cos_zenith > 0.0_wp ) THEN
    250           coszi = 1. / cos_zenith
    251 
    252           DO iphot = 1,nphot
    253              DO iav = 1,nsimple
    254                 IF ( TRIM( names_s(iav) ) == TRIM( phot_names(iphot) ) ) then
    255                    phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =    &
    256                                 par_l(iav) * cos_zenith**par_m(iav) *  EXP( -par_n(iav) * coszi )
    257                 ENDIF
    258              ENDDO
    259           ENDDO
    260        ENDIF
    261     END SUBROUTINE photolysis_simple
     264    ENDIF
     265
     266
     267 END SUBROUTINE photolysis_simple
    262268
    263269 END MODULE chem_photolysis_mod
Note: See TracChangeset for help on using the changeset viewer.