Changeset 2768


Ignore:
Timestamp:
Jan 24, 2018 3:38:29 PM (6 years ago)
Author:
kanani
Message:

Added parameter check, reduced line length, some formatting

Location:
palm/trunk
Files:
3 edited

Legend:

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

    r2766 r2768  
    2727! -----------------
    2828! $Id$
     29! Shorten lines to maximum length of 132 characters
     30!
     31! 2766 2018-01-22 17:17:47Z kanani
    2932! Removed preprocessor directive __chem
    3033!
     
    813816
    814817            IF(myid == 0)  THEN
    815                WRITE(6,'(a,3x,a,3x,a,e12.4)')  '   Species:     ',chem_species(lsp)%name(1:7),' Initial Value = ',chem_species(lsp)%conc(nzb,nysg,nxlg)
     818               WRITE(6,'(a,3x,a,3x,a,e12.4)')  '   Species:     ',chem_species(lsp)%name(1:7),' &
     819                                        Initial Value = ',chem_species(lsp)%conc(nzb,nysg,nxlg)
    816820            ENDIF
    817821         ENDDO
     
    12371241       DO lsp=1,nspec
    12381242          IF (TRIM(spec_name) == TRIM(chem_species(lsp)%name))   THEN
    1239              IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ',TRIM(variable),' ',TRIM(chem_species(lsp)%name)       
     1243             IF(myid == 0 .AND. chem_debug0 )  WRITE(6,*) 'Output of species ',TRIM(variable),'  &
     1244                                                          ',TRIM(chem_species(lsp)%name)       
    12401245             
    12411246             IF (av == 0) THEN
     
    15071512!------------------------------------------------------------------------------!
    15081513
    1509  SUBROUTINE chem_tendency ( cs_scalar_p, cs_scalar, tcs_scalar_m, pr_init_cs, i, j, i_omp_start, tn, ilsp, flux_s_cs, diss_s_cs, flux_l_cs, diss_l_cs )
     1514 SUBROUTINE chem_tendency ( cs_scalar_p, cs_scalar, tcs_scalar_m, pr_init_cs,  &
     1515                            i, j, i_omp_start, tn, ilsp, flux_s_cs, diss_s_cs, &
     1516                            flux_l_cs, diss_l_cs )
    15101517    USE pegrid         
    15111518    USE advec_ws,        ONLY:  advec_s_ws
     
    15141521    USE diffusion_s_mod, ONLY:  diffusion_s
    15151522    USE indices,         ONLY:  wall_flags_0
    1516     USE surface_mod,                                                                            &
    1517                          ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
    1518                                  surf_usm_v
     1523    USE surface_mod,     ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
     1524                                surf_usm_v
    15191525!> Only one chem_spcs recieved prog_eqns at time.
    15201526!> cem_tendency is called in prog_eqns over loop => nvar
     
    15221528    IMPLICIT NONE
    15231529
    1524     REAL(wp), DIMENSION(:,:,:), POINTER                         :: cs_scalar_p, cs_scalar, tcs_scalar_m
     1530    REAL(wp), DIMENSION(:,:,:), POINTER   :: cs_scalar_p, cs_scalar, tcs_scalar_m
    15251531
    15261532    INTEGER(iwp),INTENT(IN) :: i, j, i_omp_start, tn, ilsp
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r2766 r2768  
    2525! -----------------
    2626! $Id$
     27! Added check for output quantity pcm_heatrate, some formatting
     28!
     29! 2766 2018-01-22 17:17:47Z kanani
    2730! Increased LEN of canopy mode to 30
    2831!
     
    194197    REAL(wp) ::  leaf_scalar_exch_coeff = 0.0_wp  !< canopy scalar exchange coeff.
    195198    REAL(wp) ::  leaf_surface_conc = 0.0_wp       !< leaf surface concentration
     199    REAL(wp) ::  lsc = 0.0_wp                     !< leaf surface concentration
    196200    REAL(wp) ::  lsec = 0.0_wp                    !< leaf scalar exchange coeff.
    197     REAL(wp) ::  lsc = 0.0_wp                     !< leaf surface concentration
    198201    REAL(wp) ::  prototype_lad                    !< prototype leaf area density for computing effective optical depth
    199202
     
    204207    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pre_lad        !< preliminary lad
    205208   
    206     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::                                 &
    207        pc_heating_rate                                    !< plant canopy heating rate
    208     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf !< cumulative lai for heatflux calc.
    209     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s      !< lad on scalar-grid
    210 
     209    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf       !< cumulative lai for heatflux calc.
     210    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s            !< lad on scalar-grid
     211    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pc_heating_rate  !< plant canopy heating rate
    211212
    212213    SAVE
     
    287288
    288289       CASE ( 'pcm_heatrate' )
     290          IF ( cthf == 0.0_wp )  THEN
     291             message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     292                              'res setting of parameter cthf /= 0.0'
     293             CALL message( 'pcm_check_data_output', 'PA1000', 1, 2, 0, 6, 0 )
     294          ENDIF
    289295          unit = 'K s-1'
    290296   
     
    323329          message_string = 'plant_canopy = .TRUE. requires a non-zero drag '// &
    324330                           'coefficient & given value is canopy_drag_coeff = 0.0'
    325           CALL message( 'check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
     331          CALL message( 'pcm_check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
    326332       ENDIF
    327333   
     
    331337                           'of the leaf area density profile requires '    //  &
    332338                           'both alpha_lad and beta_lad to be /= 9999999.9'
    333           CALL message( 'check_parameters', 'PA0118', 1, 2, 0, 6, 0 )
     339          CALL message( 'pcm_check_parameters', 'PA0118', 1, 2, 0, 6, 0 )
    334340       ENDIF
    335341   
     
    339345                           'a non-zero lai_beta, but given value is '      //  &
    340346                           'lai_beta = 0.0'
    341           CALL message( 'check_parameters', 'PA0119', 1, 2, 0, 6, 0 )
     347          CALL message( 'pcm_check_parameters', 'PA0119', 1, 2, 0, 6, 0 )
    342348       ENDIF
    343349
     
    349355                           'function for the construction of the leaf area '// &
    350356                           'density profile'
    351           CALL message( 'check_parameters', 'PA0120', 1, 2, 0, 6, 0 )
     357          CALL message( 'pcm_check_parameters', 'PA0120', 1, 2, 0, 6, 0 )
    352358       ENDIF
    353359
     
    355361          message_string = 'plant_canopy = .TRUE. requires cloud_scheme /=' // &
    356362                          ' seifert_beheng'
    357           CALL message( 'check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
     363          CALL message( 'pcm_check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
    358364       ENDIF
    359365!
     
    365371                           TRIM( coupling_char ) // ' requires ' //            &
    366372                           'canopy_mode = read_from_file_3d'
    367           CALL message( 'check_parameters', 'PA0999', 1, 2, 0, 6, 0 )
     373          CALL message( 'pcm_check_parameters', 'PA0999', 1, 2, 0, 6, 0 )
    368374       ENDIF
    369375
     
    844850!--    When using the urban surface model (USM), canopy heating (pc_heating_rate)
    845851!--    by radiation is calculated in the USM.
    846        IF ( cthf /= 0.0_wp  .AND. .NOT.  urban_surface)  THEN
     852       IF ( cthf /= 0.0_wp  .AND. .NOT.  urban_surface )  THEN
    847853
    848854          ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                 &
  • palm/trunk/UTIL/chemistry/gasphase_preproc/kpp4palm/src/create_kpp_module.C

    r2696 r2768  
    1212//Current revisions:
    1313//------------------
    14 //
    15 //
     14/
     15/ 
    1616//Former revisions:
    1717//-----------------
    1818//$Id: create_kpp_module.C 2470 2017-09-14 13:56:42Z forkel $
     19// Removed preprocessor directive __chem again
     20//
     21/ 2017-09-14 13:56:42Z forkel $
    1922//
    2023//
     
    5255// Generate first module lines
    5356
    54    string first_line="MODULE " + module_name;
    55    mz_kpp.add_line(first_line);
    56    mz_kpp.add_line(" ");
    57    mz_kpp.add_line("#if defined( __chem )");
    58    mz_kpp.add_line(" ");
     57     string first_line="MODULE " + module_name;
     58     mz_kpp.add_line(first_line);
     59     mz_kpp.add_line("!");
     60//   mz_kpp.add_line("#if defined( __chem )");
     61//   mz_kpp.add_line(" ");
    5962
    6063//    string e5_line = first_line +"_e5";
     
    221224// Finish module
    222225
    223    mz_kpp.add_line("#endif");
    224    string last_line="END MODULE " + module_name;
    225    mz_kpp.add_line("");
    226    mz_kpp.add_line(last_line);
     226//   mz_kpp.add_line("#endif");
     227     string last_line="END MODULE " + module_name;
     228     mz_kpp.add_line("");
     229     mz_kpp.add_line(last_line);
    227230
    228231// Handle e5 module
Note: See TracChangeset for help on using the changeset viewer.